aboutsummaryrefslogtreecommitdiffstats
path: root/BSSMAP.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-11-17 10:21:48 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-11-17 10:21:48 +0100
commit07d628ccfcbc180fd64783c27ecfcb7d834fc01c (patch)
tree996362a29596802aa3aa10c3b81e99bea2e3a3ad /BSSMAP.st
parent56bef0a6b274a760bd1dbf681dafc74a7860231d (diff)
Add GSM0808 creation support and add some test cases for these messages
Diffstat (limited to 'BSSMAP.st')
-rw-r--r--BSSMAP.st130
1 files changed, 130 insertions, 0 deletions
diff --git a/BSSMAP.st b/BSSMAP.st
new file mode 100644
index 0000000..17650f8
--- /dev/null
+++ b/BSSMAP.st
@@ -0,0 +1,130 @@
+Object subclass: GSM0808IE [
+ <comment: 'Base class of IEs for GSM0808'>
+]
+
+Object subclass: GSM0808Helper [
+ GSM0808Helper class >> msgComplL3 [ ^ 16r57 ]
+ GSM0808Helper class >> msgReset [ ^ 16r30 ]
+ GSM0808Helper class >> msgResetAck [ ^ 16r31 ]
+ GSM0808Helper class >> msgClear [ ^ 16r20 ]
+ GSM0808Helper class >> msgClearComp [ ^ 16r21 ]
+]
+
+Object subclass: GSM0808BSSMAP [
+ | ies type |
+
+ GSM0808BSSMAP class >> initWith: type [
+ ^ (self new)
+ type: type;
+ yourself
+ ]
+
+ type: aType [
+ type := aType.
+ ]
+
+ addIe: aIe [
+ self ies add: aIe.
+ ]
+
+ ies [
+ ies isNil ifTrue: [
+ ies := OrderedCollection new.
+ ].
+
+ ^ ies
+ ]
+
+ storeOn: aMsg [
+ aMsg putByte: type.
+
+ self ies do: [:each | each storeOn: aMsg ]
+ ]
+]
+
+Object subclass: BCD [
+ BCD class >> encode: aNumber [
+ | col num |
+ col := OrderedCollection new.
+
+ num := aNumber.
+ 1 to: 3 do: [:each |
+ col add: num \\ 10.
+ num := num // 10.
+ ].
+
+ ^ col reverse asByteArray
+ ]
+]
+
+Object subclass: LAI [
+ LAI class >> generateLAI: mcc mnc: mnc [
+ | 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)
+ ].
+
+ ^ ByteArray with: lai_0 with: lai_1 with: lai_2
+ ]
+]
+
+GSM0808IE subclass: GSMCellIdentifier [
+ | mcc mnc lac ci |
+ GSMCellIdentifier class >> elementId [ ^ 5 ]
+ GSMCellIdentifier class >> initWith: mcc mnc: mnc lac: lac ci: ci [
+ ^ (self new)
+ mcc: mcc mnc: mnc lac: lac ci: ci;
+ yourself
+ ]
+
+ mcc: aMcc mnc: aMnc lac: aLac ci: aCi [
+ mcc := aMcc.
+ mnc := aMnc.
+ lac := aLac.
+ ci := aCi.
+ ]
+
+ storeOn: aMsg [
+ | lai |
+ lai := LAI generateLAI: mcc mnc: mnc.
+
+ aMsg putByte: self class elementId.
+ aMsg putByte: 1 + lai size + 2 + 2.
+ aMsg putByte: 0.
+ aMsg putByteArray: lai.
+ aMsg putLen16: lac.
+ aMsg putLen16: ci.
+ ]
+]
+
+GSM0808IE subclass: GSMLayer3Info [
+ | data |
+ GSMLayer3Info class >> elementId [ ^ 23 ]
+ GSMLayer3Info class >> initWith: data [
+ ^ (self new)
+ data: data;
+ yourself
+ ]
+
+ data: aData [
+ data := aData
+ ]
+
+ storeOn: aMsg [
+ aMsg putByte: self class elementId.
+ aMsg putByte: data size.
+ aMsg putByteArray: data.
+ ]
+]