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/BSSMAP.st

198 lines
4.8 KiB
Smalltalk
Raw Normal View History

Object subclass: GSM0808IE [
<category: 'osmo-message'>
<comment: 'Base class of IEs for GSM0808'>
]
Object subclass: GSM0808Helper [
GSM0808Helper class >> msgComplL3 [ <category: 'spec'> ^ 16r57 ]
GSM0808Helper class >> msgReset [ <category: 'spec'> ^ 16r30 ]
GSM0808Helper class >> msgResetAck [ <category: 'spec'> ^ 16r31 ]
GSM0808Helper class >> msgClear [ <category: 'spec'> ^ 16r20 ]
GSM0808Helper class >> msgClearComp [ <category: 'spec'> ^ 16r21 ]
]
Object subclass: LAI [
| mcc mnc |
<category: 'osmo-message'>
<comment: 'Generate a Location Area Identifier'>
LAI class >> initWith: mcc mnc: mnc [
^ self new
mcc: mcc;
mnc: mnc;
yourself
]
LAI class >> parseFrom: aByteArray [
| mcc mnc |
mcc := ByteArray new: 3.
mcc at: 1 put: ((aByteArray at: 1) bitAnd: 16rF).
mcc at: 2 put: (((aByteArray at: 1) bitAnd: 16rF0) bitShift: -4).
mcc at: 3 put: ((aByteArray at: 2) bitAnd: 16rF).
mcc := BCD decode: mcc.
mnc := ByteArray new: 3.
mnc at: 1 put: ((aByteArray at: 3) bitAnd: 16rF).
mnc at: 2 put: (((aByteArray at: 3) bitAnd: 16rF0) bitShift: -4).
mnc at: 3 put: (((aByteArray at: 2) bitAnd: 16rF0) bitShift: -4).
"Need to check if we have two or three bytes here."
(mnc at: 3) = 16rF
ifTrue: [
mnc := BCD decode: (mnc copyFrom: 1 to: 2).
]
ifFalse: [
mnc := BCD decode: mnc.
].
^ LAI initWith: mcc mnc: mnc.
]
LAI class >> generateLAI: mcc mnc: mnc [
<category: 'creation'>
| lai |
lai := LAI initWith: mcc mnc: mnc.
^ lai toMessage asByteArray.
]
writeOn: aMsg [
| mcc_bcd mnc_bcd lai_0 lai_1 lai_2 |
mcc_bcd := BCD encode: mcc.
mnc_bcd := BCD encode: mnc.
lai_0 := (mcc_bcd at: 1) bitOr: ((mcc_bcd at: 2) bitShift: 4).
lai_1 := mcc_bcd at: 3.
mnc > 99
ifTrue: [
lai_1 := lai_1 bitOr: ((mnc_bcd at: 3) bitShift: 4).
lai_2 := (mnc_bcd at: 1) bitOr: ((mnc_bcd at: 2) bitShift: 4)
]
ifFalse: [
lai_1 := lai_1 bitOr: (16rF bitShift: 4).
lai_2 := (mnc_bcd at: 2) bitOr: ((mnc_bcd at: 3) bitShift: 4)
].
aMsg putByte: lai_0.
aMsg putByte: lai_1.
aMsg putByte: lai_2.
]
mcc [
^ mcc
]
mcc: aMcc [
mcc := aMcc.
]
mnc [
^ mnc
]
mnc: aMnc [
mnc := aMnc.
]
]
GSM0808IE subclass: GSMCellIdentifier [
<category: 'osmo-message'>
<comment: 'Generate a GSM0808 Cell Identifier'>
| lai lac ci |
GSMCellIdentifier class >> elementId [ <category: 'spec'> ^ 5 ]
GSMCellIdentifier class >> initWith: mcc mnc: mnc lac: lac ci: ci [
<category: 'creation'>
^ (self new)
mcc: mcc mnc: mnc lac: lac ci: ci;
yourself
]
GSMCellIdentifier class >> parseFrom: aByteArray [
| lai lac ci |
(aByteArray at: 3) = 0
ifFalse: [
Error signal: 'Can not handle Cell Identifier of type != 0'.
].
lai := LAI parseFrom: (aByteArray copyFrom: 4).
lac := (aByteArray ushortAt: 7) swap16.
ci := (aByteArray ushortAt: 9) swap16.
^ self new
mcc: lai mcc mnc: lai mnc lac: lac ci: ci;
yourself
]
mcc: aMcc mnc: aMnc lac: aLac ci: aCi [
<category: 'creation'>
lai := LAI initWith: aMcc mnc: aMnc.
lac := aLac.
ci := aCi.
]
mcc [
<category: 'access'>
^ lai mcc
]
mnc [
<category: 'access'>
^ lai mnc
]
lac [
<category: 'access'>
^ lac
]
ci [
<category: 'access'>
^ ci
]
writeOn: aMsg [
<category: 'creation'>
| lai_data |
lai_data := lai toMessageOrByteArray.
aMsg putByte: self class elementId.
aMsg putByte: 1 + lai_data size + 2 + 2.
aMsg putByte: 0.
aMsg putByteArray: lai_data.
aMsg putLen16: lac.
aMsg putLen16: ci.
]
]
GSM0808IE subclass: GSMLayer3Info [
<category: 'osmo-message'>
<comment: 'Generate a Layer3 IE'>
| data |
GSMLayer3Info class >> elementId [ <category: 'spec'> ^ 23 ]
GSMLayer3Info class >> initWith: data [
<category: 'creation'>
^ (self new)
data: data;
yourself
]
data: aData [
<category: 'creation'>
data := aData
]
writeOn: aMsg [
| dat |
<category: 'creation'>
aMsg putByte: self class elementId.
dat := data toMessageOrByteArray.
aMsg putByte: dat size.
aMsg putByteArray: dat.
]
]