1
0
Fork 0

GSM: Moved all classes to the osmo-network module

This commit is contained in:
Holger Hans Peter Freyther 2010-12-15 12:36:17 +01:00
parent 1b56da9dfb
commit 716e4ac30c
11 changed files with 7 additions and 3132 deletions

49
A3A8.st
View File

@ -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 <http://www.gnu.org/licenses/>.
"
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 [
<cCall: 'COMP128_3' returning: #void args: #(#string #string #cObject)>
]
]
Eval [
A3A8 initialize.
]

149
BSSAP.st
View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: BSSAPHelper [
<category: 'osmo-message'>
<comment: 'BSSAP message routines'>
BSSAPHelper class >> msgManagemnt [ <category: 'spec'> ^ 0 ]
BSSAPHelper class >> msgDtap [ <category: 'spec'> ^ 1 ]
BSSAPHelper class >> prependManagement: aMsg [
<category: 'creation'>
"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 [
<category: 'creation'>
"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 [ <category: 'factory'> ^ 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 [ <category: 'factory'> ^ 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.
]
]

637
BSSMAP.st
View File

@ -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.
]
]

1368
GSM48.st

File diff suppressed because it is too large Load Diff

View File

@ -22,6 +22,7 @@ Object subclass: GSMDriver [
<comment: 'I create a SCCP connection and handle stuff on it. In the base class
I am just capable of handling BSSMAP Management and need to dispatch it to other
classes.'>
<import: OsmoGSM>
GSMDriver class >> new [
<category: 'private'>
@ -207,6 +208,8 @@ classes.'>
Object subclass: ProcedureBase [
| driver conn success |
<import: OsmoGSM>
ProcedureBase class >> initWith: aHandler phone: aPhone [
^ self new
createConnection: aHandler phone: aPhone;

View File

@ -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 <http://www.gnu.org/licenses/>.
"
"General IE based message handling"
Object subclass: IEBase [
<comment: 'I am a base for IE types'>
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 [
<category: 'osmo-messages'>
| ies type |
IEMessage class >> initWith: type [
<category: 'creation'>
^ (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 [
<category: 'creation'>
type := aType.
]
type [
^ type
]
addIe: aIe [
<category: 'creation'>
self ies add: aIe.
]
ies [
<category: 'access'>
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 [
<category: 'creation'>
aMsg putByte: type.
self ies do: [:each | each writeOn: aMsg ]
]
]
Object subclass: BCD [
<category: 'osmo-message'>
<comment: 'Class to deal with Binary Coded Decimals'>
BCD class >> encode: aNumber [
<category: 'access'>
| 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 [
<category: 'access'>
| 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
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
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 [
<category: 'private'>
conManager := aHandler.
]
readQueue [
<category: 'private'>
^ queue
]
srcRef [
<category: 'access'>
^ src
]
srcRef: aRef [
<category: 'access'>
src := aRef
]
dstRef: aRef [
<category: 'access'>
dst := aRef
]
dstRef [
<category: 'access'>
^ 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 [
<category: 'connection-handling'>
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 [
<comment: 'I take a SCCP message and recursively parse all the data'>
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 |
<comment: 'I handle SCCP messages'>
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 [
<category: 'private'>
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. ]
]
]

View File

@ -20,6 +20,8 @@ PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: IPAConnection [
| socket demuxer queue muxer dispatcher sccp ipa sem |
<import: OsmoGSM>
IPAConnection class >> initWith: anAddr port: aPort token: aToken [
^ (self new)
socket: (Sockets.Socket remote: anAddr port: aPort);

428
Tests.st
View File

@ -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 <http://www.gnu.org/licenses/>.
"
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.
]
]

View File

@ -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'.

View File

@ -3,29 +3,11 @@
<namespace>OsmoTestPhone</namespace>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoLogging</prereq>
<prereq>OsmoGSM</prereq>
<filein>Messages.st</filein>
<filein>BSSAP.st</filein>
<filein>BSSMAP.st</filein>
<filein>GSM48.st</filein>
<filein>SCCPHandler.st</filein>
<filein>GSMDriver.st</filein>
<filein>TestPhone.st</filein>
<test>
<sunit>OsmoTestPhone.GSM0808Test</sunit>
<sunit>OsmoTestPhone.BSSAPTest</sunit>
<sunit>OsmoTestPhone.GSM48Test</sunit>
<sunit>OsmoTestPhone.TestMessages</sunit>
<filein>Tests.st</filein>
</test>
<file>BSSAP.st</file>
<file>BSSMAP.st</file>
<file>Messages.st</file>
<file>SCCPHandler.st</file>
<file>GSM48.st</file>
<file>GSMDriver.st</file>
<file>TestPhone.st</file>
<file>Tests.st</file>
</package>