1
0
Fork 0

sccp: Rename poi to pointCode and update selectors

This commit is contained in:
Holger Hans Peter Freyther 2013-04-30 14:26:26 +02:00
parent c6f896f645
commit e46ebff237
2 changed files with 54 additions and 36 deletions

View File

@ -134,24 +134,22 @@ TestCase subclass: SCCPTests [
]
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.
| 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 pointCode: 7.
calling := SCCPAddress createWith: 254 pointCode: 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 pointCode = 7.
self assert: udt callingAddr ssn = 254.
self assert: udt callingAddr pointCode = 92.
self assert: udt toMessage asByteArray = target
]
testUDTClass [

View File

@ -17,7 +17,7 @@
"
Object subclass: SCCPAddress [
| subSystemNumber globalTitle routedOnSsn poi gti_ind |
| subSystemNumber globalTitle routedOnSsn pointCode gti_ind |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the SCCP Address including the
@ -47,19 +47,25 @@ Object subclass: SCCPAddress [
yourself
]
SCCPAddress class >> createWith: ssn poi: aPoi [
SCCPAddress class >> createWith: ssn poi: aPointCode [
<category: 'creation'>
^ SCCPAddress new
self deprecated: 'Use >>#createWith:pointCode: instead'.
^self createWith: ssn pointCode: aPointCode
]
SCCPAddress class >> createWith: ssn pointCode: aPointCode [
<category: 'creation'>
^(self new)
ssn: ssn;
routedOnSSN: true;
poi: aPoi;
pointCode: aPointCode;
yourself
]
SCCPAddress class >> parseFrom: aByteArray [
| routed_ssn gti_ind gti len ai ssn poi dat |
| routed_ssn gti_ind gti len ai ssn pointCode dat |
<category: 'parsing'>
poi := nil.
pointCode := nil.
len := aByteArray at: 1.
ai := aByteArray at: 2.
@ -69,7 +75,7 @@ Object subclass: SCCPAddress [
"Point Code"
(ai bitAnd: 1) = 1
ifTrue: [
poi := (dat ushortAt: 1).
pointCode := (dat ushortAt: 1).
dat := dat copyFrom: 3.
].
@ -82,10 +88,9 @@ Object subclass: SCCPAddress [
gti_ind := (ai bitAnd: 16r3C) bitShift: -2.
gti := dat copyFrom: 1.
^ SCCPAddress new
^ self new
ssn: ssn;
poi: poi;
pointCode: pointCode;
routedOnSSN: routed_ssn;
gti: gti indicator: gti_ind;
yourself.
@ -140,14 +145,29 @@ Object subclass: SCCPAddress [
globalTitle := aGlobalTitle asByteArray.
]
poi: aPoi [
<category: 'point-code-indicator'>
poi := aPoi.
poi: aPointCode [
<category: 'deprecated'>
self deprecated: 'Use >>#pointCode: instead'.
self pointCode: aPointCode
]
poi [
<category: 'deprecated'>
self deprecated: 'Use >>#pointCode instead'.
^self pointCode
]
pointCode [
<category: 'point-code-indicator'>
^ poi
^pointCode
]
pointCode: aPointCode [
"When a non-nil point code is set the pointcode indicator will be set in the
address information."
<category: 'point-code-indicator'>
pointCode := aPointCode
]
ssn: aSubSystemNumber [
@ -187,7 +207,7 @@ Object subclass: SCCPAddress [
].
"Point Code"
poi ifNotNil: [
pointCode ifNotNil: [
ai := ai bitOr: 1.
].
@ -199,9 +219,9 @@ Object subclass: SCCPAddress [
data add: ai.
"POC"
poi ifNotNil: [
data add: ((poi bitAnd: 16r00FF) bitShift: 0).
data add: ((poi bitAnd: 16rFF00) bitShift: -8).
pointCode ifNotNil: [
data add: ((pointCode bitAnd: 16r00FF) bitShift: 0).
data add: ((pointCode bitAnd: 16rFF00) bitShift: -8)
].
"SSN"