smalltalk
/
osmo-st-all
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-all/osmo-st-testphone/TestPhone.st

235 lines
5.6 KiB
Smalltalk

"
(C) 2010-2011 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'.
PackageLoader fileInPackage: 'OsmoGSM'.
Object subclass: IPAConnection [
| socket demuxer queue muxer dispatcher sccp ipa sem |
<category: 'OsmoTestPhone'>
<import: OsmoGSM>
IPAConnection class >> initWith: anAddr port: aPort token: aToken [
^ (self new)
socket: (Sockets.Socket remote: anAddr port: aPort);
setup: aToken;
yourself
]
socket [
^ socket
]
socket: aSocket [
socket := aSocket.
]
setup: aToken [
sem := Semaphore forMutualExclusion.
demuxer := Osmo.IPADemuxer initOn: socket.
queue := SharedQueue new.
muxer := Osmo.IPAMuxer initOn: queue.
dispatcher := Osmo.IPADispatcher new.
sccp := SCCPHandler new.
sccp registerOn: dispatcher.
sccp connection: self.
ipa := Osmo.IPAProtoHandler new.
ipa registerOn: dispatcher.
ipa muxer: muxer.
ipa token: aToken
]
serve [
[true] whileTrue: [
[
| data |
data := demuxer next.
dispatcher dispatch: data first with: data second.
self drainSendQueue.
]
on: SystemExceptions.FileError do: [:e | ^ false ]
on: SystemExceptions.EndOfStream do: [:e | ^ false ]
].
sccp linkSetFailed.
]
drainSendQueue [
sem critical: [
[queue isEmpty] whileFalse: [
| msg |
msg := queue next.
socket nextPutAllFlush: msg.
]
]
]
send: aMsg with: aType [
muxer nextPut: aMsg with: aType.
[
self drainSendQueue.
] on: SystemExceptions.FileError do: [:e | sccp linkSetFailed ]
on: SystemExceptions.EndOfStream do: [:e | sccp linkSetFailed ]
]
sccpHandler [
^ sccp
]
]
Object subclass: IPAConfig [
| addr port token connection sem |
<category: 'OsmoTestPhone'>
addr: anAddr port: aPort [
addr := anAddr.
port := aPort.
]
token: aToken [
token := aToken.
]
connect [
sem := Semaphore new.
connection := IPAConnection initWith: addr port: port token: token.
]
connection [
^ connection
]
serve [
[
[
connection serve.
'Connection disconnected' printNl.
] ensure: [
connection := nil.
sem signal.
]
] fork.
]
isConnected [
^ connection isNil not
]
semaphore [ ^ sem ]
doIMSIDetach: aPhone [
^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
setProc: IMSIDetachProcedure new;
yourself
]
sendIMSIDetach: aPhone [
^ (self doIMSIDetach: aPhone)
openConnection; waitForTermination; yourself
]
doLU: aPhone [
^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
setProc: LUProcedure new;
yourself
]
sendLU: aPhone [
^ (self doLU: aPhone)
openConnection; waitForTermination; yourself
]
doCallNumber: aPhone nr: aNr [
^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
setProc: (CallProcedure initWithNr: aNr);
yourself
]
callNumber: aPhone nr: aNumber [
^ (self doCallNumber: aPhone nr: aNumber)
openConnection; waitForTermination; yourself
]
doUSSD: aPhone nr: aNr [
^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
setProc: (USSDProcedure initWithNr: aNr);
yourself
]
sendUSSD: aPhone nr: aNr [
^ (self doUSSD: aPhone nr: aNr)
openConnection; waitForTermination; yourself
]
]
Object subclass: PhoneConfig [
| imsi auKey auVer |
<category: 'OsmoTestPhone'>
<comment: 'I am the config of a phone. I do have an IMSI and such.'>
PhoneConfig class >> initWith: aImsi auKey: anAuKey [
^ self new
imsi: aImsi;
auKey: anAuKey;
yourself
]
imsi: aImsi [
imsi := aImsi.
]
imsi [ ^ imsi ]
auKey [ ^ auKey ]
auVer [ ^ auVer ]
auKey: anAuKey [
auKey := anAuKey.
auVer := 3.
]
auKeyV2: anAuKey [
auKey := anAuKey.
auVer := 2.
]
auKeyV1: anAuKey [
auKey := anAuKey.
auVer := 1.
]
auKeyByteArray [
^ auKey isString
ifTrue: [
| array |
array := OrderedCollection new.
1 to: auKey size by: 2 do: [:each |
array add: (Number readFrom:
(auKey copyFrom: each to: each + 1) readStream
radix: 16)
].
array asByteArray.
]
ifFalse: [auKey].
]
]