gappleto97/p2p-project

View on GitHub
sm_src/SM2P.st

Summary

Maintainability
Test Coverage
Object subclass: #InternalMessage
    instanceVariableNames: 'msg_type sender payload compression time'
    classVariableNames: ''
    poolDictionaries: ''
    category: 'Peer-to-Peer'!

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 16:28'!
id

    ^''! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 14:40'!
msg_type

    ^msg_type! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 16:28'!
packets

    | packets |
    packets := OrderedCollection new.
    packets add: self msg_type;
            add: self sender;
            add: self id asByteArray;
            add: self time_58 asByteArray;
            addAll: self payload.
    ^packets.! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 14:41'!
payload

    ^payload! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 14:41'!
sender

    ^sender! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 14:40'!
time

    ^time! !

!InternalMessage methodsFor: 'accessing' stamp: 'GVA 11/17/2016 16:27'!
time_58

    ^SM2P to_base_58: time! !


!InternalMessage methodsFor: 'serialization' stamp: 'GVA 11/17/2016 16:34'!
asByteArray

    ^self asOrderedCollection asByteArray
    ! !

!InternalMessage methodsFor: 'serialization' stamp: 'GVA 11/17/2016 16:40'!
asOrderedCollection

    | arr |
    arr := OrderedCollection new.
    self packets do: [: each |
        arr addAll: (SM2P pack_value: each size length: 4);
            addAll: each.].
    arr addAllFirst: (SM2P pack_value: arr size length: 4).
    ^arr.! !

!InternalMessage methodsFor: 'serialization' stamp: 'GVA 11/17/2016 16:32'!
asString

    ^self asByteArray asString! !


!InternalMessage methodsFor: 'setters' stamp: 'GVA 11/17/2016 15:20'!
setCompression: compressions

    compression := compressions.! !

!InternalMessage methodsFor: 'setters' stamp: 'GVA 11/17/2016 15:20'!
setTime: timestamp

    time := timestamp.! !


!InternalMessage methodsFor: 'private' stamp: 'GVA 11/17/2016 15:20'!
setMsgPayload: load

    payload := load.! !

!InternalMessage methodsFor: 'private' stamp: 'GVA 11/17/2016 15:20'!
setMsgSender: sndr

    sender := sndr.! !

!InternalMessage methodsFor: 'private' stamp: 'GVA 11/17/2016 15:20'!
setMsgType: type

    msg_type := type.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

InternalMessage class
    instanceVariableNames: ''!

!InternalMessage class methodsFor: 'private' stamp: 'GVA 11/17/2016 15:18'!
decompressString: aString compressions: compressions

    ^(aString asByteArray).! !

!InternalMessage class methodsFor: 'private' stamp: 'GVA 11/17/2016 15:18'!
process_string: aByteArray

    | processed pack_lens packets end |
    processed := 1.
      pack_lens := OrderedCollection new.
      packets := OrderedCollection new.
      [processed == ((aByteArray size) + 1)]
        whileFalse: [pack_lens add: (SM2P unpack_value: (aByteArray copyFrom:processed to: (processed+3))).
                              processed := processed + 4.
                    end := processed + (pack_lens at: (pack_lens size)).
                    packets add: (aByteArray copyFrom: processed to: (end - 1)).
                    processed := end].
      ^packets! !

!InternalMessage class methodsFor: 'private' stamp: 'GVA 11/17/2016 15:19'!
sanitizeString: aByteArray sizeless:isSizeless

    ^isSizeless
        ifTrue: [aByteArray]
        ifFalse: [((SM2P unpack_value: (aByteArray copyFrom: 1 to: 4)) == ((aByteArray size) - 4))
            ifTrue: [aByteArray allButFirst: 4]
            ifFalse: [AssertionFailure signal: 'The size header is incorrect, or the check has not been implemented']]! !


!InternalMessage class methodsFor: 'class initialization' stamp: 'GVA 11/17/2016 15:14'!
feed_string: aString

    ^(self feed_string: aString sizeless: false compressions: (Array new: 0))! !

!InternalMessage class methodsFor: 'class initialization' stamp: 'GVA 11/17/2016 15:14'!
feed_string: aString compressions: compressions

    ^(self feed_string: aString sizeless: false compressions: compressions)! !

!InternalMessage class methodsFor: 'class initialization' stamp: 'GVA 11/17/2016 15:14'!
feed_string: aString sizeless: isSizeless

    ^(self feed_string: aString sizeless: isSizeless compressions: (Array new: 0))! !

!InternalMessage class methodsFor: 'class initialization' stamp: 'GVA 11/17/2016 15:14'!
feed_string: aString sizeless: isSizeless compressions: compressions
    "Translates a serialized string into an InternalMessage"

    | temp_string packets msg |
    temp_string := self sanitizeString: aString sizeless: isSizeless.
    temp_string := self decompressString: temp_string compressions: compressions.
    packets := self process_string: temp_string.
    msg := self type: (packets at: 1) sender: (packets at: 2) payload: (packets allButFirst: 4).
    msg setTime: (SM2P from_base_58: (packets at: 4) asString).
    msg setCompression: compressions.
    ^msg.! !

