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

gsm48: Allow to store TMSI/IMEI/IMEISV as MI IE as well

The encoding is the same for IMSI, IMEI and IMEISV. The coding for
the TMSI is left 'open'. When decoding/recoding the right thing should
happen. For setting a plain TMSI some more work is required.
This commit is contained in:
Holger Hans Peter Freyther 2012-09-09 17:03:47 +02:00
parent 1f9262eef0
commit 048b1c0109
1 changed files with 88 additions and 44 deletions

132
GSM48.st
View File

@ -518,18 +518,14 @@ GSM48DataHolder subclass: GSM48Classmark2 [
]
GSM48VariableSizedIE subclass: GSM48MIdentity [
| imsi tmsi |
| type id |
<category: 'OsmoGSM'>
<comment: 'I am MobileIdentity of 10.5.1.4'>
<gsmElementId: 23>
<gsmName: 'mi'>
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)
@ -538,72 +534,104 @@ GSM48VariableSizedIE subclass: GSM48MIdentity [
]
GSM48MIdentity class >> parseFrom: aStream [
| len head type |
| len head type odd digits |
len := aStream next.
head := aStream next.
type := head bitAnd: 16r7.
type = self miIMSI
ifTrue: [
| odd digits |
digits := OrderedCollection new.
odd := (head bitShift: -3) bitAnd: 16r1.
digits := OrderedCollection new.
odd := (head bitShift: -3) bitAnd: 16r1.
digits add: ((head bitShift: -4) bitAnd: 16rF).
digits add: ((head bitShift: -4) bitAnd: 16rF).
3 to: (1 + len) do: [:each | | val |
val := aStream next.
digits add: (val bitAnd: 16rF).
digits add: ((val bitShift: -4) bitAnd: 16rF).
].
"The last was just a dummy value"
odd = 1 ifFalse: [
digits removeLast.
].
^ (self new) imsi: (BCD decode: digits) asString; yourself
3 to: (1 + len) do: [:each | | val |
val := aStream next.
digits add: (val bitAnd: 16rF).
digits add: ((val bitShift: -4) bitAnd: 16rF).
].
self notYetImplemented.
"The last was just a dummy value"
odd = 1 ifFalse: [
digits removeLast.
].
^ self new
type: type;
id: (BCD decode: digits) asString;
yourself
]
imsi: aImsi [ <category: 'creation'> imsi := aImsi. ]
imsi [ ^ imsi ]
imsi: anImsi [
<category: 'creation'>
type := GSM48IdentityType typeIMSI.
self id: anImsi.
]
imsi [
<category: 'access'>
self type = GSM48IdentityType typeIMSI
ifFalse: [^self error: 'Underlying type is not an IMSI'].
^ id
]
imei: anImei [
<category: 'creation'>
type := GSM48IdentityType typeIMEI.
self id: anImei.
]
imei [
<category: 'query'>
self type = GSM48IdentityType typeIMEI
ifFalse: [^self error: 'Underlying type is not an IMEI'].
^ id
]
id: anId [
<category: 'creation'>
id := anId
]
type: aType [
<category: 'creation'>
type := aType
]
type [
<category: 'access'>
^ type bitAnd: 2r111
]
writeOnDirect: aMsg [
<category: 'creation'>
imsi ifNotNil: [
^ self storeImsiDirect: aMsg.
].
self notYetImplemented
self storeIdentityOn: aMsg.
]
storeImsiDirect: aMsg [
storeIdentityOn: aMsg [
| odd len head encoded bcds |
<category: 'private'>
odd := imsi size odd.
odd := id 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 ].
ifTrue: [ (id size + 1) / 2 ]
ifFalse: [ (id size / 2) + 1 ].
aMsg putByte: len.
"Create the first data"
head := ((imsi at: 1) digitValue) bitShift: 4.
head := ((id at: 1) digitValue) bitShift: 4.
odd ifTrue: [
head := head bitOr: (1 bitShift: 3).
].
head := head bitOr: self class miIMSI.
head := head bitOr: self type.
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.
2 to: id size do: [:pos |
bcds add: (id at: pos) digitValue.
].
odd ifFalse: [
@ -707,15 +735,31 @@ GSM48SimpleData subclass: GSM48IdentityType [
<gsmName: 'idType'>
<gsmValueLength: 1>
GSM48IdentityType class >> typeIMSI [ ^ 1 ]
GSM48IdentityType class >> typeIMEI [ ^ 2 ]
GSM48IdentityType class >> typeIMEISV [ ^ 3 ]
GSM48IdentityType class >> typeTMSI [ ^ 4 ]
GSM48IdentityType class >> typeIMSI [ <category: 'types'> ^ 2r001 ]
GSM48IdentityType class >> typeIMEI [ <category: 'types'> ^ 2r010 ]
GSM48IdentityType class >> typeIMEISV [ <category: 'types'> ^ 2r011 ]
GSM48IdentityType class >> typeTMSI [ <category: 'types'> ^ 2r100 ]
GSM48IdentityType class >> typeNone [ <category: 'types'> ^ 2r000 ]
GSM48IdentityType class >> defaultValue [
^ ByteArray with: self typeIMSI
]
isIMSI [
<category: 'query'>
^ self data first = self class typeIMSI
]
isIMEI [
<category: 'query'>
^ self data first = self class typeIMEI
]
isIMEISV [
<category: 'query'>
^ self data first = self class typeIMEISV
]
type: aType [
self data: (ByteArray with: aType)
]