smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-gsm/GSM48.st

253 lines
6.0 KiB
Smalltalk
Raw Normal View History

"Messages for GSM04.08"
"""
IEs for GSM48MSG
"""
Object subclass: GSM48KeySeqLuType [
<category: 'osmo-message'>
| val |
GSM48KeySeqLuType class >> createDefault [
<category: 'creation'>
^ (self new)
val: 16r70;
yourself
]
2010-11-23 22:37:27 +00:00
GSM48KeySeqLuType class >> length: aByteArray [
"We always need a byte"
^ 1
]
GSM48KeySeqLuType class >> parseFrom: aByteArray [
^ self new
val: (aByteArray at: 1);
yourself
]
val [
^ val
]
val: aVal [
<category: 'creation'>
val := aVal.
]
writeOnDirect: aMsg [
<category: 'creation'>
aMsg putByte: val.
]
]
Object subclass: GSM48Lai [
| lai lac |
<category: 'osmo-message'>
GSM48Lai class >> createDefault [
<category: 'creation'>
^ (self new)
lai: (LAI initWith: 0 mnc: 0);
lac: 0;
yourself
]
GSM48Lai class >> length: aByteArray [
^ 5
]
GSM48Lai class >> parseFrom: aByteArray [
^ (self new)
lai: (LAI parseFrom: (aByteArray copyFrom: 1 to: 3));
lac: (aByteArray ushortAt: 4) swap16;
yourself
]
mcc: aMcc [ <category: 'creation'> lai mcc: aMcc ]
mnc: aMnc [ <category: 'creation'> lai mnc: aMnc ]
lai: aLai [ <category: 'creation'> lai := aLai ]
lac: aLac [ <category: 'creation'> lac := aLac ]
mcc [ ^ lai mcc ]
mnc [ ^ lai mnc ]
lac [ ^ lac ]
writeOnDirect: aMsg [
<category: 'creation'>
lai writeOn: aMsg.
2010-11-17 21:43:43 +00:00
aMsg putLen16: lac.
]
]
Object subclass: GSM48Classmark1 [
<category: 'osmo-message'>
| cm1 |
GSM48Classmark1 class >> createDefault [
<category: 'creation'>
^ (self new)
cm1: 16r33;
yourself
]
GSM48Classmark1 class >> length: aByteArray [
^ 1
]
GSM48Classmark1 class >> parseFrom: aByteArray [
^ (self new)
cm1: (aByteArray at: 1);
yourself
]
cm1: aCm [ <category: 'creation'> cm1 := aCm ]
cm1 [ ^ cm1 ]
writeOnDirect: aMsg [
<category: 'creation'>
aMsg putByte: cm1.
]
]
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)
imsi: '000000000000';
yourself
]
imsi: aImsi [ <category: 'creation'> imsi := aImsi. ]
writeOnDirect: aMsg [
<category: 'creation'>
imsi ifNotNil: [
^ self storeImsiDirect: aMsg.
].
self notYetImplemented
]
storeImsiDirect: aMsg [
| odd len head encoded bcds |
2010-11-19 18:10:38 +00:00
<category: 'private'>
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.
]
]
IEMessage subclass: GSM48MSG [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
<comment: 'GSM48 has helper code for mandantory types'>
GSM48MSG class >> addMandantory: aName with: aClass [
<comment: 'creation'>
self addInstVarName: aName asSymbol.
self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}.
self Mandantory add: aName asSymbol.
]
writeOn: aMsg [
"Write the header. Skip Ind, Sequence are hardcoded"
aMsg putByte: self class classType.
aMsg putByte: self class messageType.
"Write all Mandantory parts"
self class Mandantory do: [:each | | tmp |
tmp := self perform: each.
tmp writeOnDirect: aMsg.
].
"TODO: Handle the Conditionals too"
]
]
GSM48MSG subclass: GSM48MMMessage [
<category: 'osmo-message'>
<comment: 'Baseclass for mobility managamenet'>
GSM48MMMessage class >> classType [ ^ 5 ]
GSM48MMMessage class >> msgLU [ ^ 8 ]
]
GSM48MMMessage subclass: LocationUpdatingRequest [
<category: 'osmo-message'>
Mandantory := nil.
LocationUpdatingRequest class >> messageType [ ^ self msgLU ]
LocationUpdatingRequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
LocationUpdatingRequest class >> initialize [
self addMandantory: 'luType' with: GSM48KeySeqLuType.
self addMandantory: 'lai' with: GSM48Lai.
self addMandantory: 'cm1' with: GSM48Classmark1.
self addMandantory: 'mi' with: GSM48MIdentity.
]
]
Object subclass: LocationUpdatingAccept [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
]
Object subclass: LocationUpdatingReject [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
]
Object subclass: IdentityRequest [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
]
Object subclass: IdentityResponse [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
]
Eval [
LocationUpdatingRequest initialize.
]