1
0
Fork 0

sccp: Kill the encoding and encode the extra 4 bits as 16r0 and not 16rF

This commit is contained in:
Holger Hans Peter Freyther 2013-10-14 15:04:43 +02:00
parent 92add56e05
commit c729a99672
3 changed files with 23 additions and 16 deletions

View File

@ -213,6 +213,24 @@ TestCase subclass: SCCPTests [
self assert: parsed asByteArray = addr. self assert: parsed asByteArray = addr.
] ]
testAddrGTIOdd [
| addr parsed gti |
addr := #(16r0B 16r12 16r08 16r00 16r11 16r04 16r64 16r07 16r97 16r36 16r71 16r03) asByteArray.
parsed := SCCPAddress parseFrom: addr.
self assert: parsed ssn = SCCPAddress ssnMSC.
self assert: parsed asByteArray = addr.
"GTI encoding.."
gti := parsed gtiAsParsed.
self assert: gti translation = 0.
self assert: gti plan = SCCPGlobalTitle npISDN.
self assert: gti nature = SCCPGlobalTitle naiInternationalNumber.
self assert: gti addr = '46707963173'.
parsed gtiFromAddr: gti.
self assert: parsed asByteArray = addr.
]
] ]
TestCase subclass: MessageBufferTest [ TestCase subclass: MessageBufferTest [

View File

@ -109,7 +109,7 @@ Object subclass: SCCPGlobalTitle [
]. ].
odd ifTrue: [ odd ifTrue: [
nr add: 16rF. nr add: 16r0.
]. ].
1 to: nr size by: 2 do: [:each| 1 to: nr size by: 2 do: [:each|

View File

@ -17,7 +17,7 @@
" "
SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [ SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan enc nature addr | | trans plan nature addr |
<category: 'OsmoNetwork-SCCP'> <category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the global title translation specific <comment: 'I represent the global title translation specific
@ -32,7 +32,6 @@ SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
^ self new ^ self new
translation: (data at: 1); translation: (data at: 1);
plan: (((data at: 2) bitAnd: 16rF0) bitShift: -4); plan: (((data at: 2) bitAnd: 16rF0) bitShift: -4);
encoding: enc;
nature: ((data at: 3) bitAnd: 16r7F); nature: ((data at: 3) bitAnd: 16r7F);
addr: (self parseAddr: (data copyFrom: 4) encoding: enc); addr: (self parseAddr: (data copyFrom: 4) encoding: enc);
yourself yourself
@ -60,19 +59,9 @@ SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
encoding [ encoding [
<category: 'accessing'> <category: 'accessing'>
^ enc ifNil: [ ^addr size odd
addr size odd ifTrue: [1]
ifTrue: [ ifFalse: [2]
1
]
ifFalse: [
2
].
].
]
encoding: aEnc [
<category: 'accessing'>
enc := aEnc
] ]
nature [ nature [