diff --git a/A3A8.st b/A3A8.st deleted file mode 100644 index b5f56b5..0000000 --- a/A3A8.st +++ /dev/null @@ -1,49 +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 . -" - -Object subclass: A3A8 [ - A3A8 class >> initialize [ - DLD addLibrary: 'liba3a8.so' - ] - - A3A8 class >> COMP128_v3: aKI rand: aRand [ - | str | - - aKI size = 16 ifFalse: [ - ^ self error: 'KI needs to be 16 bytes' - ]. - - aRand size = 16 ifFalse: [ - ^ self error: 'RAND needs to be 16 bytes' - ]. - - - str := ByteArray new: 16. - self int_COMP128_v3: aKI rand: aRand res: (CObject new storage: str). - - ^ str - ] - - A3A8 class >> int_COMP128_v3: aKI rand: aRand res: aRes [ - - ] -] - -Eval [ - A3A8 initialize. -] diff --git a/BSSAP.st b/BSSAP.st deleted file mode 100644 index ae5ccd2..0000000 --- a/BSSAP.st +++ /dev/null @@ -1,149 +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 . -" - -Object subclass: BSSAPHelper [ - - - - BSSAPHelper class >> msgManagemnt [ ^ 0 ] - BSSAPHelper class >> msgDtap [ ^ 1 ] - - BSSAPHelper class >> prependManagement: aMsg [ - - "Prepent the BSSAP Management header" - | tmp | - - tmp := OrderedCollection new. - tmp add: self msgManagemnt. - tmp add: aMsg size. - aMsg prependByteArray: tmp asByteArray. - ] - - BSSAPHelper class >> prependDTAP: aMsg dlci: sapi [ - - "Prepend the DTAP header" - | tmp | - tmp := OrderedCollection new. - tmp add: self msgDtap. - tmp add: sapi. - tmp add: aMsg size. - aMsg prependByteArray: tmp asByteArray. - ] -] - -Object subclass: BSSAPMessage [ - BSSAPMessage class >> decode: bssap [ - | type | - type := bssap at: 1. - - BSSAPMessage allSubclassesDo: [:each | - each msgType = type - ifTrue: [ - ^ each parseFrom: bssap. - ] - ]. - - ^ Error signal: 'No handler for: ', type asString. - ] -] - -BSSAPMessage subclass: BSSAPManagement [ - | data | - - BSSAPManagement class >> msgType [ ^ BSSAPHelper msgManagemnt ] - BSSAPManagement class >> initWith: data [ - ^ (self new) - data: data; - yourself. - ] - - BSSAPMessage class >> parseFrom: aByteArray [ - | size data | - size := aByteArray at: 2. - data := aByteArray copyFrom: 3 to: 2 + size. - - ^ BSSAPManagement initWith: data. - ] - - data: aPayload [ - data := aPayload. - ] - - data [ - ^ data - ] - - writeOn: aMsg [ - | dat | - aMsg putByte: BSSAPHelper msgManagemnt. - - dat := data toMessageOrByteArray. - aMsg putByte: dat size. - aMsg putByteArray: dat. - ] -] - -BSSAPMessage subclass: BSSAPDTAP [ - | data li | - - BSSAPDTAP class >> msgType [ ^ BSSAPHelper msgDtap ] - BSSAPDTAP class >> initWith: data linkIdentifier: li [ - ^ self new - data: data; - linkIdentifier: li; - yourself - ] - - BSSAPDTAP class >> parseFrom: aByteArray [ - | li size dat | - li := aByteArray at: 2. - size := aByteArray at: 3. - dat := aByteArray copyFrom: 4 to: 4 + size - 1. - - ^ BSSAPDTAP initWith: dat linkIdentifier: li. - ] - - writeOn: aMsg [ - | dat | - - dat := data toMessageOrByteArray. - - aMsg putByte: self class msgType. - aMsg putByte: li. - aMsg putByte: dat size. - aMsg putByteArray: dat. - ] - - data [ - ^ data - ] - data: aData [ - data := aData. - ] - - sapi [ - ^ li bitAnd: 7 - ] - - linkIdentifier [ - ^ li - ] - linkIdentifier: aLi [ - li := aLi. - ] -] 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 . -" - -IEBase subclass: GSM0808IE [ - - - - GSM0808IE class >> length: aByteArray [ - ^ (aByteArray at: 2) + 1. - ] -] - -Object subclass: GSM0808Helper [ - GSM0808Helper class >> msgComplL3 [ ^ 16r57 ] - GSM0808Helper class >> msgReset [ ^ 16r30 ] - GSM0808Helper class >> msgResetAck [ ^ 16r31 ] - GSM0808Helper class >> msgClear [ ^ 16r20 ] - GSM0808Helper class >> msgClearComp [ ^ 16r21 ] - GSM0808Helper class >> msgClearReq [ ^ 16r22 ] - GSM0808Helper class >> msgCipherModeCmd [ ^ 16r53 ] - GSM0808Helper class >> msgCipherModeCmpl [ ^ 16r55 ] - GSM0808Helper class >> msgAssRequest [ ^ 16r1 ] - GSM0808Helper class >> msgAssComplete [ ^ 16r2 ] -] - -Object subclass: LAI [ - | mcc mnc | - - - - 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 [ - - | 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 | - 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 - ] - - 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 [ - - lai := LAI initWith: aMcc mnc: aMnc. - lac := aLac. - ci := aCi. - ] - - mcc [ - - ^ lai mcc - ] - - mnc [ - - ^ lai mnc - ] - - lac [ - - ^ lac - ] - - ci [ - - ^ ci - ] - - writeOnDirect: aMsg [ - - | 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 | - GSMLayer3Info class >> elementId [ ^ 23 ] - GSMLayer3Info class >> initWith: data [ - - ^ (self new) - data: data; - yourself - ] - - GSMLayer3Info class >> parseFrom: aByteArray [ - | size | - size := aByteArray at: 2. - ^ GSMLayer3Info initWith: (aByteArray copyFrom: 3 to: 2 + size) - ] - - data: aData [ - - data := aData - ] - - data [ - ^ data - ] - - writeOnDirect: aMsg [ - | dat | - - - dat := data toMessageOrByteArray. - aMsg putByte: dat size. - aMsg putByteArray: dat. - ] -] - -GSM0808IE subclass: GSMCauseIE [ - | cause | - - - - "TODO: Only simple ones are supported right now" - - GSMCauseIE class >> elementId [ ^ 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. - ] -] diff --git a/GSM48.st b/GSM48.st deleted file mode 100644 index c5c31fe..0000000 --- a/GSM48.st +++ /dev/null @@ -1,1368 +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 . -" -"Messages for GSM04.08" - -""" -IEs for GSM48MSG -""" - -IEBase subclass: GSM48IE [ - - - GSM48IE class >> ieMask [ - "Some IEs encode the IE and the value into one. Return the mask to be used - to determine the IE and see if it is matching." - ^ 16rFF - ] -] - -GSM48IE subclass: GSM48SimpleTag [ - | value | - - - - GSM48SimpleTag class >> ieMask [ ^ 16rF0 ] - GSM48SimpleTag class >> initWithData: aData [ - ^ self new - value: aData; - yourself - ] - - GSM48SimpleTag class >> length: aByteArray [ - ^ 0 - ] - - value: aValue [ - | inv | - inv := 255 - self class ieMask. - value := (aValue bitAnd: inv) - ] - - value [ - ^ value ifNil: [ 0 ] - ] - - writeOn: aMsg [ - | combined | - combined := self class elementId bitOr: value. - aMsg putByte: combined. - ] - - writeOnDirect: aMsg [ - self shouldNotImplement - ] -] - -GSM48IE subclass: GSM48DataHolder [ - | data | - - - GSM48DataHolder class >> createDefault [ - | size data | - size := self validSizes first. - data := ByteArray new: size. - ^ self new data: data; yourself. - ] - - GSM48DataHolder class >> validSizes [ ^ 1 to: 180 ] - - GSM48DataHolder class >> length: aByteArray [ - ^ (aByteArray at: 1) + 1. - ] - - GSM48DataHolder class >> initWithData: aData [ - ^ self new - data: aData; - yourself. - ] - - GSM48DataHolder class >> parseFrom: aData [ - | len | - len := aData at: 1. - ^ self initWithData: (aData copyFrom: 2 to: 2 + len - 1) - ] - - data: aData [ - | size | - "Add the size for the length header" - (self class validSizes includes: aData size + 1) - ifFalse: [ - ^ self error: 'The data is not of a valid size'. - ]. - - data := aData. - ] - - data [ ^ data ] - - writeOn: aMsg [ - aMsg putByte: self class elementId. - aMsg putByte: data size. - aMsg putByteArray: data. - ] - - writeOnDirect: aMsg [ - aMsg putByte: data size. - aMsg putByteArray: data. - ] -] - -GSM48IE subclass: GSM48SimpleData [ - | data | - - - - - 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 | - 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 [ - - - | val | - - GSM48KeySeqLuType class >> createDefault [ - - ^ (self new) - val: 16r70; - yourself - ] - - GSM48KeySeqLuType class >> length [ - "We always need a byte" - ^ 1 - ] - - val [ - ^ self data at: 1 - ] - - val: aVal [ - - self data: (ByteArray with: aVal). - ] -] - -GSM48IE subclass: GSM48Lai [ - | lai lac | - - GSM48Lai class >> createDefault [ - - ^ (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 [ lai mcc: aMcc ] - mnc: aMnc [ lai mnc: aMnc ] - lai: aLai [ lai := aLai ] - lac: aLac [ lac := aLac ] - - mcc [ ^ lai mcc ] - mnc [ ^ lai mnc ] - lac [ ^ lac ] - - writeOnDirect: aMsg [ - - lai writeOn: aMsg. - aMsg putLen16: lac. - ] -] - -GSM48IE subclass: GSM48Classmark1 [ - - | cm1 | - - GSM48Classmark1 class >> createDefault [ - - ^ (self new) - cm1: 16r33; - yourself - ] - - GSM48Classmark1 class >> length: aByteArray [ - ^ 1 - ] - - GSM48Classmark1 class >> parseFrom: aByteArray [ - ^ (self new) - cm1: (aByteArray at: 1); - yourself - ] - - cm1: aCm [ cm1 := aCm ] - cm1 [ ^ cm1 ] - - writeOnDirect: aMsg [ - - aMsg putByte: cm1. - ] -] - -GSM48DataHolder subclass: GSM48Classmark2 [ - "TODO: This is broken... it needs to be a simple data holder" - - - GSM48Classmark2 class >> createDefault [ - ^ self new - data: self defaultValue; - yourself - ] - - GSM48Classmark2 class >> defaultValue [ - ^ ByteArray with: 16r33 with: 16r19 with: 16rA2. - ] - - GSM48Classmark2 class >> validSizes [ ^ 4 to: 4 ] -] - -GSM48IE subclass: GSM48MIdentity [ - - | imsi tmsi | - - GSM48MIdentity class >> miIMSI [ ^ 16r1 ] - GSM48MIdentity class >> miIMEI [ ^ 16r2 ] - GSM48MIdentity class >> miIMEISV [ ^ 16r3 ] - GSM48MIdentity class >> miTMSI [ ^ 16r4 ] - - GSM48MIdentity class >> elementId [ ^ 23 ] - - GSM48MIdentity class >> createDefault [ - - ^ (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 [ imsi := aImsi. ] - imsi [ ^ imsi ] - - writeOnDirect: aMsg [ - - imsi ifNotNil: [ - ^ self storeImsiDirect: aMsg. - ]. - self notYetImplemented - ] - - storeImsiDirect: aMsg [ - | odd len head encoded bcds | - - - 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 [ - - ^ self new - cause: 11; - yourself. - ] - - GSM48RejectCause class >> length [ - ^ 1 - ] - - cause [ - ^ self data at: 1 - ] - - cause: aCause [ - self data: (ByteArray with: aCause). - ] -] - -GSM48SimpleData subclass: GSM48AuthRand [ - - - - GSM48AuthRand class >> length [ ^ 16 ] -] - -GSM48SimpleData subclass: GSM48AuthSRES [ - - - - GSM48AuthSRES class >> length [ ^ 4 ] -] - -GSM48SimpleTag subclass: GSM48FollowOn [ - - - - GSM48FollowOn class >> ieMask [ ^ 16rFF ] - GSM48FollowOn class >> elementId [ ^ 16rA1 ] -] - -GSM48SimpleTag subclass: GSM48CTSPermission [ - - - - GSM48CTSPermission class >> ieMask [ ^ 16rFF ] - GSM48CTSPermission class >> elementId [ ^ 16rA2 ] -] - -GSM48SimpleData subclass: GSM48IdentityType [ - - - "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 ] -] - -GSM48SimpleTag subclass: GSMRepeatInd [ - GSMRepeatInd class >> elementId [ ^ 16rD0 ] -] - -GSM48SimpleTag subclass: GSMPriorityLevel [ - GSMPriorityLevel class >> elementId [ ^ 16r80 ] -] - -GSM48DataHolder subclass: GSMBearerCap [ - GSMBearerCap class >> elementId [ ^ 16r04 ] - GSMBearerCap class >> validSizes [ ^ 1 to: 14 ] -] - -GSM48DataHolder subclass: GSMFacility [ - GSMFacility class >> elementId [ ^ 16r1C ] - GSMFacility class >> validSizes [ ^ 1 to: 254 ] -] - -GSM48DataHolder subclass: GSMProgress [ - GSMProgress class >> elementId [ ^ 16r1E ] - GSMProgress class >> validSizes [ ^ 3 to: 3 ] -] - -GSM48SimpleData subclass: GSMSignal [ - | signal | - GSMSignal class >> elementId [ ^ 16r34 ] - GSMSignal class >> length [ ^ 1 ] -] - -Object subclass: GSMNumberingPlan [ - - GSMNumberingPlan class >> planUnknown [ ^ 0 ] - GSMNumberingPlan class >> planISDN [ ^ 1 ] - GSMNumberingPlan class >> planData [ ^ 3 ] - GSMNumberingPlan class >> planTelex [ ^ 4 ] - GSMNumberingPlan class >> planNational [ ^ 8 ] - GSMNumberingPlan class >> planPrivate [ ^ 9 ] - GSMNumberingPlan class >> planReserved [ ^ 15 ] -] - -Object subclass: GSMNumberDigits [ - - DigitMap := nil. - ReverseMap := nil. - - GSMNumberDigits class >> mapDigit: aBinary [ - ^ self digitMap at: aBinary asInteger + 1. - ] - - GSMNumberDigits class >> digitMap: aDigit [ - ^ self reverseMap at: aDigit. - ] - - GSMNumberDigits class >> digitMap [ - ^ DigitMap ifNil: [ - DigitMap := Dictionary new. - 1 to: 10 do: [:each | - DigitMap at: each put: (each + 48 - 1) asCharacter. - ]. - - DigitMap at: 11 put: $*. - DigitMap at: 12 put: $#. - DigitMap at: 13 put: $a. - DigitMap at: 14 put: $b. - DigitMap at: 15 put: $c. - DigitMap at: 16 put: Character eof. - DigitMap yourself. - ]. - ] - - GSMNumberDigits class >> reverseMap [ - ^ ReverseMap ifNil: [ - ReverseMap := Dictionary new. - self digitMap associationsDo: [:each | - ReverseMap at: each value put: (each key - 1). - ]. - - ReverseMap yourself. - ]. - ] - - - - GSMNumberDigits class >> decodeFrom: anArray [ - | str | - - str := OrderedCollection new. - - 1 to: anArray size do: [:each | - | low high char | - low := (anArray at: each) bitAnd: 16r0F. - str add: (self mapDigit: low). - - high := ((anArray at: each) bitAnd: 16rF0) bitShift: -4. - char := (self mapDigit: high). - char = Character eof - ifFalse: [ - str add: char. - ]. - ]. - - ^ str asString - ] - - GSMNumberDigits class >> encodeFrom: aNumber [ - | digits res | - digits := OrderedCollection new. - - aNumber do: [:digit | - digits add: (self digitMap: digit). - ]. - - digits size odd - ifTrue: [ - digits add: 16rF. - ]. - - "Create the binary structure" - res := OrderedCollection new. - 1 to: digits size by: 2 do: [:each | - | low high | - low := digits at: each. - high := digits at: each + 1. - - res add: (low bitOr: (high bitShift: 4)). - ]. - - ^ res asByteArray. - ] -] - -GSM48DataHolder subclass: GSMCalledBCDNumber [ - GSMCalledBCDNumber class >> elementId [ ^ 16r5E ] - GSMCalledBCDNumber class >> validSizes [ ^ 2 to: 18 ] -] - -GSM48DataHolder subclass: GSMCalledSubBCDNumber [ - GSMCalledSubBCDNumber class >> elementId [ ^ 16r6D ] - GSMCalledSubBCDNumber class >> validSizes [ ^ 1 to: 22 ] -] - -GSM48DataHolder subclass: GSMCallingBCDNumber [ - GSMCallingBCDNumber class >> elementId [ ^ 16r5C ] - GSMCallingBCDNumber class >> validSizes [ ^ 2 to: 13 ] -] - -GSM48DataHolder subclass: GSMCallingSubBCDNumber [ - GSMCallingSubBCDNumber class >> elementId [ ^ 16r5D ] - GSMCallingSubBCDNumber class >> validSizes [ ^ 1 to: 22 ] -] - -GSM48DataHolder subclass: GSMRedirectingBCDNumber [ - GSMRedirectingBCDNumber class >> elementId [ ^ 16r74 ] - GSMRedirectingBCDNumber class >> validSizes [ ^ 2 to: 18 ] -] - -GSM48DataHolder subclass: GSMRedirectingSubBCDNumber [ - GSMRedirectingSubBCDNumber class >> elementId [ ^ 16r75 ] - GSMRedirectingSubBCDNumber class >> validSizes [ ^ 1 to: 22 ] -] - -GSM48DataHolder subclass: GSMLLCompability [ - GSMLLCompability class >> elementId [ ^ 16r7C ] - GSMLLCompability class >> validSizes [ ^ 1 to: 14 ] -] - -GSM48DataHolder subclass: GSMHLCompability [ - GSMHLCompability class >> elementId [ ^ 16r7D ] - GSMHLCompability class >> validSizes [ ^ 1 to: 4 ] -] -GSM48DataHolder subclass: GSMUserUser [ - GSMUserUser class >> elementId [ ^ 16r7E ] - GSMUserUser class >> validSizes [ ^ 2 to: 34 ] -] - -GSM48DataHolder subclass: GSMSSVersionInd [ - GSMSSVersionInd class >> elementId [ ^ 16r7F ] - GSMSSVersionInd class >> validSizes [ ^ 1 to: 2 ] -] - -GSM48SimpleTag subclass: GSMClirSuppression [ - GSMClirSuppression class >> elementId [ ^ 16rA1 ] - GSMClirSuppression class >> ieMask [ ^ 16rFF ] -] - -GSM48SimpleTag subclass: GSMClirInvocation [ - GSMClirInvocation class >> elementId [ ^ 16rA2 ] - GSMClirInvocation class >> ieMask [ ^ 16rFF ] -] - -GSM48DataHolder subclass: GSMCCCapabilities [ - "TODO: the length is fixed to three" - GSMCCCapabilities class >> elementId [ ^ 16r15 ] - GSMCCCapabilities class >> validSizes [ ^ 2 to: 2 ] -] - -GSM48DataHolder subclass: GSMConnectedNumber [ - - GSMConnectedNumber class >> elementId [ ^ 16r4C ] - GSMConnectedNumber class >> validSizes [ ^ 2 to: 13 ] -] - -GSM48DataHolder subclass: GSMConnectedSubNumber [ - - GSMConnectedSubNumber class >> elementId [ ^ 16r4D ] - GSMConnectedSubNumber class >> validSizes [ ^ 1 to: 22 ] -] - -GSM48DataHolder subclass: GSMAllowedActions [ - - GSMAllowedActions class >> elementId [ ^ 16r7B ] - GSMAllowedActions class >> validSizes [ ^ 2 to: 2 ] -] - -GSM48DataHolder subclass: GSM48Cause [ - - GSM48Cause class >> elementId [ ^ 16r8 ] - GSM48Cause class >> validSizes [ ^ 3 to: 31 ] -] - -GSM48DataHolder subclass: GSMAlertingPattern [ - GSMAlertingPattern class >> elementId [ ^ 16r19 ] - GSMAlertingPattern class >> validSizes [ ^ 3 to: 3 ] -] - -IEMessage subclass: GSM48MSG [ - | seq ti | - - - - GSM48MSG class >> addVariable: aName [ - "Check if the variable exists, otherwise add it" - (self instVarNames includes: aName) - ifFalse: [ - self addInstVarName: aName. - ]. - ] - - GSM48MSG class >> addMandantory: aName with: aClass [ - - self addVariable: aName asSymbol. - self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}. - self Mandantory add: (aName asSymbol -> aClass). - ] - - GSM48MSG class >> addOptional: aName with: aClass [ - - - aClass = nil - ifTrue: [ - self error: 'Class should not be null for ', aName - ]. - - self addVariable: aName asSymbol. - self compile: '%1 [ ^ %1 ]' % {aName}. - self compile: '%1OrDefault [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}. - self Optional add: (aName asSymbol -> aClass). - ] - - GSM48MSG class >> isCompatible: classType msgType: messageType [ - | localType | - - "Ignore the base classes. TODO: find a better way" - (self = GSM48MMMessage or: [self = GSM48CCMessage]) - ifTrue: [^ false]. - - localType := classType bitAnd: 16r0F. - ^ (self classType = localType) and: [self messageType = messageType]. - ] - - GSM48MSG class >> decode: aByteArray [ - | classType messageType | - classType := aByteArray at: 1. - 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). - res ti: ((aByteArray at: 1) bitShift: -4). - 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 | - - "We have consumed everything" - dat size = 0 - ifTrue: [ - ^ res - ]. - - tag := (dat at: 1) bitAnd: each value ieMask. - tag = each value elementId - ifTrue: [ - | len data | - data := dat copyFrom: 2. - len := each value length: data. - - "treat the T only tags specially" - len = 0 - ifTrue: [ - res instVarNamed: each key - put: (each value initWithData: (dat at: 1)). - dat := data. - ] - ifFalse: [ - res instVarNamed: each key - put: (each value parseFrom: data). - dat := data copyFrom: len + 1. - ]. - ]. - ]. - - "TODO: Complain if we have not consumed everything" - dat size = 0 - ifFalse: [ - res inspect. - dat printNl. - self error: 'Every byte should be consumed'. - ]. - - ^ res - ] - - writeOn: aMsg [ - | type classType | - - type := self seq bitShift: 6. - type := type bitOr: self class messageType. - - "Write the header. Skip Ind, Sequence are hardcoded" - classType := self ti bitShift: 4. - classType := classType bitOr: self class classType. - aMsg putByte: 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 ] - ] - - ti: aTi [ - ti := aTi. - ] - - ti [ - "by default treat it like a spare" - ^ 0 - ] -] - -GSM48MSG subclass: GSM48MMMessage [ - - - - GSM48MMMessage class >> classType [ ^ 16r5 ] - GSM48MMMessage class >> msgLUAcc [ ^ 16r02 ] - GSM48MMMessage class >> msgLURej [ ^ 16r04 ] - GSM48MMMessage class >> msgLUReq [ ^ 16r08 ] - GSM48MMMessage class >> msgIdRes [ ^ 16r19 ] - GSM48MMMessage class >> msgIdReq [ ^ 16r18 ] - GSM48MMMessage class >> msgAuReq [ ^ 16r12 ] - GSM48MMMessage class >> msgAuRes [ ^ 16r14 ] - GSM48MMMessage class >> msgCMAccept [ ^ 16r21 ] - GSM48MMMessage class >> msgCMReject [ ^ 16r22 ] - GSM48MMMessage class >> msgCMReq [ ^ 16r24 ] - GSM48MMMessage class >> msgIMSIDetach [ ^ 16r01 ] -] - -GSM48MSG subclass: GSM48CCMessage [ - - - - GSM48CCMessage class >> classType [ ^ 16r3 ] - - GSM48CCMessage class >> msgAlerting [ ^ 16r1 ] - GSM48CCMessage class >> msgProceeding [ ^ 16r2 ] - GSM48CCMessage class >> msgSetup [ ^ 16r5 ] - GSM48CCMessage class >> msgConnect [ ^ 16r7 ] - GSM48CCMessage class >> msgConnectAck [ ^ 16rF ] - GSM48CCMessage class >> msgDisconnect [ ^ 16r25 ] - GSM48CCMessage class >> msgReleaseCompl [ ^ 16r2A ] - GSM48CCMessage class >> msgRelease [ ^ 16r2D ] - - ti [ - ^ ti ifNil: [ 0 ] - ] -] - -GSM48MMMessage subclass: GSM48LURequest [ - - Mandantory := nil. - Optional := nil. - - GSM48LURequest class >> messageType [ ^ self msgLUReq ] - - GSM48LURequest class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48LURequest class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ]. - ] - - GSM48LURequest class >> initialize [ - self addMandantory: 'luType' with: GSM48KeySeqLuType. - self addMandantory: 'lai' with: GSM48Lai. - self addMandantory: 'cm1' with: GSM48Classmark1. - self addMandantory: 'mi' with: GSM48MIdentity. - ] -] - -GSM48MMMessage subclass: GSM48LUAccept [ - - Mandantory := nil. - Optional := nil. - - GSM48LUAccept class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48LUAccept class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ]. - ] - - GSM48LUAccept class >> messageType [ ^ self msgLUAcc ] - GSM48LUAccept class >> initialize [ - self addMandantory: 'cause' with: GSM48Lai. - self addOptional: 'mi' with: GSM48MIdentity. - self addOptional: 'follow' with: GSM48FollowOn. - self addOptional: 'cts' with: GSM48CTSPermission. - ] -] - -GSM48MMMessage subclass: GSM48LUReject [ - - Mandantory := nil. - Optional := nil. - - GSM48LUReject class >> messageType [ ^ self msgLURej ] - - GSM48LUReject class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48LUReject class >> initialize [ - self addMandantory: 'cause' with: GSM48RejectCause. - ] -] - -GSM48MMMessage subclass: GSM48AuthReq [ - - Mandantory := nil. - Optional := nil. - - GSM48AuthReq class >> messageType [ ^ self msgAuReq ] - GSM48AuthReq class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48AuthReq class >> initialize [ - self addMandantory: 'key' with: GSM48KeySeqLuType. - self addMandantory: 'auth' with: GSM48AuthRand. - ] -] - -GSM48MMMessage subclass: GSM48AuthResp [ - - Mandantory := nil. - - GSM48AuthResp class >> messageType [ ^ self msgAuRes ] - GSM48AuthResp class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48AuthResp class >> initialize [ - self addMandantory: 'sres' with: GSM48AuthSRES. - ] -] - -GSM48MMMessage subclass: GSM48IdentityReq [ - - - Mandantory := nil. - GSM48IdentityReq class >> messageType [ ^ self msgIdReq ] - GSM48IdentityReq class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48IdentityReq class >> initialize [ - self addMandantory: 'idType' with: GSM48IdentityType. - ] -] - -GSM48MMMessage subclass: GSM48IdentityResponse [ - - - Mandantory := nil. - GSM48IdentityResponse class >> messageType [ ^ self msgIdRes ] - GSM48IdentityResponse class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48IdentityResponse class >> initialize [ - self addMandantory: 'mi' with: GSM48MIdentity. - ] -] - -GSM48MMMessage subclass: GSM48CMServiceReq [ - - - Mandantory := nil. - Optional := nil. - - GSM48CMServiceReq class >> messageType [ ^ self msgCMReq ] - GSM48CMServiceReq class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - GSM48CMServiceReq class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CMServiceReq class >> initialize [ - self addMandantory: 'keyAndType' with: GSM48KeySeqLuType. - self addMandantory: 'cm2' with: GSM48Classmark2. - self addMandantory: 'mi' with: GSM48MIdentity. - - self addOptional: 'prio' with: GSMPriorityLevel. - ] - -] - -GSM48MMMessage subclass: GSM48CMServiceReject [ - - - Mandantory := nil. - GSM48CMServiceReject class >> messageType [ ^ self msgCMReject ] - GSM48CMServiceReject class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ] - ] - - GSM48CMServiceReject class >> initialize [ - self addMandantory: 'reject' with: GSM48RejectCause. - ] -] - -GSM48MMMessage subclass: GSM48IMSIDetachInd [ - - - Mandantory := nil. - GSM48IMSIDetachInd class >> messageType [ ^ self msgIMSIDetach ] - GSM48IMSIDetachInd class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - - GSM48IMSIDetachInd class >> initialize [ - self addMandantory: 'cm1' with: GSM48Classmark1. - self addMandantory: 'mi' with: GSM48MIdentity. - ] -] - -GSM48CCMessage subclass: GSM48CCSetup [ - - - Mandantory := nil. - Optional := nil. - - GSM48CCSetup class >> messageType [ ^ self msgSetup ] - GSM48CCSetup class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]. - ] - GSM48CCSetup class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CCSetup class >> initialize [ - self addOptional: 'repeatInd' with: GSMRepeatInd. - self addOptional: 'bearer1' with: GSMBearerCap. - self addOptional: 'bearer2' with: GSMBearerCap. - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'progress' with: GSMProgress. - self addOptional: 'signal' with: GSMSignal. - self addOptional: 'calling' with: GSMCallingBCDNumber. - self addOptional: 'callingSub' with: GSMCallingSubBCDNumber. - self addOptional: 'called' with: GSMCalledBCDNumber. - self addOptional: 'calledSub' with: GSMCalledSubBCDNumber. - self addOptional: 'redirect' with: GSMRedirectingBCDNumber. - self addOptional: 'redirectSub' with: GSMRedirectingSubBCDNumber. - self addOptional: 'LLCInd' with: GSMRepeatInd. - self addOptional: 'llc1' with: GSMLLCompability. - self addOptional: 'llc2' with: GSMLLCompability. - self addOptional: 'HLCInd' with: GSMRepeatInd. - self addOptional: 'hlc1' with: GSMHLCompability. - self addOptional: 'hlc2' with: GSMHLCompability. - self addOptional: 'useruser' with: GSMUserUser. - "For MO call" - self addOptional: 'ssVersion' with: GSMSSVersionInd. - self addOptional: 'clirSuppr' with: GSMClirSuppression. - self addOptional: 'clirInvoc' with: GSMClirInvocation. - self addOptional: 'ccCapabil' with: GSMCCCapabilities. - self addOptional: 'facilityCCBS' with: GSMFacility. - self addOptional: 'facilityReca' with: GSMFacility. - - "For MT call" - self addOptional: 'prio' with: GSMPriorityLevel. - self addOptional: 'alert' with: GSMAlertingPattern. - ] - - writeOn: aMsg [ - "TODO: these are incomplete and wrong" - "Implement the conditionals" - (self bearer1 ~= nil and: [self bearer2 ~= nil]) - ifTrue: [ - self instVarNamed: #repeatInd put: GSMRepeatInd new. - ] - ifFalse: [ - self instVarNamed: #repeatInd put: nil. - ]. - - (self llc1 ~= nil and: [self llc2 ~= nil]) - ifTrue: [ - self instVarNamed: #LLCInd put: GSMRepeatInd new. - ] - ifFalse: [ - self instVarNamed: #LLCInd put: nil. - ]. - - (self hlc1 ~= nil and: [self hlc2 ~= nil]) - ifTrue: [ - self instVarNamed: #HLCInd put: GSMRepeatInd new. - ] - ifFalse: [ - self instVarNamed: #HLCInd put: nil. - ]. - - ^ super writeOn: aMsg. - ] -] - -GSM48CCMessage subclass: GSM48CCProceeding [ - - - Mandantory := nil. - Optional := nil. - - GSM48CCProceeding class >> messageType [ ^ self msgProceeding ] - GSM48CCProceeding class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ] - ] - GSM48CCProceeding class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CCProceeding class >> initialize [ - self addOptional: 'repeatInd' with: GSMRepeatInd. - self addOptional: 'bearer1' with: GSMBearerCap. - self addOptional: 'bearer2' with: GSMBearerCap. - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'progress' with: GSMProgress. - self addOptional: 'priorityGranted' with: GSMPriorityLevel. - ] - - writeOn: aMsg [ - (self bearer1 ~= nil and: [self bearer2 ~= nil]) - ifTrue: [ - self instVarNamed: #repeatInd put: GSMRepeatInd new. - ] - ifFalse: [ - self instVarNamed: #repeatInd put: nil. - ]. - - ^ super writeOn: aMsg. - ] -] - -GSM48CCMessage subclass: GSM48CCAlerting [ - - Mandantory := nil. - Optional := nil. - - GSM48CCAlerting class >> messageType [ ^ self msgAlerting ] - GSM48CCAlerting class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ] - ] - - GSM48CCAlerting class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CCAlerting class >> initialize [ - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'progress' with: GSMProgress. - self addOptional: 'useruser' with: GSMUserUser. - - "mobile station to network" - self addOptional: 'ssVersion' with: GSMSSVersionInd. - ] -] - -GSM48CCMessage subclass: GSM48CCConnect [ - - - Mandantory := nil. - Optional := nil. - - GSM48CCConnect class >> messageType [ ^ self msgConnect ] - GSM48CCConnect class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ] - ] - - GSM48CCConnect class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new. ] - ] - - GSM48CCConnect class >> initialize [ - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'progress' with: GSMProgress. - self addOptional: 'connected' with: GSMConnectedNumber. - self addOptional: 'connectedSub' with: GSMConnectedSubNumber. - self addOptional: 'useruser' with: GSMUserUser. - self addOptional: 'ssVersion' with: GSMSSVersionInd. - ] -] - -GSM48CCMessage subclass: GSM48CCConnectAck [ - - - Optional := nil. - Mandantory := nil. - - GSM48CCConnectAck class >> messageType [ ^ self msgConnectAck ] - GSM48CCConnectAck class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ] - ] - - GSM48CCConnectAck class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new. ] - ] - - GSM48CCConnectAck class >> initialize [ - ] -] - -GSM48CCMessage subclass: GSM48CCDisconnect [ - - - Optional := nil. - Mandantory := nil. - - GSM48CCDisconnect class >> messageType [ ^ self msgDisconnect ] - GSM48CCDisconnect class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ] - ] - - GSM48CCDisconnect class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new. ] - ] - - GSM48CCDisconnect class >> initialize [ - self addMandantory: 'cause' with: GSM48Cause. - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'progress' with: GSMProgress. - self addOptional: 'useruser' with: GSMUserUser. - self addOptional: 'allowedActions' with: GSMAllowedActions. - - "MO addition" - self addOptional: 'ssVersion' with: GSMSSVersionInd. - ] - -] - -GSM48CCMessage subclass: GSM48CCRelease [ - - - Optional := nil. - Mandantory := nil. - - GSM48CCRelease class >> messageType [ ^ self msgRelease ] - GSM48CCRelease class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ] - ] - - GSM48CCRelease class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CCRelease class >> initialize [ - self addOptional: 'cause' with: GSM48Cause. - self addOptional: 'secondCause' with: GSM48Cause. - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'useruser' with: GSMUserUser. - self addOptional: 'ssVersion' with: GSMSSVersionInd. - ] -] - -GSM48CCMessage subclass: GSM48CCReleaseCompl [ - - - Optional := nil. - Mandantory := nil. - - GSM48CCReleaseCompl class >> messageType [ ^ self msgReleaseCompl ] - GSM48CCReleaseCompl class >> Mandantory [ - ^ Mandantory ifNil: [ Mandantory := OrderedCollection new ] - ] - - GSM48CCReleaseCompl class >> Optional [ - ^ Optional ifNil: [ Optional := OrderedCollection new ] - ] - - GSM48CCReleaseCompl class >> initialize [ - self addOptional: 'cause' with: GSM48Cause. - self addOptional: 'facility' with: GSMFacility. - self addOptional: 'useruser' with: GSMUserUser. - self addOptional: 'ssVersion' with: GSMSSVersionInd. - ] -] - -Eval [ - GSM48LURequest initialize. - GSM48LUReject initialize. - GSM48LUAccept initialize. - GSM48AuthReq initialize. - GSM48AuthResp initialize. - GSM48IdentityReq initialize. - GSM48IdentityResponse initialize. - GSM48CMServiceReq initialize. - GSM48CMServiceReject initialize. - GSM48IMSIDetachInd initialize. - - GSM48CCSetup initialize. - GSM48CCProceeding initialize. - GSM48CCAlerting initialize. - GSM48CCConnect initialize. - GSM48CCConnectAck initialize. - GSM48CCDisconnect initialize. - GSM48CCRelease initialize. - GSM48CCReleaseCompl initialize. -] diff --git a/GSMDriver.st b/GSMDriver.st index 531cff0..9b5085b 100644 --- a/GSMDriver.st +++ b/GSMDriver.st @@ -22,6 +22,7 @@ Object subclass: GSMDriver [ + GSMDriver class >> new [ @@ -207,6 +208,8 @@ classes.'> Object subclass: ProcedureBase [ | driver conn success | + + ProcedureBase class >> initWith: aHandler phone: aPhone [ ^ self new createConnection: aHandler phone: aPhone; diff --git a/Messages.st b/Messages.st deleted file mode 100644 index 5433cd1..0000000 --- a/Messages.st +++ /dev/null @@ -1,171 +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 . -" -"General IE based message handling" - -Object subclass: IEBase [ - - - type [ - "Go through the elementId of the class" - ^ self class elementId - ] - - writeOnDirect: aMsg [ - "This should be implemented by the subclass" - self subclassResponsibility - ] - - writeOn: aMsg [ - aMsg putByte: self class elementId. - self writeOnDirect: aMsg. - ] -] - -Object subclass: IEMessage [ - - | ies type | - - IEMessage class >> initWith: type [ - - ^ (self new) - type: type; - yourself - ] - - IEMessage class >> findIE: data from: aIEBase on: aMsg [ - "TODO: This needs to move some basic dispatch class" - "Find the IE that handles the type specified" - | type | - type := data at: 1. - - aIEBase allSubclassesDo: [:each | - each elementId = type - ifTrue: [ - | enc size | - size := each length: data. - enc := data copyFrom: 1 to: 1 + size. - aMsg addIe: (each parseFrom: enc). - ^ 1 + size - ]. - ]. - - ^ Exception signal: 'Unsupported IE type: ', type asString. - ] - - IEMessage class >> decode: aByteArray with: aIEBase [ - | msg dat | - msg := IEMessage initWith: (aByteArray at: 1). - - dat := aByteArray copyFrom: 2. - [dat isEmpty not] whileTrue: [ - | consumed | - consumed := self findIE: dat from: aIEBase on: msg. - dat := dat copyFrom: consumed + 1. - ]. - - ^ msg - ] - - type: aType [ - - type := aType. - ] - - type [ - ^ type - ] - - addIe: aIe [ - - self ies add: aIe. - ] - - ies [ - - ies isNil ifTrue: [ - ies := OrderedCollection new. - ]. - - ^ ies - ] - - findIE: type ifAbsent: block [ - "Find the IE with the type" - self ies do: [:each | - each type = type - ifTrue: [ - ^ each - ]. - ]. - - ^ block value. - ] - - findIE: type ifPresent: block [ - "Find the IE with the type" - self ies do: [:each | - each type = type - ifTrue: [ - ^ block value: each - ]. - ]. - - ^ nil. - ] - - writeOn: aMsg [ - - aMsg putByte: type. - - self ies do: [:each | each writeOn: 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 - ] - - BCD class >> decode: aByteArray [ - - | num cum | - - num := 0. - cum := 1. - aByteArray size to: 1 by: -1 do: [:each | - | at | - num := num + ((aByteArray at: each) * cum). - cum := cum * 10. - ]. - - ^ num - ] -] - diff --git a/SCCPHandler.st b/SCCPHandler.st deleted file mode 100644 index 94960f3..0000000 --- a/SCCPHandler.st +++ /dev/null @@ -1,305 +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 . -" - -PackageLoader fileInPackage: 'OsmoNetwork'. - -Object subclass: SCCPConnection [ - | src dst queue conManager confirmSem proc state | - - SCCPConnection class >> stateInitial [ ^ 0 ] - SCCPConnection class >> stateConnected [ ^ 1 ] - SCCPConnection class >> stateReleased [ ^ 2 ] - SCCPConnection class >> stateTimeout [ ^ 3 ] - - SCCPConnection class >> new [ - ^ super new - initialize; yourself - ] - - initialize [ - state := SCCPConnection stateInitial. - confirmSem := Semaphore new. - queue := SharedQueue new. - ] - - conManager: aHandler [ - - conManager := aHandler. - ] - - readQueue [ - - ^ queue - ] - - srcRef [ - - ^ src - ] - srcRef: aRef [ - - src := aRef - ] - - dstRef: aRef [ - - dst := aRef - ] - - dstRef [ - - ^ dst - ] - - next [ - "Read the next item. If the connection is terminated" - | msg | - - "If we are not connected we need to wait" - state = SCCPConnection stateInitial - ifTrue: [ - self waitForConfirmation. - ]. - - "If we are not connected here. Send a EndOfStream signal" - state = SCCPConnection stateConnected - ifFalse: [ - ^ SystemExceptions.EndOfStream signal - ]. - - msg := self readQueue next. - - "If this is a small integer our connection is gone" - (msg isKindOf: SmallInteger) - ifTrue: [ - ^ SystemExceptions.EndOfStream signal - ]. - - "We do have a real message" - ^ msg - ] - - nextPutData: aMsg [ - | dt1 | - dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg. - self nextPut: dt1 toMessage. - ] - - nextPut: aMsg [ - conManager sendMsg: aMsg. - ] - - waitForConfirmation [ - "Wait for the connection to be confirmed and then exit" - - ((Delay forSeconds: 10) timedWaitOn: confirmSem) - ifTrue: [ - state := SCCPConnection stateTimeout. - conManager connectionTimeout: self. - ^ false - ]. - - ^ true - ] - - - "SCCP Connection state handling" - terminate [ - self readQueue nextPut: 0. - ] - - confirm: aCC [ - - self dstRef: aCC src. - state := SCCPConnection stateConnected. - confirmSem signal. - ] - - data: aDT [ - self readQueue nextPut: aDT data. - ] - - released: aRLSD [ - | rlc | - "Give up local resources here. We are done." - - state := SCCPConnection stateReleased. - rlc := Osmo.SCCPConnectionReleaseComplete - initWithDst: aRLSD src src: aRLSD dst. - self nextPut: rlc toMessage. - self terminate. - ] -] - -Object subclass: MSGParser [ - - - MSGParser class >> parse: aByteArray [ - | sccp | - "Return a completely decoded subtree" - - sccp := Osmo.SCCPMessage decode: aByteArray. - (sccp respondsTo: #data) - ifTrue: [ - sccp data: (self decodeBSSAP: sccp data). - ]. - - ^ sccp - ] - - MSGParser class >> decodeBSSAP: aData [ - | bssap | - bssap := BSSAPMessage decode: aData. - bssap class msgType = BSSAPDTAP msgType - ifTrue: [ - bssap data: (GSM48MSG decode: bssap data) - ] - ifFalse: [ - bssap data: (self decodeBSSMAP: bssap data). - ]. - - ^ bssap - ] - - MSGParser class >> decodeBSSMAP: aData [ - | bssmap | - bssmap := IEMessage decode: aData with: GSM0808IE. - bssmap findIE: (GSMLayer3Info elementId) ifPresent: [:each | - each data: (GSM48MSG decode: each data). - ]. - ^ bssmap - ] - -] - -Object subclass: SCCPHandler [ - | connections last_ref connection | - - - registerOn: aDispatcher [ - aDispatcher addHandler: Osmo.IPAConstants protocolSCCP - on: self with: #handleMsg:. - ] - - connectionTimeout: aConnection [ - ('SCCP Connection ', aConnection srcRef asString, ' timeout.') printNl. - self connections remove: aConnection. - ] - - forwardMessage: aMessage with: aConnection[ - (aMessage isKindOf: Osmo.SCCPConnectionConfirm) - ifTrue: [ - aConnection confirm: aMessage. - ^ true - ]. - (aMessage isKindOf: Osmo.SCCPConnectionData) - ifTrue: [ - aConnection data: aMessage. - ^ true - ]. - (aMessage isKindOf: Osmo.SCCPConnectionReleased) - ifTrue: [ - aConnection released: aMessage. - self connections remove: aConnection. - ^ true - ]. - - "Message is not handled here" - ^ false - ] - - dispatchMessage: aMessage [ - self connections do: [:each | - each srcRef = aMessage dst - ifTrue: [ - ^ self forwardMessage: aMessage with: each. - ]. - ]. - - 'No one has handled the connection with ', aMessage dst asString printNl. - ] - - handleMsg: aMsg [ - | sccp | - - [ - sccp := MSGParser parse: (aMsg asByteArray). - ] on: Exception do: [ - self logError: 'Failed to parse message' area: #sccp. - aMsg asByteArray printNl. - ^ false - ]. - - self dispatchMessage: sccp. - ] - - - connection: aConnection [ - connection := aConnection. - ] - - sendMsg: aMsg [ - "Send a SCCP message." - connection send: aMsg with: Osmo.IPAConstants protocolSCCP. - ] - - createConnection: aData [ - | con res| - - con := SCCPConnection new. - con srcRef: self assignSrcRef. - con conManager: self. - res := Osmo.SCCPConnectionRequest - initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData. - self connections add: con. - self sendMsg: res toMessage. - - ^ con - ] - - referenceIsFree: aRef [ - - self connections do: [:each | - each srcRef = aRef - ifTrue: [ - ^ false - ]. - ]. - - ^ true - ] - - assignSrcRef [ - "Find a free SCCP reference" - 1 to: 16rFFFFFE do: [:dummy | - | ref | - ref := Random between: 1 and: 16rFFFFFE. - (self referenceIsFree: ref) - ifTrue: [ - ^ ref. - ]. - ]. - - self error: 'No free SCCP Connection. Close some'. - ] - - connections [ - ^ connections ifNil: [ connections := OrderedCollection new. ] - ] -] - diff --git a/TestPhone.st b/TestPhone.st index 4bb3106..8dd044f 100644 --- a/TestPhone.st +++ b/TestPhone.st @@ -20,6 +20,8 @@ PackageLoader fileInPackage: 'OsmoNetwork'. Object subclass: IPAConnection [ | socket demuxer queue muxer dispatcher sccp ipa sem | + + IPAConnection class >> initWith: anAddr port: aPort token: aToken [ ^ (self new) socket: (Sockets.Socket remote: anAddr port: aPort); diff --git a/Tests.st b/Tests.st deleted file mode 100644 index ac434b2..0000000 --- a/Tests.st +++ /dev/null @@ -1,428 +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 . -" - -TestCase subclass: GSM0808Test [ - testLAI [ - | lai res | - res := #(16r72 16rF4 16r80) asByteArray. - lai := LAI generateLAI: 274 mnc: 8. - - self assert: lai = res. - ] - - testCellIE [ - | ie res msg | - - res := #(5 8 0 114 244 128 32 18 117 48) asByteArray. - msg := Osmo.MessageBuffer new. - - ie := GSMCellIdentifier initWith: 274 mnc: 8 lac: 8210 ci: 30000. - ie writeOn: msg. - - self assert: msg asByteArray = res. - - ie := GSMCellIdentifier parseFrom: res. - self assert: ie mcc = 274. - self assert: ie mnc = 8. - self assert: ie lac = 8210. - self assert: ie ci = 30000. - ] - - testLayer3IE [ - | ie res msg | - - res := #(23 3 1 2 3) asByteArray. - msg := Osmo.MessageBuffer new. - ie := GSMLayer3Info initWith: #(1 2 3) asByteArray. - ie writeOn: msg. - - self assert: msg asByteArray = res. - - ie := GSMLayer3Info parseFrom: res. - self assert: ie data = #(1 2 3) asByteArray. - ] - - testComplL3 [ - | msg buf ie res | - msg := IEMessage initWith: GSM0808Helper msgComplL3. - - msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 8210 ci: 30000). - msg addIe: (GSMLayer3Info initWith: #(1 2 3) asByteArray). - - buf := Osmo.MessageBuffer new. - msg writeOn: buf. - - res := #(16r57 16r05 16r08 16r00 16r72 16rF4 16r80 16r20 16r12 - 16r75 16r30 16r17 16r03 16r01 16r02 16r03) asByteArray. - self assert: buf asByteArray = res - ] - - testCuaseIE [ - | buf ie res | - res := #(4 1 32) asByteArray. - - ie := GSMCauseIE initWith: 32. - buf := ie toMessage asByteArray. - self assert: buf = res. - - ie := GSMCauseIE parseFrom: res. - self assert: ie cause = 32. - ] - - testIEDecoding [ - | inp res | - inp := #(16r57 16r05 16r08 16r00 16r72 16rF4 16r80 16r20 16r12 - 16r75 16r30 16r17 16r03 16r01 16r02 16r03) asByteArray. - - res := IEMessage decode: inp with: GSM0808IE. - self assert: res type = GSM0808Helper msgComplL3. - self assert: res ies size = 2. - ] -] - -TestCase subclass: BSSAPTest [ - testPrependManagment [ - | msg | - msg := Osmo.MessageBuffer new. - msg putByteArray: #(1 2 3) asByteArray. - - BSSAPHelper prependManagement: msg. - self assert: msg asByteArray = #(0 3 1 2 3) asByteArray. - ] - - testManagment [ - | man | - - man := BSSAPManagement initWith: #(1 2 3) asByteArray. - self assert: man toMessage asByteArray = #(0 3 1 2 3) asByteArray. - ] - - testParseManagement [ - | man | - - man := BSSAPMessage decode: #(0 3 1 2 3) asByteArray. - self assert: (man isKindOf: BSSAPManagement). - self assert: man data = #(1 2 3) asByteArray. - ] - - testPrependDTAP [ - | msg | - msg := Osmo.MessageBuffer new. - msg putByteArray: #(1 2 3) asByteArray. - - BSSAPHelper prependDTAP: msg dlci: 0. - self assert: msg asByteArray = #(1 0 3 1 2 3) asByteArray. - ] -] - -TestCase subclass: GSM48Test [ - testKeySeqLu [ - | gsm msg res | - res := #(16r70) asByteArray. - msg := Osmo.MessageBuffer new. - gsm := GSM48KeySeqLuType createDefault. - gsm writeOnDirect: msg. - - self assert: msg asByteArray = res. - - self assert: (GSM48KeySeqLuType length: res) = 1. - gsm := GSM48KeySeqLuType parseFrom: res. - self assert: gsm val = 16r70. - ] - - testLai [ - | gsm msg res | - res := #(16r02 16rF2 16r50 16rFF 16rFE) asByteArray. - msg := Osmo.MessageBuffer new. - gsm := GSM48Lai createDefault. - gsm mcc: 202; mnc: 5; lac: 65534. - gsm writeOnDirect: msg. - - self assert: msg asByteArray = res. - - self assert: (GSM48Lai length: res) = res size. - gsm := GSM48Lai parseFrom: res. - self assert: gsm mcc = 202. - self assert: gsm mnc = 5. - self assert: gsm lac = 65534. - ] - - testCM1 [ - | gsm msg res | - res := #(16r33) asByteArray. - msg := Osmo.MessageBuffer new. - gsm := GSM48Classmark1 createDefault. - gsm writeOnDirect: msg. - - self assert: msg asByteArray = res. - - self assert: (GSM48Classmark1 length: res) = res size. - gsm := GSM48Classmark1 parseFrom: res. - self assert: gsm cm1 = 16r33. - ] - - testMI [ - | gsm msg res imsi | - res := #(8 41 71 128 0 0 0 116 8) asByteArray. - imsi := '274080000004780'. - - msg := Osmo.MessageBuffer new. - gsm := GSM48MIdentity createDefault. - gsm imsi: imsi. - gsm writeOnDirect: msg. - - self assert: msg asByteArray = res. - - self assert: (GSM48MIdentity length: res) = res size. - gsm := GSM48MIdentity parseFrom: res. - self assert: gsm imsi = imsi. - ] - - testRejectCause [ - | rej msg target | - target := #(11) asByteArray. - - msg := Osmo.MessageBuffer new. - rej := GSM48RejectCause createDefault. - rej writeOnDirect: msg. - self assert: msg asByteArray = target. - - self assert: (GSM48RejectCause length: target) = 1. - rej := GSM48RejectCause parseFrom: target. - self assert: rej cause = 11. - ] - - testLU [ - | gsm msg res | - - res := #(5 8 112 2 242 80 255 254 51 8 105 102 1 69 0 114 131 136) asByteArray. - msg := Osmo.MessageBuffer new. - gsm := GSM48LURequest new. - (gsm lai) mcc: 202; mnc: 5; lac: 65534. - (gsm mi) imsi: '666105400273888'. - gsm writeOn: msg. - - self assert: msg asByteArray = res - ] - - testNumberDecode [ - | number res | - number := #(73 132 50 23 120). - res := GSMNumberDigits decodeFrom: number. - self assert: res = '9448237187'. - - number := #(73 132 50 23 120 186 220 174). - res := GSMNumberDigits decodeFrom: number. - self assert: res = '9448237187*#abc*'. - ] - - testNumberEncode [ - | res | - res := GSMNumberDigits encodeFrom: '9448237187*#abc*'. - self assert: res = #(73 132 50 23 120 186 220 174) asByteArray. - ] -] - -SCCPHandler subclass: TestSCCPHandler [ - assignSrcRef [ - ^ 666 - ] -] - -TestCase subclass: TestMessages [ - testMsgParser [ - | msg bssap bssmap ies l3 gsm48 inp | - - inp := #(1 154 2 0 2 2 4 2 66 254 15 32 0 30 87 - 5 8 0 114 244 128 16 3 156 64 23 17 5 8 - 112 0 240 0 0 0 51 7 97 102 102 102 102 - 102 246 0 ) asByteArray. - msg := MSGParser parse: inp. - self assert: (msg isKindOf: Osmo.SCCPConnectionRequest). - - bssap := msg data. - self assert: (bssap isKindOf: BSSAPManagement). - - bssmap := bssap data. - self assert: (bssmap isKindOf: IEMessage). - - ies := bssmap ies. - self assert: ies size = 2. - - l3 := bssmap findIE: (GSMLayer3Info elementId) ifAbsent: [ - self assert: false. - ]. - - self assert: (l3 isKindOf: GSMLayer3Info). - - gsm48 := l3 data. - self assert: (gsm48 isKindOf: GSM48LURequest). - - self assert: gsm48 mi imsi = '666666666666'. - - self assert: msg toMessage asByteArray = inp. - ] - - testMsgParserDt1 [ - | inp msg bssap gsm48 | - inp := #(6 154 2 0 0 1 6 1 0 3 5 4 11 ) asByteArray. - - msg := MSGParser parse: inp. - self assert: (msg isKindOf: Osmo.SCCPConnectionData). - - bssap := msg data. - self assert: (bssap isKindOf: BSSAPDTAP). - - gsm48 := bssap data. - self assert: (gsm48 isKindOf: GSM48LUReject). - - self assert: msg toMessage asByteArray = inp. - ] - - testMsgparserDt1Clear [ - | inp msg bssap bssmap | - inp := #(6 154 2 0 0 1 6 0 4 32 4 1 32) asByteArray. - msg := MSGParser parse: inp. - self assert: (msg isKindOf: Osmo.SCCPConnectionData). - - bssap := msg data. - self assert: (bssap isKindOf: BSSAPManagement). - - bssmap := bssap data. - self assert: (bssmap isKindOf: IEMessage). - - self assert: msg toMessage asByteArray = inp. - ] - - testRandomMessages [ - | inp msg | - "This only tests some parsing... it does not verify the content" - - inp := #(6 1 8 101 0 1 3 0 1 33 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - inp := #(6 48 4 5 0 1 22 1 0 19 5 18 1 83 3 123 16 155 119 176 138 215 28 107 26 47 193 59 248 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - inp := #(6 1 8 104 0 1 9 1 0 6 5 84 253 230 198 47) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - inp := #(6 46 4 5 0 1 20 1 0 17 5 2 114 244 128 16 3 23 8 41 34 1 96 16 85 37 115) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - - "Identity Request" - inp := #(16r06 16r3A 16r04 16r05 16r00 16r01 16r06 16r01 16r00 16r03 16r05 16r18 16r01) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Identity Response" - inp := #(16r06 16r01 16r08 16r76 16r00 16r01 16r0E 16r01 16r00 16r0B 16r05 16r59 16r08 16r29 16r20 16r10 16r31 16r61 16r35 16r45 16r06) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "CM Service Request" - inp := #(1 205 4 5 2 2 4 2 66 254 15 33 0 31 87 5 8 0 114 244 128 16 3 156 64 23 16 5 36 17 3 51 25 129 8 41 32 1 153 118 6 1 152 33 1 0) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "IMSI Detach Ind" - inp := #(1 255 4 5 2 2 4 2 66 254 15 29 0 27 87 5 8 0 114 244 128 16 3 156 64 23 12 5 1 51 8 41 65 112 6 16 9 71 34 33 1 0 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "BSSMAP paging" - inp := #(16r09 16r00 16r03 16r07 16r0B 16r04 16r43 16r07 16r00 16rFE 16r04 16r43 16r5C 16r00 16rFE 16r12 16r00 16r10 16r52 16r08 16r08 16r29 16r22 16r88 16r81 16r04 16r56 16r44 16r24 16r1A 16r03 16r05 16r10 16r03) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Ciphermode Command" - inp := #(6 0 0 72 0 1 14 0 12 83 10 9 3 8 90 152 155 24 30 20 226 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Ciphermode Complete" - inp := #(16r06 16r01 16r03 16r23 16r00 16r01 16r05 16r00 16r03 16r55 16r2C 16r02) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Assignment Command" - inp := #(6 0 0 72 0 1 11 0 9 1 11 3 1 10 17 1 0 20 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Assignment Complete" - inp := #(6 1 3 35 0 1 11 0 9 2 21 0 33 152 44 2 64 17) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Classmark update" - inp := #(6 1 3 35 0 1 16 0 14 84 18 3 51 25 145 19 6 96 20 69 0 1 0) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "MO Setup message" - inp := #(6 1 3 35 0 1 21 1 128 18 3 69 4 6 96 4 2 0 5 129 94 6 145 83 132 54 23 121 ) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "MO Proceeding" - inp := #(6 0 0 72 0 1 5 1 0 2 131 2) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Alerting" - inp := #(6 0 0 72 0 1 9 1 0 6 131 1 30 2 234 129) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Connect" - inp := #(6 0 0 72 0 1 5 1 0 2 131 7) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Connct acknowledge" - inp := #(6 1 3 35 0 1 5 1 128 2 3 15) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Disconnect" - inp := #(6 0 0 72 0 1 8 1 0 5 131 37 2 225 144) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Release" - inp := #(6 1 3 35 0 1 5 1 128 2 3 109) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "Release Complete" - inp := #(6 0 0 72 0 1 9 1 0 6 131 42 8 2 225 144) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - - "CM Service Reject" - inp := #(6 0 103 68 0 1 6 1 0 3 5 34 11) asByteArray. - msg := MSGParser parse: inp. - self assert: msg toMessage asByteArray = inp. - ] -] diff --git a/WebApp.st b/WebApp.st index 716e97b..3633f33 100644 --- a/WebApp.st +++ b/WebApp.st @@ -21,12 +21,7 @@ PackageLoader fileInPackage: 'Iliad-More-Comet'. PackageLoader fileInPackage: 'Iliad-More-Formula'. PackageLoader fileInPackage: 'Iliad-Swazoo'. -FileStream fileIn: 'A3A8.st'. -FileStream fileIn: 'Messages.st'. -FileStream fileIn: 'BSSAP.st'. -FileStream fileIn: 'BSSMAP.st'. -FileStream fileIn: 'GSM48.st'. -FileStream fileIn: 'SCCPHandler.st'. +PackageLoader fileInPackage: 'OsmoGSM'. FileStream fileIn: 'GSMDriver.st'. FileStream fileIn: 'TestPhone.st'. diff --git a/package.xml b/package.xml index 15274a5..7944ab9 100644 --- a/package.xml +++ b/package.xml @@ -3,29 +3,11 @@ OsmoTestPhone OsmoNetwork OsmoLogging + OsmoGSM - Messages.st - BSSAP.st - BSSMAP.st - GSM48.st - SCCPHandler.st GSMDriver.st TestPhone.st - - OsmoTestPhone.GSM0808Test - OsmoTestPhone.BSSAPTest - OsmoTestPhone.GSM48Test - OsmoTestPhone.TestMessages - Tests.st - - - BSSAP.st - BSSMAP.st - Messages.st - SCCPHandler.st - GSM48.st GSMDriver.st TestPhone.st - Tests.st