1
0
Fork 0

SCCP: Implement the SCCP UDT message, add POI handling to the addr.

This commit is contained in:
Holger Hans Peter Freyther 2010-11-27 16:43:38 +01:00
parent 5268577afb
commit b09a906af1
2 changed files with 154 additions and 6 deletions

139
SCCP.st
View File

@ -104,7 +104,7 @@ Object subclass: SCCPPNC [
]
Object subclass: SCCPAddress [
| ssn |
| ssn poi |
SCCPAddress class >> createWith: ssn [
^ (SCCPAddress new)
@ -112,17 +112,48 @@ Object subclass: SCCPAddress [
yourself
]
SCCPAddress class >> createWith: ssn poi: aPoi [
^ SCCPAddress new
ssn: ssn;
poi: aPoi;
yourself
]
SCCPAddress class >> parseFrom: aByteArray [
| len ai ssn |
| len ai ssn poi dat |
poi := nil.
len := aByteArray at: 1.
ai := aByteArray at: 2.
ai ~= 66 ifTrue: [
Error sifnal: 'Address can not be parsed: ', ai asString
(ai bitAnd: 16r40) = 16r40
ifFalse: [
Error signal: 'Address must be routed on SSN'.
].
ssn := aByteArray at: 3.
^ SCCPAddress createWith: ssn.
(ai bitAnd: 16r3C) = 0
ifFalse: [
Error signal: 'GlobalTitle indicator must be zero'.
].
dat := aByteArray copyFrom: 3.
(ai bitAnd: 1) = 1
ifTrue: [
poi := dat at: 1.
poi := poi bitOr: ((dat at: 2) bitShift: 8).
dat := dat copyFrom: 3.
].
ssn := dat at: 1.
^ SCCPAddress createWith: ssn poi: poi.
]
poi: aPoi [
poi := aPoi.
]
poi [
^ poi
]
ssn: assn [
@ -139,10 +170,24 @@ Object subclass: SCCPAddress [
| ai data |
data := OrderedCollection new.
"Create the Address Information"
ai := 0.
ai := ai bitOr: 2.
ai := ai bitOr: 64.
poi ifNotNil: [
ai := ai bitOr: 1.
].
data add: ai.
"Now write the data in the right order"
poi ifNotNil: [
data add: ((poi bitAnd: 16r00FF) bitShift: 0).
data add: ((poi bitAnd: 16rFF00) bitShift: -8).
].
data add: ssn.
data addFirst: data size.
@ -501,3 +546,85 @@ SCCPMessage subclass: SCCPConnectionReleased [
self pnc writeOn: aMsg.
]
]
SCCPMessage subclass: SCCPUDT [
| called calling data |
SCCPUDT class >> msgType [
^ SCCPHelper msgUdt
]
SCCPUDT class >> initWith: aCalled calling: aCalling data: aData [
^ self new
calledAddr: aCalled;
callingAddr: aCalling;
data: aData;
yourself
]
SCCPUDT class >> parseFrom: aByteArray [
| called calledData calling callingData data dataData dataSize |
(aByteArray at: 2) = 0
ifFalse: [
Error signal: 'Can only handle simple UDT messages.'.
].
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.
]
calledAddr: aCalled [
called := aCalled
]
calledAddr [
^ called
]
callingAddr: aCalling [
calling := aCalling
]
callingAddr [
^ calling
]
data [
^ data
]
data: aData [
data := aData.
]
writeOn: aMsg [
| calledData callingData |
calledData := called asByteArray.
callingData := calling asByteArray.
aMsg putByte: self class msgType.
aMsg putByte: 0.
"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.
aMsg putByte: data size.
aMsg putByteArray: data.
]
]

View File

@ -94,6 +94,27 @@ TestCase subclass: SCCPTests [
self assert: rlsd toMessage asByteArray = target.
]
testUdt [
| target udt called calling |
target := #(9 0 3 7 11 4 67 7 0 254 4 67 92 0 254 3 1 2 3) asByteArray.
called := SCCPAddress createWith: 254 poi: 7.
calling := SCCPAddress createWith: 254 poi: 92.
udt := SCCPUDT
initWith: called
calling: calling
data: #(1 2 3) asByteArray.
self assert: udt toMessage asByteArray = target.
udt := SCCPMessage decode: target.
self assert: (udt isKindOf: SCCPUDT).
self assert: udt calledAddr ssn = 254.
self assert: udt calledAddr poi = 7.
self assert: udt callingAddr ssn = 254.
self assert: udt callingAddr poi = 92.
self assert: udt toMessage asByteArray = target.
]
testAddrFromByteArray [
| byte |
byte := #(191 0 3) asByteArray.