1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-network/sccp/SCCP.st

841 lines
21 KiB
Smalltalk

"
(C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SCCPHelper [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the SCCP message class constants and provide
an easy way to create specific messages.'>
SCCPHelper class >> msgCr [ <category: 'constants'> ^ 16r01 ]
SCCPHelper class >> msgCc [ <category: 'constants'> ^ 16r02 ]
SCCPHelper class >> msgCref [ <category: 'constants'> ^ 16r03 ]
SCCPHelper class >> msgRlsd [ <category: 'constants'> ^ 16r04 ]
SCCPHelper class >> msgRlc [ <category: 'constants'> ^ 16r05 ]
SCCPHelper class >> msgDt1 [ <category: 'constants'> ^ 16r06 ]
SCCPHelper class >> msgDt2 [ <category: 'constants'> ^ 16r07 ]
SCCPHelper class >> msgAk [ <category: 'constants'> ^ 16r08 ]
SCCPHelper class >> msgUdt [ <category: 'constants'> ^ 16r09 ]
SCCPHelper class >> msgUdts [ <category: 'constants'> ^ 16r0A ]
SCCPHelper class >> msgEd [ <category: 'constants'> ^ 16r0B ]
SCCPHelper class >> msgEa [ <category: 'constants'> ^ 16r0C ]
SCCPHelper class >> msgRsr [ <category: 'constants'> ^ 16r0D ]
SCCPHelper class >> msgRsc [ <category: 'constants'> ^ 16r0E ]
SCCPHelper class >> msgErr [ <category: 'constants'> ^ 16r0F ]
SCCPHelper class >> msgIt [ <category: 'constants'> ^ 16r10 ]
SCCPHelper class >> msgXudt [ <category: 'constants'> ^ 16r11 ]
SCCPHelper class >> msgXudts[ <category: 'constants'> ^ 16r12 ]
SCCPHelper class >> msgLudt [ <category: 'constants'> ^ 16r13 ]
SCCPHelper class >> msgLudts[ <category: 'constants'> ^ 16r14 ]
SCCPHelper class >> pncData [ <category: 'constants'> ^ 16r0F ]
SCCPHelper class >> pncEoO [ <category: 'constants'> ^ 16r00 ]
SCCPHelper class >> createCR: src dest: dest data: aData [
<category: 'creation'>
^ (SCCPConnectionRequest initWith: src dest: dest data: aData)
toMessage.
]
SCCPHelper class >> createRLSD: src dest: dest cause: cause [
<category: 'creation'>
^ (SCCPConnectionReleased initWithDst: dest src: src cause: cause)
toMessage.
]
SCCPHelper class >> createDT1: dst data: data [
<category: 'creation'>
^ (SCCPConnectionData initWith: dst data: data)
toMessage.
]
]
Object subclass: SCCPPNC [
| dict |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I can parse and write the optional
data of SCCP messages.'>
SCCPPNC class >> parseFrom: aPnc [
| dict pnc |
<category: 'parsing'>
pnc := aPnc.
dict := Dictionary new.
[pnc isEmpty not] whileTrue: [
| type |
type := pnc at: 1.
type = SCCPHelper pncEoO
ifTrue: [
pnc := ByteArray new.
]
ifFalse: [
| size data |
size := pnc at: 2.
data := pnc copyFrom: 3 to: 3 + size - 1.
pnc := pnc copyFrom: 3 + size.
dict at: type put: data.
].
].
^ (self new)
dict: dict;
yourself.
]
at: aKey put: aValue [
<category: 'accessing'>
self dict at: aKey put: aValue.
]
at: aKey [
<category: 'accessing'>
^ self dict at: aKey.
]
dict [
<category: 'accessing'>
^ dict ifNil: [dict := Dictionary new.]
]
dict: aDict [
<category: 'private'>
dict := aDict.
]
writeOn: aMsg [
<category: 'encoding'>
self dict keysAndValuesDo: [:key :val |
| dat |
dat := val toMessageOrByteArray.
aMsg putByte: key.
aMsg putByte: dat size.
aMsg putByteArray: dat.
].
aMsg putByte: SCCPHelper pncEoO.
]
]
Object subclass: SCCPAddrReference [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Address Reference, e.g. the source
or destination reference address as used for SCCP connections.'>
SCCPAddrReference class >> store: anAddress on: aMsg [
"Store the threee bytes of an sccp address on a messagebuffer"
<category: 'encoding'>
aMsg putByte: ((anAddress bitAnd: 16r000000FF) bitShift: -0).
aMsg putByte: ((anAddress bitAnd: 16r0000FF00) bitShift: -8).
aMsg putByte: ((anAddress bitAnd: 16r00FF0000) bitShift: -16).
]
SCCPAddrReference class >> fromCData: anArray [
| oct1 oct2 oct3 |
"Parse from an CArray"
<category: 'encoding'>
oct1 := (anArray at: 0) bitShift: 0.
oct2 := (anArray at: 1) bitShift: 8.
oct3 := (anArray at: 2) bitShift: 16.
^ (oct1 bitOr: oct2) bitOr: oct3
]
SCCPAddrReference class >> fromByteArray: anArray [
| oct1 oct2 oct3 |
"Parse from a ByteArray"
<category: 'encoding'>
oct1 := (anArray at: 1) bitShift: 0.
oct2 := (anArray at: 2) bitShift: 8.
oct3 := (anArray at: 3) bitShift: 16.
^ (oct1 bitOr: oct2) bitOr: oct3
]
]
Object subclass: SCCPMessage [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I am the generic base class for all defined
SCCP messages. You should only deal with me to decode
data.'>
SCCPMessage class >> decode: aByteArray [
| type |
<category: 'parsing'>
type := aByteArray at: 1.
SCCPMessage allSubclassesDo: [:each |
each msgType = type
ifTrue: [
^ each parseFrom: aByteArray.
]
].
"raise exception"
^ Error signal: ('No handler for: <1p>' expandMacrosWith: type).
]
]
SCCPMessage subclass: SCCPConnectionRequest [
| src dst pnc |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection request.'>
SCCPConnectionRequest class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCr
]
SCCPConnectionRequest class >> initWith: src dest: dest pnc: pnc [
<category: 'construction'>
^ self new
src: src dest: dest pnc: pnc;
yourself
]
SCCPConnectionRequest class >> initWith: src dest: dest data: data [
<category: 'construction'>
| pnc |
pnc := SCCPPNC new.
pnc at: SCCPHelper pncData put: data.
^ self new
src: src dest: dest pnc: pnc;
yourself
]
SCCPConnectionRequest class >> parseFrom: aMsg [
| src addr proto variable optional pnc |
<category: 'parsing'>
src := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4).
proto := (aMsg at: 5) asInteger.
variable := (aMsg at: 6) asInteger.
optional := (aMsg at: 7) asInteger.
"some sanity check"
proto ~= 2 ifTrue: [
Exception signal: 'Proto should be two was ', proto asString.
].
"parse the address"
addr := SCCPAddress parseFrom: (aMsg copyFrom: (6 + variable)).
"parse the optional data"
pnc := SCCPPNC parseFrom: (aMsg copyFrom: (7 + optional)).
^ SCCPConnectionRequest initWith: src dest: addr pnc: pnc.
]
src [
<category: 'accessing'>
^ src
]
dest [
<category: 'accessing'>
^ dst
]
data [
<category: 'accessing'>
^ pnc at: SCCPHelper pncData.
]
data: aData [
<category: 'accessing'>
pnc at: SCCPHelper pncData put: aData.
]
src: aSrc dest: aDest pnc: aPnc [
<category: 'accessing'>
src := aSrc.
dst := aDest.
pnc := aPnc.
]
writeOn: aMsg [
<category: 'encoding'>
| dat len addr |
addr := dst asByteArray.
aMsg putByte: self class msgType.
SCCPAddrReference store: src on: aMsg.
"store proto_class, variable_called, optional_start"
aMsg putByte: 2.
aMsg putByte: 2.
aMsg putByte: 1 + addr size.
aMsg putByteArray: addr.
" place the data now "
pnc writeOn: aMsg.
^ aMsg.
]
]
SCCPMessage subclass: SCCPConnectionConfirm [
| src dst pnc |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection confirm.'>
SCCPConnectionConfirm class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCc
]
SCCPConnectionConfirm class >> initWithSrc: aSrc dst: aDst [
<category: 'creation'>
^ self new
src: aSrc dst: aDst;
yourself
]
SCCPConnectionConfirm class >> parseFrom: aMsg [
| src dst proto optional |
<category: 'parsing'>
dst := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4).
src := SCCPAddrReference fromByteArray: (aMsg copyFrom: 5 to: 7).
proto := aMsg at: 8.
optional := aMsg at: 9.
"TODO: Add additional items"
^ self new
src: src dst: dst;
yourself
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: SCCPHelper msgCc.
SCCPAddrReference store: dst on: aMsg.
SCCPAddrReference store: src on: aMsg.
aMsg putByte: 2.
aMsg putByte: 1.
self pnc writeOn: aMsg.
]
src: aSrc dst: aDst [
<category: 'accessing'>
src := aSrc.
dst := aDst.
]
src [
<category: 'accessing'>
^ src
]
dst [
<category: 'accessing'>
^ dst
]
pnc [
<category: 'accessing'>
^ pnc ifNil: [ pnc := SCCPPNC new. ]
]
]
SCCPMessage subclass: SCCPConnectionRefused [
| dst cause |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection refused.'>
SCCPConnectionRefused class >> msgType [
<category: 'factory'>
^SCCPHelper msgCref
]
SCCPConnectionRefused class >> initWithDst: aDst cause: aCause [
<category: 'creation'>
^self new
dst: aDst;
cause: aCause;
yourself
]
SCCPConnectionRefused class >> parseFrom: aMsg [
| dst cause |
<category: 'parsing'>
dst := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4).
cause := aMsg at: 5.
^self initWithDst: dst cause: cause.
]
dst: aDst [
dst := aDst
]
dst [
^dst
]
cause: aCause [
cause := aCause
]
cause [
^cause
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
aMsg putByte: cause.
"End of optional?"
aMsg putByte: 1; putByte: 0.
]
]
SCCPMessage subclass: SCCPConnectionData [
| dst data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a data memssage.'>
SCCPConnectionData class >> msgType [
<category: 'factory'>
^ SCCPHelper msgDt1
]
SCCPConnectionData class >> initWith: dst data: data [
<category: 'creation'>
^ (self new)
dst: dst;
data: data;
yourself.
]
SCCPConnectionData class >> parseFrom: aByteArray [
| more_data var_start addr size data |
<category: 'parsing'>
addr := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2).
more_data := aByteArray at: 5.
more_data = 0 ifFalse: [
Error signal: 'Fragmented data is not supported.'.
].
var_start := aByteArray at: 6.
size := aByteArray at: 6 + var_start.
data := aByteArray copyFrom: (6 + var_start + 1) to: (6 + var_start + size).
^ SCCPConnectionData initWith: addr data: data.
]
dst: aDst [
<category: 'private'>
dst := aDst.
]
data: aData [
<category: 'private'>
data := aData.
data size > 16rFF ifTrue: [
self error: ('Data must be < 256 in size but was <1p>' expandMacrosWith: data size)
].
]
dst [
<category: 'accessing'>
^ dst
]
data [
<category: 'accessing'>
^ data
]
writeOn: aMsg [
| dat |
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
aMsg putByte: 0.
aMsg putByte: 1.
dat := data toMessageOrByteArray.
aMsg putByte: dat size.
aMsg putByteArray: dat.
^ aMsg
]
]
SCCPMessage subclass: SCCPConnectionReleased [
| src dst cause pnc |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection release message.'>
SCCPConnectionReleased class >> msgType [
<category: 'factory'>
^ SCCPHelper msgRlsd
]
SCCPConnectionReleased class >> initWithDst: aDst src: aSrc cause: aCause [
<category: 'creation'>
^ self new
dst: aDst;
src: aSrc;
cause: aCause;
yourself.
]
SCCPConnectionReleased class >> parseFrom: aByteArray [
| dst src cause |
<category: 'parsing'>
dst := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2).
src := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5).
cause := aByteArray at: 8.
^ SCCPConnectionReleased initWithDst: dst src: src cause: cause.
]
dst [
<category: 'accessing'>
^ dst
]
src [
<category: 'accessing'>
^ src
]
cause [
<category: 'accessing'>
^ cause
]
dst: aDst [
<category: 'accessing'>
dst := aDst
]
src: aSrc [
<category: 'accessing'>
src := aSrc
]
cause: aCause [
<category: 'accessing'>
cause := aCause
]
pnc [
<category: 'accessing'>
^ pnc ifNil: [pnc := SCCPPNC new]
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
SCCPAddrReference store: src on: aMsg.
aMsg putByte: cause.
aMsg putByte: 1.
self pnc writeOn: aMsg.
]
]
SCCPMessage subclass: SCCPConnectionReleaseComplete [
| dst src |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a released connection.'>
SCCPConnectionReleaseComplete class >> msgType [
<category: 'fields'>
^ SCCPHelper msgRlc.
]
SCCPConnectionReleaseComplete class >> initWithDst: aDst src: aSrc [
<category: 'creation'>
^ self new
dst: aDst; src: aSrc;
yourself
]
SCCPConnectionReleaseComplete class >> parseFrom: aByteArray [
<category: 'parsing'>
^ self new
dst: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2 to: 4));
src: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5 to: 7));
yourself
]
dst [
<category: 'accessing'>
^ dst
]
dst: aDst [
<category: 'accessing'>
dst := aDst.
]
src [
<category: 'accessing'>
^ src
]
src: aSrc [
<category: 'accessing'>
src := aSrc.
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
SCCPAddrReference store: src on: aMsg.
]
]
SCCPMessage subclass: SCCPUDT [
| called calling data error udtClass |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection less data message.'>
SCCPUDT class >> msgType [
<category: 'fields'>
^ SCCPHelper msgUdt
]
SCCPUDT class >> initWith: aCalled calling: aCalling data: aData [
<category: 'creation'>
^ self new
calledAddr: aCalled;
callingAddr: aCalling;
data: aData;
yourself
]
SCCPUDT class >> parseFrom: aByteArray [
| called calledData calling callingData data dataData dataSize |
<category: 'parsing'>
called := aByteArray at: 3.
calledData := aByteArray copyFrom: (3 + called).
calling := aByteArray at: 4.
callingData := aByteArray copyFrom: (4 + calling).
data := aByteArray at: 5.
dataSize := aByteArray at: (5 + data).
dataData := aByteArray copyFrom: (6 + data) to: 5 + data + dataSize.
^ (SCCPUDT initWith: (SCCPAddress parseFrom: calledData)
calling: (SCCPAddress parseFrom: callingData)
data: dataData)
udtClass: ((aByteArray at: 2) bitAnd: 16r0F);
errorHandling: ((aByteArray at: 2) bitShift: -4);
yourself.
]
calledAddr: aCalled [
<category: 'accessing'>
called := aCalled
]
calledAddr [
<category: 'accessing'>
^ called
]
callingAddr: aCalling [
<category: 'accessing'>
calling := aCalling
]
callingAddr [
<category: 'accessing'>
^ calling
]
data [
<category: 'accessing'>
^ data
]
data: aData [
<category: 'accessing'>
data := aData.
]
errorHandling: aStrategy [
<category: 'accessing'>
error := aStrategy.
]
errorHandling [
<category: 'accessing'>
^ error ifNil: [0]
]
udtClass: aClass [
<category: 'accessing'>
udtClass := aClass.
]
udtClass [
<category: 'accessing'>
^ udtClass ifNil: [0]
]
writeOn: aMsg [
| calledData callingData dat |
<category: 'encoding'>
calledData := called asByteArray.
callingData := calling asByteArray.
aMsg putByte: self class msgType.
aMsg putByte: (((self errorHandling bitAnd: 16r0F) bitShift: 4) bitOr: self udtClass).
"pointers"
aMsg putByte: 3.
aMsg putByte: 1 + calledData size + 1.
aMsg putByte: calledData size + callingData size + 1.
"the data"
aMsg putByteArray: calledData.
aMsg putByteArray: callingData.
dat := data toMessageOrByteArray.
aMsg putByte: dat size.
aMsg putByteArray: dat.
]
]
SCCPMessage subclass: SCCPInactivityTest [
| src dst proto seq credit |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of an inactivity test.'>
SCCPInactivityTest class >> msgType [
<category: 'field'>
^ SCCPHelper msgIt
]
SCCPInactivityTest class >> initWithDst: aDst src: aSrc [
<category: 'creation'>
^ self new
dst: aDst;
src: aSrc;
yourself.
]
SCCPInactivityTest class >> parseFrom: aByteArray [
| dst src proto seq credit |
<category: 'parsing'>
dst := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2).
src := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5).
^ (self initWithDst: dst src: src)
instVarNamed: #proto put: (aByteArray at: 8);
instVarNamed: #seq put: (aByteArray copyFrom: 9 to: 10);
instVarNamed: #credit put: (aByteArray at: 11);
yourself
]
src: aSrc [
<category: 'stuff'>
src := aSrc.
]
src [
<category: 'stuff'>
^ src
]
dst: aDst [
<category: 'stuff'>
dst := aDst
]
dst [
<category: 'stuff'>
^ dst
]
credit [
<category: 'stuff'>
^ credit ifNil: [0]
]
credit: aCredit [
<category: 'stuff'>
credit := aCredit
]
protoClass [
<category: 'stuff'>
^ proto ifNil: [0]
]
protoClass: aClass [
<category: 'stuff'>
proto := aClass.
]
seq [
<category: 'stuff'>
^ seq ifNil: [ByteArray new: 2]
]
seq: aSeq [
<category: 'stuff'>
seq := aSeq.
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
SCCPAddrReference store: src on: aMsg.
aMsg putByte: self protoClass.
aMsg putByteArray: self seq.
aMsg putByte: self credit.
]
]