aboutsummaryrefslogtreecommitdiffstats
path: root/BSSMAP.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-12-15 12:36:17 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-12-15 12:52:34 +0100
commit716e4ac30cb0235e25132dd23349f67afeeff7e9 (patch)
tree8fd1ce8e94bc0c0d03a31286a2420da10bf7c18e /BSSMAP.st
parent1b56da9dfbe67cebf024422a4e816366046eb284 (diff)
GSM: Moved all classes to the osmo-network module
Diffstat (limited to 'BSSMAP.st')
-rw-r--r--BSSMAP.st637
1 files changed, 0 insertions, 637 deletions
diff --git a/BSSMAP.st b/BSSMAP.st
deleted file mode 100644
index e89da2c..0000000
--- a/BSSMAP.st
+++ /dev/null
@@ -1,637 +0,0 @@
-"
- (C) 2010 by Holger Hans Peter Freyther
- All Rights Reserved
-
- This program is free software: you can redistribute it and/or modify
- it under the terms of the GNU Affero General Public License as
- published by the Free Software Foundation, either version 3 of the
- License, or (at your option) any later version.
-
- This program is distributed in the hope that it will be useful,
- but WITHOUT ANY WARRANTY; without even the implied warranty of
- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- GNU Affero General Public License for more details.
-
- You should have received a copy of the GNU Affero General Public License
- along with this program. If not, see <http://www.gnu.org/licenses/>.
-"
-
-IEBase subclass: GSM0808IE [
- <category: 'osmo-message'>
- <comment: 'Base class of IEs for GSM0808'>
-
- GSM0808IE class >> length: aByteArray [
- ^ (aByteArray at: 2) + 1.
- ]
-]
-
-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 ]
- GSM0808Helper class >> msgClearReq [ <category: 'spec'> ^ 16r22 ]
- GSM0808Helper class >> msgCipherModeCmd [ <category: 'spec'> ^ 16r53 ]
- GSM0808Helper class >> msgCipherModeCmpl [ <category: 'spec'> ^ 16r55 ]
- GSM0808Helper class >> msgAssRequest [ <category: 'spec'> ^ 16r1 ]
- GSM0808Helper class >> msgAssComplete [ <category: 'spec'> ^ 16r2 ]
-]
-
-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
- ]
-
- writeOnDirect: aMsg [
- <category: 'creation'>
- | lai_data |
- lai_data := lai toMessageOrByteArray.
-
- 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
- ]
-
- GSMLayer3Info class >> parseFrom: aByteArray [
- | size |
- size := aByteArray at: 2.
- ^ GSMLayer3Info initWith: (aByteArray copyFrom: 3 to: 2 + size)
- ]
-
- data: aData [
- <category: 'creation'>
- data := aData
- ]
-
- data [
- ^ data
- ]
-
- writeOnDirect: aMsg [
- | dat |
- <category: 'creation'>
-
- dat := data toMessageOrByteArray.
- aMsg putByte: dat size.
- aMsg putByteArray: dat.
- ]
-]
-
-GSM0808IE subclass: GSMCauseIE [
- | cause |
-
- <category: 'osmo-message'>
- <comment: 'Generate a CauseIE'>
- "TODO: Only simple ones are supported right now"
-
- GSMCauseIE class >> elementId [ <category: 'spec'> ^ 4 ]
-
- GSMCauseIE class >> initWith: aCause [
- ^ self new
- cause: aCause;
- yourself
- ]
- GSMCauseIE class >> parseFrom: aByteArray [
- | size |
- size := aByteArray at: 2.
- size = 1
- ifFalse: [
- ^ Error signal: 'Extended error codes are not supported.'.
- ].
-
- ^ GSMCauseIE initWith: (aByteArray at: 3)
- ]
-
- cause [ ^ cause ]
- cause: aCause [ cause := aCause ]
-
- writeOnDirect: aMsg [
- aMsg putByte: 1.
- aMsg putByte: cause.
- ]
-]
-
-GSM0808IE subclass: GSM0808ChosenChannel [
- | channel |
-
- GSM0808ChosenChannel class >> elementId [ ^ 33 ]
- GSM0808ChosenChannel class >> initWith: aChannel [
- ^ self new
- channel: aChannel;
- yourself
- ]
-
- GSM0808ChosenChannel class >> length: aByteArray [
- ^ 1
- ]
-
- GSM0808ChosenChannel class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 2).
- ]
-
- channel [ ^ channel ]
- channel: aChannel [ channel := aChannel ]
-
- writeOnDirect: aMsg [
- aMsg putByte: channel
- ]
-]
-
-GSM0808IE subclass: GSM0808IMSI [
- | imsi |
-
- GSM0808IMSI class >> elementId [ ^ 8 ]
- GSM0808IMSI class >> initWith: anImsi [
- ^ self new
- imsi: anImsi;
- yourself
- ]
-
- GSM0808IMSI class >> parseFrom: aByteArray [
- | imsi |
- imsi := (GSM48MIdentity parseFrom: (aByteArray copyFrom: 2)) imsi.
- imsi ifNil: [
- ^ Error signal: 'MI did not include the IMSI.'.
- ].
-
- ^ GSM0808IMSI initWith: imsi.
- ]
-
- imsi [ ^ imsi ]
- imsi: anIMSI [ imsi := anIMSI ]
-
- writeOnDirect: aMsg [
- | mi |
- mi := GSM48MIdentity new.
- mi imsi: imsi.
-
- mi writeOnDirect: aMsg.
- ]
-]
-
-GSM0808IE subclass: GSM0808CellIdentifierList [
- | ident cells |
-
- GSM0808CellIdentifierList class >> elementId [ ^ 26 ]
- GSM0808CellIdentifierList class >> parseFrom: aByteArray [
- | len ident cells |
-
- len := aByteArray at: 2.
- len < 2
- ifTrue: [
- Error signal: 'No place for the cell identifier list'.
- ].
-
- (len - 1) even
- ifFalse: [
- Error signal: 'Need to have an even number of cells'.
- ].
-
- ident := aByteArray at: 3.
-
- cells := OrderedCollection new.
- 1 to: len - 1 by: 2 do: [:each |
- | cell |
- cell := (aByteArray ushortAt: 3 + each) swap16.
- cells add: cell.
- ].
-
- ^ self new
- cells: cells;
- ident: ident;
- yourself
- ]
-
- ident [ ^ ident ]
- ident: anIdent [ ident := anIdent bitAnd: 16r00FF ]
-
- cells [ ^ cells ]
- cells: aCells [ cells := aCells ]
-
- writeOnDirect: aMsg [
- aMsg putByte: 1 + (cells size * 2).
- aMsg putByte: ident.
-
- cells do: [:lac |
- aMsg putLen16: lac.
- ].
- ]
-]
-
-GSM0808IE subclass: GSM0808EncrIE [
- | crypt key |
-
- GSM0808EncrIE class >> encrNone [ ^ -0 ]
- GSM0808EncrIE class >> encrA1 [ ^ -1 ]
- GSM0808EncrIE class >> encrA2 [ ^ -2 ]
- GSM0808EncrIE class >> encrA3 [ ^ -3 ]
- GSM0808EncrIE class >> encrA4 [ ^ -4 ]
- GSM0808EncrIE class >> encrA5 [ ^ -5 ]
- GSM0808EncrIE class >> encrA6 [ ^ -6 ]
- GSM0808EncrIE class >> encrA7 [ ^ -7 ]
-
- GSM0808EncrIE class >> elementId [ ^ 10 ]
- GSM0808EncrIE class >> initWith: aCrypt key: aKey [
- ^ self new
- crypt: aCrypt;
- key: aKey;
- yourself
- ]
-
- GSM0808EncrIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 3) key: (aByteArray copyFrom: 4).
- ]
-
- crypt [ ^ crypt ]
- crypt: aCrypt [
- crypt := aCrypt.
- ]
-
- key [ ^ key ]
- key: aKey [
- crypt > 1 ifTrue: [
- aKey size = 8 ifFalse: [
- aKey printNl.
- self error: 'When encryption is enabled key must be eight byte.'.
- ].
- ].
-
- key := aKey
- ]
-
- supports: aCrypt [
- ((crypt bitShift: aCrypt) bitAnd: 16r1) > 0
- ]
-
- writeOnDirect: aMsg [
- aMsg putByte: key size + 1.
- aMsg putByte: crypt.
- aMsg putByteArray: key.
- ]
-]
-
-GSM0808IE subclass: GSM0808ChosenEncrIE [
- | algo |
-
- GSM0808ChosenEncrIE class >> elementId [ ^ 44 ]
- GSM0808ChosenEncrIE class >> initWith: anAlgo [
- ^ self new
- cryptAlgo: anAlgo;
- yourself
- ]
-
- GSM0808ChosenEncrIE class >> length: aByteArray [
- ^ 1
- ]
-
- GSM0808ChosenEncrIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 2)
- ]
-
- cryptAlgo [ ^ algo ]
- cryptAlgo: anAlgo [
- (anAlgo < 0 or: [anAlgo > 255])
- ifTrue: [
- self error: 'Crypt algo must be from 0-255'.
- ].
-
- algo := anAlgo.
- ]
-
- writeOnDirect: aMsg [
- aMsg putByte: algo.
- ]
-]
-
-GSM0808IE subclass: GSM0808ChannelTypeIE [
- | type preferred codecs |
-
- GSM0808ChannelTypeIE class >> speechSpeech [ ^ 1 ]
- GSM0808ChannelTypeIE class >> speechData [ ^ 2 ]
- GSM0808ChannelTypeIE class >> speechSignalling [ ^ 3 ]
-
- "TODO: provide defs for the 3.2.2.11 ChannelType rate"
-
- GSM0808ChannelTypeIE class >> elementId [ ^ 11 ]
- GSM0808ChannelTypeIE class >> initWith: aType audio: anAudioType codecs: codecs [
- ^ self new
- type: aType;
- preferred: anAudioType;
- audioCodecs: codecs;
- yourself
- ]
-
- GSM0808ChannelTypeIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 3)
- audio: (aByteArray at: 4)
- codecs: (aByteArray copyFrom: 5)
- ]
-
- type [ ^ type ]
- type: aType [
- type := aType
- ]
-
- preferred [ ^ preferred ]
- preferred: aPreferred [ preferred := aPreferred ]
-
-
- "TODO: This should decode/encode the codecs"
- audioCodecs [ ^ codecs ]
- audioCodecs: aCodecs [ codecs := aCodecs. ]
-
- writeOnDirect: aMsg [
- aMsg putByte: 2 + codecs size.
- aMsg putByte: type.
- aMsg putByte: preferred.
- aMsg putByteArray: codecs.
- ]
-]
-
-GSM0808IE subclass: GSM0808CICIE [
- | cic |
- GSM0808CICIE class >> elementId [ ^ 1 ]
- GSM0808CICIE class >> length: aByteArray [ ^ 2 ]
-
- GSM0808CICIE class >> initWith: aByteArray [
- ^ self new
- cic: aByteArray;
- yourself.
- ]
-
- GSM0808CICIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray copyFrom: 2 to: 3)
- ]
-
- cic [
- ^ cic
- ]
-
- cic: aCic [
- aCic size = 2
- ifFalse: [
- ^ self error: 'CIC must be two bytes'.
- ].
-
- cic := aCic.
- ]
-
- writeOnDirect: aMsg [
- aMsg putByteArray: cic.
- ]
-]
-
-GSM0808IE subclass: GSM0808CauseIE [
- | cause |
-
- GSM0808CauseIE class >> elementId [ ^ 21 ]
- GSM0808CauseIE class >> length: aByteArray [ ^ 1 ]
- GSM0808CauseIE class >> initWith: aCause [
- ^ self new
- cause: aCause;
- yourself
- ]
-
- GSM0808CauseIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 2)
- ]
-
- cause [ ^ cause ]
- cause: aCause [ cause := aCause ]
-
- writeOnDirect: aMsg [
- aMsg putByte: cause.
- ]
-]
-
-GSM0808IE subclass: GSM0808SpeechVerIE [
- | speech |
-
- GSM0808SpeechVerIE class >> elementId [ ^ 64 ]
- GSM0808SpeechVerIE class >> length: aByteArray [ ^ 1 ]
- GSM0808SpeechVerIE class >> initWith: aVersion [
- ^ self new
- speechVersion: aVersion;
- yourself
- ]
-
- GSM0808SpeechVerIE class >> parseFrom: aByteArray [
- ^ self initWith: (aByteArray at: 2)
- ]
-
- speechVersion: aVersion [
- speech := aVersion
- ]
-
- speechVersion [ ^ speech ]
-
-
- writeOnDirect: aMsg [
- aMsg putByte: speech.
- ]
-]
-
-GSM0808IE subclass: GSM0808Classmark2IE [
- | cm |
-
- GSM0808Classmark2IE class >> elementId [ ^ 18 ]
- GSM0808Classmark2IE class >> initWith: aCM [
- ^ self new
- cm: aCM; yourself
- ]
-
- GSM0808Classmark2IE class >> parseFrom: aByteArray [
- | size |
- size := aByteArray at: 2.
-
- ^ self initWith: (aByteArray copyFrom: 3 to: 3 + size - 1)
- ]
-
- cm: aCM [
- cm := aCM
- ]
-
- writeOnDirect: aMsg [
- aMsg putByte: cm size.
- aMsg putByteArray: cm.
- ]
-]
-
-GSM0808IE subclass: GSM0808Classmark3IE [
- | cm |
- GSM0808Classmark3IE class >> elementId [ ^ 19 ]
- GSM0808Classmark3IE class >> initWith: aCM [
- ^ self new
- cm: aCM; yourself
- ]
-
- GSM0808Classmark3IE class >> parseFrom: aByteArray [
- | size |
- size := aByteArray at: 2.
-
- ^ self initWith: (aByteArray copyFrom: 3 to: 3 + size - 1)
- ]
-
- cm: aCM [
- cm := aCM.
- ]
-
- writeOnDirect: aMsg [
- aMsg putByte: cm size.
- aMsg putByteArray: cm.
- ]
-]