!InternalMessage class methodsFor: 'class initialization' stamp: 'GVA 11/17/2016 15:17'!
type: type sender: sender payload: payload

    | msg |
    msg := (self new).
    msg setMsgType: type;
         setMsgSender: sender;
           setMsgPayload: payload.
    ^msg.! !


SubNet subclass: #SM2P
    instanceVariableNames: ''
    classVariableNames: ''
    poolDictionaries: ''
    category: 'Peer-to-Peer'!

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SM2P class
    instanceVariableNames: ''!

!SM2P class methodsFor: 'helpers' stamp: 'GVA 11/17/2016 17:07'!
to_base_58_helper: aNumber

    | base_58 |
    base_58 := '123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz'.
    ^((aNumber > 0)
        ifTrue: [(SM2P to_base_58_helper: (aNumber // 58)), (base_58 at: (aNumber rem: 58) + 1) asString]
        ifFalse: ['']).! !

!SM2P class methodsFor: 'helpers' stamp: 'GVA 11/17/2016 17:04'!
unpack_value_helper: aByteArray

    ^(aByteArray size > 1)
        ifTrue: [(256 raisedTo: (aByteArray size - 1)) * (aByteArray at: 1) + (self unpack_value_helper: (aByteArray copyWithoutIndex: 1))]
        ifFalse: [aByteArray at: 1]! !


!SM2P class methodsFor: 'versioning' stamp: 'GVA 11/17/2016 17:11'!
node_policy_version

    ^607! !

!SM2P class methodsFor: 'versioning' stamp: 'GVA 11/17/2016 17:11'!
protocol_major_version

    ^0! !

!SM2P class methodsFor: 'versioning' stamp: 'GVA 11/17/2016 17:11'!
protocol_minor_version

    ^5! !

!SM2P class methodsFor: 'versioning' stamp: 'GVA 11/17/2016 17:11'!
protocol_version

    ^(self protocol_major_version asString, '.', self protocol_minor_version asString)! !

!SM2P class methodsFor: 'versioning' stamp: 'GVA 11/17/2016 17:12'!
version_info

    ^(self protocol_version, '.', self node_policy_version asString)! !


!SM2P class methodsFor: 'translation' stamp: 'GVA 11/17/2016 15:21'!
from_base_58: aString
    "Converts a base_58 string into a Number"

    | base_58 |
    base_58 := '123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz'.
    ^(aString size > 0)
        ifFalse: [0]
        ifTrue: [(58 raisedTo: (aString size - 1)) * ((base_58 indexOf: (aString at: 1)) - 1) + (self from_base_58: (aString copyWithoutIndex: 1))]! !

!SM2P class methodsFor: 'translation' stamp: 'GVA 11/17/2016 15:24'!
pack_value: anInteger length: aLength
    "Packs a value into a big-endian string of the given size"

    ^(aLength > 0)
        ifTrue: [((self pack_value: (anInteger // 256) length: (aLength - 1)), (String value: (anInteger rem: 256)))]
        ifFalse: ['']! !

!SM2P class methodsFor: 'translation' stamp: 'GVA 11/17/2016 15:21'!
to_base_58: aNumber
    "Converts a Number into a base_58 string"

    | ret |
    ret := SM2P to_base_58_helper: aNumber.

    ^((ret size = 0)
        ifTrue: ['1']
        ifFalse: [ret])! !

!SM2P class methodsFor: 'translation' stamp: 'GVA 11/17/2016 15:22'!
unpack_value: aString
    "Unpacks a big endian string into a Number"

    ^self unpack_value_helper: (aString asByteArray)! !


Object subclass: #Subnet
    instanceVariableNames: 'name encryption'
    classVariableNames: ''
    poolDictionaries: ''
    category: 'Peer-to-Peer'!
!Subnet commentStamp: 'GVA 11/17/2016 17:15' prior: 0!
This class defines what network label you are looking for. It requires the Cryptography package, or an analagous SHA256 implementation!


!Subnet methodsFor: 'accessing' stamp: 'GVA 11/17/2016 16:54'!
encryption

    ^encryption! !

!Subnet methodsFor: 'accessing' stamp: 'GVA 11/17/2016 17:09'!
id

    | hash info |
    info := self subnet, self encryption, SM2P protocol_version.
    hash := SHA256 new hashStream: (ReadStream on: info).
    ^SM2P to_base_58: (SM2P unpack_value: hash).! !

!Subnet methodsFor: 'accessing' stamp: 'GVA 11/17/2016 16:54'!
subnet

    ^name! !


!Subnet methodsFor: 'private' stamp: 'GVA 11/17/2016 16:58'!
setEncryption: aMethod

    encryption := aMethod! !

!Subnet methodsFor: 'private' stamp: 'GVA 11/17/2016 16:53'!
setSubName: aName

    name := aName! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Subnet class
    instanceVariableNames: ''!

!Subnet class methodsFor: 'as yet unclassified' stamp: 'GVA 11/17/2016 16:52'!
subnet: aName encryption: aMethod

    ^(self new)
        setSubName: aName;
        setEncryption: aMethod;
        yourself.! !