smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0

gsm: Fix and test the TMSI parsing and storing

Go for the easiest option and special case the TMSI handling.
This commit is contained in:
Holger Hans Peter Freyther 2012-11-24 13:45:04 +01:00
parent 8f1ee67556
commit be139c87ef
2 changed files with 57 additions and 10 deletions

View File

@ -543,18 +543,37 @@ GSM48VariableSizedIE subclass: GSM48MIdentity [
]
GSM48MIdentity class >> parseFrom: aStream [
| len head type odd digits |
| len head type id |
len := aStream next.
head := aStream next.
type := head bitAnd: 16r7.
id := type = GSM48IdentityType typeTMSI
ifTrue: [self parseTMSI: aStream length: len head: head]
ifFalse: [self parseBCDId: aStream length: len head: head].
^ self new
type: type;
id: id;
yourself
]
GSM48MIdentity class >> parseTMSI: aStream length: aLength head: aHead [
aLength = 5
ifFalse: [^self error: 'MI should be five bytes'].
^ aStream next: 4.
]
GSM48MIdentity class >> parseBCDId: aStream length: aLength head: aHead [
| digits odd |
digits := OrderedCollection new.
odd := (head bitShift: -3) bitAnd: 16r1.
odd := (aHead bitShift: -3) bitAnd: 16r1.
digits add: ((head bitShift: -4) bitAnd: 16rF).
digits add: ((aHead bitShift: -4) bitAnd: 16rF).
3 to: (1 + len) do: [:each | | val |
3 to: (1 + aLength) do: [:each | | val |
val := aStream next.
digits add: (val bitAnd: 16rF).
digits add: ((val bitShift: -4) bitAnd: 16rF).
@ -565,10 +584,7 @@ GSM48VariableSizedIE subclass: GSM48MIdentity [
digits removeLast.
].
^ self new
type: type;
id: (BCD decode: digits) asString;
yourself
^ (BCD decode: digits) asString.
]
imsi: anImsi [
@ -597,6 +613,15 @@ GSM48VariableSizedIE subclass: GSM48MIdentity [
^ id
]
tmsi: aTmsi [
<category: 'query'>
aTmsi size = 4
ifFalse: [^self error: 'TMSI must be four bytes'].
type := GSM48IdentityType typeTMSI.
self id: aTmsi.
]
tmsi [
<category: 'query'>
self type = GSM48IdentityType typeTMSI
@ -621,10 +646,19 @@ GSM48VariableSizedIE subclass: GSM48MIdentity [
writeOnDirect: aMsg [
<category: 'creation'>
self storeIdentityOn: aMsg.
type = GSM48IdentityType typeTMSI
ifTrue: [self storeTMSIOn: aMsg]
ifFalse: [self storeBCDIdentityOn: aMsg].
]
storeIdentityOn: aMsg [
storeTMSIOn: aMsg [
aMsg
putByte: 5;
putByte: (type bitOr: 16rF0);
putByteArray: id.
]
storeBCDIdentityOn: aMsg [
| odd len head encoded bcds |
<category: 'private'>

View File

@ -237,6 +237,19 @@ TestCase subclass: GSM48Test [
self assert: gsm imsi = imsi.
]
testMITMSI [
| data res |
data := #(23 16r05 16rF4 16r1E 16r35 16rC7 16r24) asByteArray.
res := GSM48MIdentity parseFrom: (data readStream skip: 1).
self assert: res toMessage asByteArray = data.
]
testMITMSIGen [
| res |
res := (GSM48MIdentity new tmsi: #(1 2 3 4); toMessage) asByteArray.
self assert: res = #(16r17 16r05 16rF4 1 2 3 4) asByteArray.
]
testRejectCause [
| rej msg target |
target := #(11) asByteArray.