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

671 lines
17 KiB
Smalltalk
Raw Normal View History

"Messages for GSM04.08"
"""
IEs for GSM48MSG
"""
IEBase subclass: GSM48IE [
<comment: 'I am a Information Element for GSM48'>
]
GSM48IE subclass: GSM48SimpleData [
| data |
<category: 'osmo-meesage'>
<comment: 'I am the base for some simple data encapsulated'>
GSM48SimpleData class >> initWithData: aData [
^ self new
data: aData;
yourself.
]
GSM48SimpleData class >> length: aByteArray [
^ self length
]
GSM48SimpleData class >> defaultValue [
^ ByteArray new: self length
]
GSM48SimpleData class >> createDefault [
^ self new
data: self defaultValue;
yourself
]
GSM48SimpleData class >> parseFrom: aByteArray [
| dat |
self length = 0
ifTrue: [
dat := ByteArray new.
]
ifFalse: [
dat := aByteArray copyFrom: 1 to: self length.
].
^ self new
data: dat;
yourself
]
data [
^ data
]
data: aData [
aData size = self class length
ifFalse: [
Error signal: 'DATA needs to be ', self class length asString, ' long.',
'But it was ', aData size asString, ' long.'.
].
data := aData.
]
writeOnDirect: aMsg [
aMsg putByteArray: data.
]
writeOn: aMsg [
"Write a TV"
aMsg putByte: self class elementId.
self writeOnDirect: aMsg
]
]
GSM48SimpleData subclass: GSM48KeySeqLuType [
<category: 'osmo-message'>
<comment: 'This byte is shared for two things'>
| val |
GSM48KeySeqLuType class >> createDefault [
<category: 'creation'>
^ (self new)
val: 16r70;
yourself
]
GSM48KeySeqLuType class >> length [
2010-11-23 22:37:27 +00:00
"We always need a byte"
^ 1
]
val [
^ self data at: 1
2010-11-23 22:37:27 +00:00
]
val: aVal [
<category: 'creation'>
self data: (ByteArray with: aVal).
]
]
GSM48IE 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.
]
]
GSM48IE 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.
]
]
GSM48SimpleData subclass: GSM48Classmark2 [
<comment: 'I am CM2 of 10.5.1.6'>
GSM48Classmark2 class >> defaultValue [
^ ByteArray with: 16r33 with: 16r19 with: 16rA2.
]
GSM48Classmark2 class >> length [
^ 4
]
]
GSM48IE 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 >> elementId [ ^ 23 ]
GSM48MIdentity class >> createDefault [
<category: 'creation'>
^ (self new)
imsi: '000000000000';
yourself
]
GSM48MIdentity class >> length: aByteArray [
^ (aByteArray at: 1) + 1
]
GSM48MIdentity class >> parseFrom: aByteArray [
| len head type |
len := aByteArray at: 1.
head := aByteArray at: 2.
type := head bitAnd: 16r7.
type = self miIMSI
ifTrue: [
| odd digits |
digits := OrderedCollection new.
odd := (head bitShift: -3) bitAnd: 16r1.
digits add: ((head bitShift: -4) bitAnd: 16rF).
3 to: (1 + len) do: [:each |
digits add: ((aByteArray at: each) bitAnd: 16rF).
digits add: (((aByteArray at: each) bitShift: -4) bitAnd: 16rF).
].
"The last was just a dummy value"
odd = 1 ifFalse: [
digits removeLast.
].
^ (self new) imsi: (BCD decode: digits) asString; yourself
].
self notYetImplemented.
]
imsi: aImsi [ <category: 'creation'> imsi := aImsi. ]
imsi [ ^ imsi ]
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.
]
]
GSM48SimpleData subclass: GSM48RejectCause [
GSM48RejectCause class >> createDefault [
<category: 'creation'>
^ self new
cause: 11;
yourself.
]
GSM48RejectCause class >> length [
^ 1
]
cause [
^ self data at: 1
]
cause: aCause [
self data: (ByteArray with: aCause).
]
]
GSM48SimpleData subclass: GSM48AuthRand [
<category: 'osmo-meesage'>
<comment: 'I represent the 10.5.3.1 Authentication parameter RAND'>
GSM48AuthRand class >> length [ ^ 16 ]
]
GSM48SimpleData subclass: GSM48AuthSRES [
<category: 'osmo-message'>
<comment: 'I represent the 10.5.3.2 Auth. parameter SRES'>
GSM48AuthSRES class >> length [ ^ 4 ]
]
GSM48SimpleData subclass: GSM48FollowOn [
<category: 'osmo-message'>
<comment: 'I represent the 10.5.3.7. A simple tag value'>
GSM48FollowOn class >> length [ ^ 0 ]
GSM48FollowOn class >> elementId [ ^ 16rA1 ]
]
GSM48SimpleData subclass: GSM48CTSPermission [
<category: 'osmo-message'>
<comment: 'I represent the 10.5.3.7. A simple tag value'>
GSM48CTSPermission class >> length [ ^ 0 ]
GSM48CTSPermission class >> elementId [ ^ 16rA2 ]
]
GSM48SimpleData subclass: GSM48IdentityType [
<category: 'osmo-message'>
<comment: 'I represent the 10.5.3.4. Identity Type'>
"Ignore the spare values"
GSM48IdentityType class >> typeIMSI [ ^ 1 ]
GSM48IdentityType class >> typeIMEI [ ^ 2 ]
GSM48IdentityType class >> typeIMEISV [ ^ 3 ]
GSM48IdentityType class >> typeTMSI [ ^ 4 ]
GSM48IdentityType class >> defaultValue [
^ ByteArray with: self typeIMSI
]
GSM48IdentityType class >> length [ ^ 1 ]
]
IEMessage subclass: GSM48MSG [
| seq |
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 instVarNames includes: aName asSymbol)
ifFalse: [
self addInstVarName: aName asSymbol.
].
self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}.
self Mandantory add: (aName asSymbol -> aClass).
]
GSM48MSG class >> addOptional: aName with: aClass [
<comment: 'creation'>
self addInstVarName: aName asSymbol.
self compile: '%1 [ ^ %1 ]' % {aName}.
self Optional add: (aName asSymbol -> aClass).
]
GSM48MSG class >> isCompatible: classType msgType: messageType [
self = GSM48MMMessage
ifTrue: [^ false].
^ (self classType = classType) and: [self messageType = messageType].
]
GSM48MSG class >> decode: aByteArray [
| classType messageType |
classType := aByteArray at: 1.
2010-11-26 22:11:58 +00:00
messageType := (aByteArray at: 2) bitAnd: 16r3F.
GSM48MSG allSubclassesDo: [:each |
(each isCompatible: classType msgType: messageType)
ifTrue: [
^ each parseFrom: aByteArray.
].
].
Exception signal: 'No one handles: ', classType asString,
' and: ', (aByteArray at: 2) asString.
]
GSM48MSG class >> parseFrom: aByteArray [
| res dat |
res := self new.
res seq: ((aByteArray at: 2) bitShift: -6).
dat := aByteArray copyFrom: 3.
self Mandantory do: [:each |
| len |
len := each value length: dat.
res instVarNamed: each key put: (each value parseFrom: dat).
"Move the parser forward"
dat := dat copyFrom: len + 1.
].
"We are done here if this class has no optional IEs"
(self respondsTo: #Optional)
ifFalse: [
^ res
].
"Types must appear in order"
self Optional do: [:each |
| tag |
tag := dat at: 1.
tag = each value elementId
ifTrue: [
| len data |
data := dat copyFrom: 2.
len := each value length: data.
res instVarNamed: each key put: (each value parseFrom: data).
dat := dat copyFrom: len + 1.
].
].
^ res
]
writeOn: aMsg [
| type |
type := self seq bitShift: 6.
type := type bitOr: self class messageType.
"Write the header. Skip Ind, Sequence are hardcoded"
aMsg putByte: self class classType.
aMsg putByte: type.
"Write all Mandantory parts"
self class Mandantory do: [:each | | tmp |
tmp := self perform: each key.
tmp writeOnDirect: aMsg.
].
(self class respondsTo: #Optional)
ifFalse: [
^ 0
].
self class Optional do: [:each | | tmp |
tmp := self perform: each key.
tmp ifNotNil: [
tmp writeOn: aMsg.
].
].
"TODO: Handle the Conditionals too"
^ 0
]
seq: aSeq [
seq := aSeq.
]
seq [
^ seq ifNil: [ 0 ]
]
]
GSM48MSG subclass: GSM48MMMessage [
<category: 'osmo-message'>
<comment: 'Baseclass for mobility managamenet'>
GSM48MMMessage class >> classType [ ^ 16r5 ]
GSM48MMMessage class >> msgLUAcc [ ^ 16r02 ]
GSM48MMMessage class >> msgLURej [ ^ 16r04 ]
GSM48MMMessage class >> msgLUReq [ ^ 16r08 ]
GSM48MMMessage class >> msgIdRes [ ^ 16r19 ]
GSM48MMMessage class >> msgIdReq [ ^ 16r18 ]
2010-11-24 20:46:34 +00:00
GSM48MMMessage class >> msgAuReq [ ^ 16r12 ]
GSM48MMMessage class >> msgAuRes [ ^ 16r14 ]
GSM48MMMessage class >> msgCMReq [ ^ 16r24 ]
GSM48MMMessage class >> msgIMSIDetach [ ^ 16r01 ]
]
GSM48MMMessage subclass: LocationUpdatingRequest [
<category: 'osmo-message'>
Mandantory := nil.
Optional := nil.
LocationUpdatingRequest class >> messageType [ ^ self msgLUReq ]
LocationUpdatingRequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
LocationUpdatingRequest class >> Optional [
^ Optional ifNil: [ Optional := 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.
]
]
GSM48MMMessage subclass: LocationUpdatingAccept [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
Mandantory := nil.
Optional := nil.
LocationUpdatingAccept class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
LocationUpdatingAccept class >> Optional [
^ Optional ifNil: [ Optional := OrderedCollection new ].
]
LocationUpdatingAccept class >> messageType [ ^ self msgLUAcc ]
LocationUpdatingAccept class >> initialize [
self addMandantory: 'cause' with: GSM48Lai.
self addOptional: 'mi' with: GSM48MIdentity.
self addOptional: 'follow' with: GSM48FollowOn.
self addOptional: 'cts' with: GSM48CTSPermission.
]
]
GSM48MMMessage subclass: LocationUpdatingReject [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
Mandantory := nil.
Optional := nil.
LocationUpdatingReject class >> messageType [ ^ self msgLURej ]
LocationUpdatingReject class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
LocationUpdatingReject class >> initialize [
self addMandantory: 'cause' with: GSM48RejectCause.
]
]
2010-11-24 20:46:34 +00:00
GSM48MMMessage subclass: AuthenticationRequest [
<category: 'osmo-message'>
Mandantory := nil.
Optional := nil.
2010-11-24 20:46:34 +00:00
AuthenticationRequest class >> messageType [ ^ self msgAuReq ]
AuthenticationRequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
AuthenticationRequest class >> initialize [
self addMandantory: 'key' with: GSM48KeySeqLuType.
self addMandantory: 'auth' with: GSM48AuthRand.
]
]
GSM48MMMessage subclass: AuthenticationResponse [
<category: 'osmo-message'>
Mandantory := nil.
AuthenticationResponse class >> messageType [ ^ self msgAuRes ]
AuthenticationResponse class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
AuthenticationResponse class >> initialize [
self addMandantory: 'sres' with: GSM48AuthSRES.
]
]
GSM48MMMessage subclass: IdentityRequest [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
Mandantory := nil.
IdentityRequest class >> messageType [ ^ self msgIdReq ]
IdentityRequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
IdentityRequest class >> initialize [
self addMandantory: 'idType' with: GSM48IdentityType.
]
]
2010-11-26 23:17:34 +00:00
GSM48MMMessage subclass: IdentityResponse [
2010-11-19 18:11:55 +00:00
<category: 'osmo-message'>
2010-11-26 23:17:34 +00:00
Mandantory := nil.
IdentityResponse class >> messageType [ ^ self msgIdRes ]
IdentityResponse class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
IdentityResponse class >> initialize [
self addMandantory: 'mi' with: GSM48MIdentity.
]
]
GSM48MMMessage subclass: CMServiceRequest [
<category: 'osmo-message'>
Mandantory := nil.
CMServiceRequest class >> messageType [ ^ self msgCMReq ]
CMServiceRequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
CMServiceRequest class >> initialize [
self addMandantory: 'keyAndType' with: GSM48KeySeqLuType.
self addMandantory: 'cm2' with: GSM48Classmark2.
self addMandantory: 'mi' with: GSM48MIdentity.
"TODO: This ie and value are mixed and need to be ored"
"self addOptional: 'priority' with: GSM48PriorityIE"
]
]
GSM48MMMessage subclass: IMSIDetachIndication [
<category: 'osmo-message'>
Mandantory := nil.
IMSIDetachIndication class >> messageType [ ^ self msgIMSIDetach ]
IMSIDetachIndication class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
]
IMSIDetachIndication class >> initialize [
self addMandantory: 'cm1' with: GSM48Classmark1.
self addMandantory: 'mi' with: GSM48MIdentity.
]
]
Eval [
LocationUpdatingRequest initialize.
LocationUpdatingReject initialize.
LocationUpdatingAccept initialize.
AuthenticationRequest initialize.
AuthenticationResponse initialize.
IdentityRequest initialize.
2010-11-26 23:17:34 +00:00
IdentityResponse initialize.
CMServiceRequest initialize.
IMSIDetachIndication initialize.
]