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

GSM48: Implement generating the Mobile Identity

Fix the unit tests...
This commit is contained in:
Holger Hans Peter Freyther 2010-11-19 20:26:59 +01:00
parent fdd716a58b
commit aed157b033
2 changed files with 56 additions and 9 deletions

View File

@ -69,6 +69,12 @@ Object subclass: GSM48Classmark1 [
Object subclass: GSM48MIdentity [
<category: 'osmo-message'>
| imsi tmsi |
GSM48MIdentity class >> miIMSI [ <category: 'spec'> ^ 16r1 ]
GSM48MIdentity class >> miIMEI [ <category: 'spec'> ^ 16r2 ]
GSM48MIdentity class >> miIMEISV [ <category: 'spec'> ^ 16r3 ]
GSM48MIdentity class >> miTMSI [ <category: 'sepc'> ^ 16r4 ]
GSM48MIdentity class >> createDefault [
<category: 'creation'>
^ (self new)
@ -86,8 +92,47 @@ Object subclass: GSM48MIdentity [
]
storeImsiDirect: aMsg [
| odd len head encoded bcds |
<category: 'private'>
self notYetImplemented.
odd := imsi size odd.
"Calculate the length. We can fit two digits into one byte"
len := odd
ifTrue: [ (imsi size + 1) / 2 ]
ifFalse: [ (imsi size / 2) + 1 ].
aMsg putByte: len.
"Create the first data"
head := ((imsi at: 1) digitValue) bitShift: 4.
odd ifTrue: [
head := head bitOr: (1 bitShift: 3).
].
head := head bitOr: self class miIMSI.
aMsg putByte: head.
"Encode everything from 2..n into a ByteArray of len - 1"
bcds := OrderedCollection new.
2 to: imsi size do: [:pos |
bcds add: (imsi at: pos) digitValue.
].
odd ifFalse: [
bcds add: 16r0F.
].
"now fold the bcds into and encoded array"
encoded := OrderedCollection new.
1 to: bcds size by: 2 do: [:pos |
| lower upper |
lower := bcds at: pos.
upper := bcds at: pos + 1.
encoded add: ((upper bitShift: 4) bitOr: lower).
].
aMsg putByteArray: encoded asByteArray.
]
]
@ -109,7 +154,7 @@ IEMessage subclass: GSM48MSG [
aMsg putByte: self class messageType.
"Write all Mandantory parts"
self Mandantory do: [:each | | tmp |
self class Mandantory do: [:each | | tmp |
tmp := self perform: each.
tmp storeOnDirect: aMsg.
].

View File

@ -99,19 +99,21 @@ TestCase subclass: GSM48Test [
| gsm msg |
msg := Osmo.MessageBuffer new.
gsm := GSM48MIdentity createDefault.
gsm imsi: '181818181818181'.
gsm imsi: '274080000004780'.
gsm storeOnDirect: msg.
self assert: msg toByteArray = #() asByteArray
self assert: msg toByteArray = #(8 41 71 128 0 0 0 116 8) asByteArray.
]
testLU [
| msg |
| gsm msg |
msg := LocationUpdatingRequest new.
(msg lai) mcc: 272 mnc: 5 lac: 65534.
(msg mi) imsi: '181818181818181'.
msg := Osmo.MessageBuffer new.
gsm := LocationUpdatingRequest new.
(gsm lai) mcc: 202; mnc: 5; lac: 65534.
(gsm mi) imsi: '666105400273888'.
gsm storeOn: msg.
self assert: msg toByteArray = #() asByteArray.
self assert: msg toByteArray = #(5 8 112 2 242 80 255 254 51 8 105 102 1 69 0 114 131 136) asByteArray.
]
]