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

828 lines
20 KiB
Smalltalk

"
(C) 2010-2012 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: 'OsmoGSM'>
<comment: 'Base class of IEs for GSM0808'>
GSM0808IE class >> length: aStream [
"Length plus the length field"
^ aStream peek + 1
]
]
Object subclass: GSM0808Helper [
<category: 'OsmoGSM'>
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 >> msgPaging [ <category: 'spec'> ^ 2r01010010 ]
GSM0808Helper class >> msgCipherModeCmd [ <category: 'spec'> ^ 16r53 ]
GSM0808Helper class >> msgCipherModeCmpl [ <category: 'spec'> ^ 16r55 ]
GSM0808Helper class >> msgAssRequest [ <category: 'spec'> ^ 16r1 ]
GSM0808Helper class >> msgAssComplete [ <category: 'spec'> ^ 16r2 ]
GSM0808Helper class >> msgAssFailure [ <category: 'spec'> ^ 16r3 ]
GSM0808Helper class >> msgCMUpdate [ <category: 'spec'> ^ 2r01010100 ]
]
Object subclass: LAI [
| mcc mnc |
<category: 'OsmoGSM'>
<comment: 'Generate a Location Area Identifier'>
LAI class >> initWith: mcc mnc: mnc [
^ self new
mcc: mcc;
mnc: mnc;
yourself
]
LAI class >> parseFrom: aStream [
| mcc mnc tmp |
"TODO: this would benefit from a 4 bit read..."
tmp := aStream next: 3.
mcc := ByteArray new: 3.
mcc at: 1 put: ((tmp at: 1) bitAnd: 16rF).
mcc at: 2 put: (((tmp at: 1) bitAnd: 16rF0) bitShift: -4).
mcc at: 3 put: ((tmp at: 2) bitAnd: 16rF).
mcc := BCD decode: mcc.
mnc := ByteArray new: 3.
mnc at: 1 put: ((tmp at: 3) bitAnd: 16rF).
mnc at: 2 put: (((tmp at: 3) bitAnd: 16rF0) bitShift: -4).
mnc at: 3 put: (((tmp 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 [
| lai lac ci |
<category: 'OsmoGSM'>
<comment: 'Generate a GSM0808 Cell Identifier'>
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: aStream [
| lai lac ci |
aStream skip: 1.
(aStream next) = 0
ifFalse: [
Error signal: 'Can not handle Cell Identifier of type != 0'.
].
lai := LAI parseFrom: aStream.
lac := ((aStream next: 2) asByteArray ushortAt: 1) swap16.
ci := ((aStream next: 2) asByteArray ushortAt: 1) 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 [
| data |
<category: 'OsmoGSM'>
<comment: 'Generate a Layer3 IE'>
GSMLayer3Info class >> elementId [ <category: 'spec'> ^ 23 ]
GSMLayer3Info class >> initWith: data [
<category: 'creation'>
^ (self new)
data: data;
yourself
]
GSMLayer3Info class >> parseFrom: aStream [
| size |
size := aStream next.
^ GSMLayer3Info initWith: (aStream next: 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: 'OsmoGSM'>
<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: aStream [
| size |
size := aStream next.
size = 1
ifFalse: [
^ Error signal: 'Extended error codes are not supported.'.
].
^ GSMCauseIE initWith: aStream next.
]
cause [ ^ cause ]
cause: aCause [ cause := aCause ]
writeOnDirect: aMsg [
aMsg putByte: 1.
aMsg putByte: cause.
]
]
GSM0808IE subclass: GSM0808ChosenChannel [
| channel |
<category: 'OsmoGSM'>
GSM0808ChosenChannel class >> elementId [ ^ 33 ]
GSM0808ChosenChannel class >> initWith: aChannel [
^ self new
channel: aChannel;
yourself
]
GSM0808ChosenChannel class >> length: aStream [
^ 1
]
GSM0808ChosenChannel class >> parseFrom: aStream [
^ self initWith: aStream next.
]
channel [ ^ channel ]
channel: aChannel [ channel := aChannel ]
writeOnDirect: aMsg [
aMsg putByte: channel
]
]
GSM0808IE subclass: GSM0808IMSI [
| imsi |
<category: 'OsmoGSM'>
<comment: 'I represent 3.2.2.6 of GSM 08.08'>
GSM0808IMSI class >> elementId [ ^ 8 ]
GSM0808IMSI class >> initWith: anImsi [
^ self new
imsi: anImsi;
yourself
]
GSM0808IMSI class >> parseFrom: aStream [
| imsi |
imsi := (GSM48MIdentity parseFrom: aStream) 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 |
<category: 'OsmoGSM'>
<comment: 'I represent a 3.2.2.27 of GSM 08.08'>
GSM0808CellIdentifierList class [
cellWholeGlobal [
<category: 'types'>
"The whole Cell Global Identification, CGI, is used to identify the cells."
^ 2r0000
]
cellLocationAreaCodeCi [
<category: 'types'>
"Location Area Code, LAC, and Cell Identify, CI, is used to identify the cells."
^ 2r0001
]
cellCi [
<category: 'types'>
"Cell Identity, CI, is used to identify the cells."
^ 2r0010
]
cellNoCell [
<category: 'types'>
"No cell is associated with the transaction."
^ 2r0011
]
cellLocationAreaIdentification [
<category: 'types'>
"Location Area Identification, LAI, is used to identify all cells within a Location Area."
^ 2r0100
]
cellLocationAreaCode [
<category: 'types'>
"Location Area Code, LAC, is used to identify all cells within a location area."
^ 2r0101
]
cellAllCells [
<category: 'types'>
"All cells on the BSS are identified."
^ 2r0110
]
cellUtranHandoverPlmnLacRnc [
<category: 'types'>
"Intersystem Handover to UTRAN or cdma2000. PLMN-ID, LAC, and RNC-ID, are encoded to identify the target RNC."
^ 2r1000
]
cellUtranHandoverRnc [
<category: 'types'>
"Intersystem Handover to UTRAN or cdma2000. The RNC-ID is coded to identify the target RNC."
^ 2r1001
]
cellUtranHanoverLacRnc [
<category: 'types'>
"Intersystem Handover to UTRAN or cdma2000. LAC and RNC-ID are encoded to identify the target RNC."
^ 2r1010
]
]
GSM0808CellIdentifierList class >> elementId [ ^ 26 ]
GSM0808CellIdentifierList class >> parseFrom: aStream [
| len ident cells |
len := aStream next.
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 := aStream next.
cells := OrderedCollection new.
1 to: len - 1 by: 2 do: [:each |
| cell |
cell := ((aStream next: 2) asByteArray ushortAt: 1) 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.
"TODO: assumes that cells are only lacs.."
cells do: [:lac |
aMsg putLen16: lac.
].
]
]
GSM0808IE subclass: GSM0808EncrIE [
| crypt key |
<category: 'OsmoGSM'>
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: aStream [
| len |
len := aStream next.
^ self initWith: (aStream next) key: (aStream next: len - 1).
]
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 |
<category: 'OsmoGSM'>
GSM0808ChosenEncrIE class >> elementId [ ^ 44 ]
GSM0808ChosenEncrIE class >> initWith: anAlgo [
^ self new
cryptAlgo: anAlgo;
yourself
]
GSM0808ChosenEncrIE class >> length: aStream [
^ 1
]
GSM0808ChosenEncrIE class >> parseFrom: aStream [
^ self initWith: (aStream next).
]
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 |
<category: 'OsmoGSM'>
<comment: 'I implement 3.2.2.11 of GSM08.08'>
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 [
chanSpeechFullBm [ <category: 'ChannelType-Speech'> ^ 2r1000 ]
chanSpeechHalfLm [ <category: 'ChannelType-Speech'> ^ 2r1001 ]
chanSpeechFullPref [ <category: 'ChannelType-Speech'> ^ 2r1010 ]
chanSpeechHalfPref [ <category: 'ChannelType-Speech'> ^ 2r1011 ]
chanSpeechFullPrefNoChange [ <category: 'ChannelType-Speech'> ^ 2r11010 ]
chanSpeechHalfPrefNoChange [ <category: 'ChannelType-Speech'> ^ 2r11011 ]
chanSpeechAny [ <category: 'ChannelType-Speech'> ^ 2r1111 ]
chanSpeechAnyNoChange [ <category: 'ChannelType-Speec'> ^ 2r11111 ]
speechFullRateVersion1 [ <category: 'Speech-Version'> ^ 2r000001 ]
speechFullRateVersion2 [ <category: 'Speech-Version'> ^ 2r010001 ]
speechFullRateVersion3 [ <category: 'Speech-Version'> ^ 2r100001 ]
speechHalfRateVersion1 [ <category: 'Speech-Version'> ^ 2r000101 ]
speechHalfRateVersion2 [ <category: 'Speech-Version'> ^ 2r010101 ]
speechHalfRateVersion3 [ <category: 'Speech-Version'> ^ 2r100101 ]
buildPermittedSpeechList: aList [
| out |
out := aList asByteArray copy.
1 to: out size - 1 do: [:pos |
out at: pos put: ((out at: pos) bitOr: 16r80)
].
^ out
]
]
GSM0808ChannelTypeIE class >> elementId [ ^ 11 ]
GSM0808ChannelTypeIE class >> initWith: aType audio: anAudioType [
^ self new
type: aType;
preferred: anAudioType;
yourself
]
GSM0808ChannelTypeIE class >> parseFrom: aStream [
| size |
size := aStream next.
^ (self initWith: aStream next audio: aStream next)
audioCodecs: (aStream next: size - 2);
yourself
]
type [ ^ type ]
type: aType [
type := aType
]
preferred [ ^ preferred ]
preferred: aPreferred [ preferred := aPreferred ]
audioCodecs: aList [
<category: 'audio-codes'>
self audioCodecsData: (self class buildPermittedSpeechList: aList).
]
"TODO: This should decode/encode the codecs"
audioCodecsData [ ^ codecs ]
audioCodecsData: aCodecs [ codecs := aCodecs. ]
writeOnDirect: aMsg [
aMsg putByte: 2 + codecs size.
aMsg putByte: type.
aMsg putByte: preferred.
aMsg putByteArray: codecs.
]
]
GSM0808IE subclass: GSM0808CICIE [
| cic |
<category: 'OsmoGSM'>
GSM0808CICIE class >> elementId [ ^ 1 ]
GSM0808CICIE class >> length: aStream [ ^ 2 ]
GSM0808CICIE class >> initWith: aByteArray [
<category: 'creation'>
^ self new
cic: aByteArray;
yourself.
]
GSM0808CICIE class >> initWithMultiplex: aMul timeslot: aTs [
<category: 'creation'>
^ self new
multiplex: aMul timeslot: aTs;
yourself
]
GSM0808CICIE class >> parseFrom: aStream [
<category: 'creation'>
^ self initWith: (aStream next: 2)
]
cic [
^ cic
]
multiplex: aMul timeslot: aTimeslot [
| cic |
cic := (aMul bitAnd: 16r7FF) bitShift: 5.
cic := cic bitOr: (aTimeslot bitAnd: 16r1F).
self cic: (Array
with: ((cic bitAnd: 16rFF00) bitShift: -8)
with: ((cic bitAnd: 16r00FF) bitShift: 0)).
]
cic: aCic [
aCic size = 2
ifFalse: [
^ self error: 'CIC must be two bytes'.
].
cic := aCic.
]
writeOnDirect: aMsg [
aMsg putByteArray: cic.
]
]
GSM0808IE subclass: GSM0808CauseIE [
| cause |
<category: 'OsmoGSM'>
GSM0808CauseIE class >> elementId [ ^ 21 ]
GSM0808CauseIE class >> length: aStream [ ^ 1 ]
GSM0808CauseIE class >> initWith: aCause [
^ self new
cause: aCause;
yourself
]
GSM0808CauseIE class >> parseFrom: aStream [
^ self initWith: aStream next
]
cause [ ^ cause ]
cause: aCause [ cause := aCause ]
writeOnDirect: aMsg [
aMsg putByte: cause.
]
]
GSM0808IE subclass: GSM0808SpeechVerIE [
| speech |
<category: 'OsmoGSM'>
GSM0808SpeechVerIE class >> elementId [ ^ 64 ]
GSM0808SpeechVerIE class >> length: aStream [ ^ 1 ]
GSM0808SpeechVerIE class >> initWith: aVersion [
^ self new
speechVersion: aVersion;
yourself
]
GSM0808SpeechVerIE class >> parseFrom: aStream [
^ self initWith: aStream next
]
speechVersion: aVersion [
speech := aVersion
]
speechVersion [ ^ speech ]
writeOnDirect: aMsg [
aMsg putByte: speech.
]
]
GSM0808IE subclass: GSM0808Classmark2IE [
| cm |
<category: 'OsmoGSM'>
GSM0808Classmark2IE class >> elementId [ ^ 18 ]
GSM0808Classmark2IE class >> initWith: aCM [
^ self new
cm: aCM; yourself
]
GSM0808Classmark2IE class >> parseFrom: aStream [
| size |
size := aStream next.
^ self initWith: (aStream next: size)
]
cm: aCM [
cm := aCM
]
writeOnDirect: aMsg [
aMsg putByte: cm size.
aMsg putByteArray: cm.
]
]
GSM0808IE subclass: GSM0808Classmark3IE [
| cm |
<category: 'OsmoGSM'>
GSM0808Classmark3IE class >> elementId [ ^ 19 ]
GSM0808Classmark3IE class >> initWith: aCM [
^ self new
cm: aCM; yourself
]
GSM0808Classmark3IE class >> parseFrom: aStream [
| size |
size := aStream next.
^ self initWith: (aStream next: size)
]
cm: aCM [
cm := aCM.
]
writeOnDirect: aMsg [
aMsg putByte: cm size.
aMsg putByteArray: cm.
]
]
GSM0808IE subclass: GSM0808Layer3MessageContents [
| layer3Message |
<category: 'OsmoGSM'>
GSM0808Layer3MessageContents class >> elementId [^32]
GSM0808Layer3MessageContents class >> initWith: aByteArray [
^self new
layer3Message: aByteArray;
yourself
]
GSM0808Layer3MessageContents class >> parseFrom: aStream [
| size |
size := aStream next.
^self initWith: (aStream next: size)
]
layer3Message: aByteArray [
layer3Message := aByteArray
]
writeOnDirect: aMsg [
aMsg
putByte: layer3Message size;
putByteArray: layer3Message.
]
]