smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Add 'osmo-st-testphone/' from commit '98a9d07856671daf934aa0029f3bebcc13a06f9d'

git-subtree-dir: osmo-st-testphone
git-subtree-mainline: 31711e7ba2
git-subtree-split: 98a9d07856
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:03 +02:00
commit 77017cf5e0
5 changed files with 1034 additions and 0 deletions

View File

@ -0,0 +1,480 @@
"
(C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: #OsmoASN1.
OsmoGSM.SCCPConnectionBase subclass: GSMConnection [
| sapis completeSem phoneConfig mainProc |
<category: 'OsmoTestPhone'>
<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>
GSMConnection class >> on: aHandler withPhone: aPhone [
<category: 'creation'>
^ (self on: aHandler)
phone: aPhone;
yourself
]
initialize [
<category: 'private'>
super initialize.
completeSem := Semaphore new.
sapis := Dictionary new.
]
completeSem [
^ completeSem
]
isComplete [
^ completeSem signals > 0
]
waitForTermination [
"I wait until the connection is closed"
<category: 'accessing'>
^ completeSem wait
]
setProc: aProc [
<category: 'manage'>
mainProc := aProc.
mainProc connection: self.
sapis at: aProc sapi put: aProc.
]
openConnection [
self connectionRequest: mainProc completeLayer3.
]
mainProc [
<category: 'accessing'>
^ mainProc
]
phone: aPhone [
<category: 'private'>
phoneConfig := aPhone.
]
phone [
<category: 'accessing'>
^ phoneConfig
]
sendClearRequest [
| clear |
clear := IEMessage initWith: GSM0808Helper msgClearReq.
clear addIe: (GSMCauseIE initWith: 0).
self nextPutData: (BSSAPManagement initWith: clear).
]
data: aDT [
[
self dispatch: aDT data.
] on: Error do: [:e |
'SCCP Cleaning up connection' printNl.
self sendClearRequest.
]
]
terminate [
completeSem signal.
]
cleanUp [
<category: 'protected'>
]
dispatchBSSAP: aMsg [
<category: 'private'>
aMsg type = GSM0808Helper msgClear ifTrue: [
| resp |
resp := IEMessage initWith: GSM0808Helper msgClearComp.
self nextPutData: (BSSAPManagement initWith: resp).
^ true
].
aMsg type = GSM0808Helper msgCipherModeCmd ifTrue: [
| resp |
resp := IEMessage initWith: GSM0808Helper msgCipherModeCmpl.
resp addIe: (GSM0808ChosenEncrIE initWith: 1).
self nextPutData: (BSSAPManagement initWith: resp).
self dispatchCMAccept.
^ true
].
aMsg type = GSM0808Helper msgAssRequest ifTrue: [
| resp |
"Reply with a AMR halfrate statement"
resp := IEMessage initWith: GSM0808Helper msgAssComplete.
resp addIe: (GSM0808CauseIE initWith: 0).
resp addIe: (GSM0808ChosenChannel initWith: 16r98).
resp addIe: (GSM0808ChosenEncrIE initWith: 1).
resp addIe: (GSM0808SpeechVerIE initWith: 16r25).
self nextPutData: (BSSAPManagement initWith: resp).
^ true
].
'Unhandled message' printNl.
aMsg inspect.
]
auKey [
^ phoneConfig auKeyByteArray.
]
imsi [
^ phoneConfig imsi.
]
dispatchDTAP: aMsg sapi: aSapi [
<category: 'private'>
aMsg class messageType = GSM48MMMessage msgAuReq ifTrue: [
| auth resp |
'Authentication....' printNl.
auth := A3A8 COMP128: phoneConfig auVer
ki: self auKey
rand: aMsg auth data.
resp := GSM48AuthResp new.
resp sres data: (auth copyFrom: 1 to: 4).
self nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
^ true
].
aMsg class messageType = GSM48MMMessage msgCMAccept ifTrue: [
self dispatchCMAccept.
^ true
].
sapis at: aSapi ifPresent: [:handler |
handler handleData: aMsg sapi: aSapi.
].
'Unhandled DTAP message' printNl.
aMsg inspect.
]
dispatch: aMsg [
<category: 'protected'>
aMsg class msgType = BSSAPHelper msgManagemnt
ifTrue: [
self dispatchBSSAP: aMsg data.
]
ifFalse: [
self dispatchDTAP: aMsg data sapi: aMsg sapi.
].
]
dispatchCMAccept [
sapis do: [:each |
each serviceAccepted.
].
]
onConnectionConfirmed [
mainProc connectionConfirmed.
]
]
Object subclass: ProcedureBase [
| success conn |
<category: 'OsmoTestPhone'>
<comment: 'I provide a transaction base class for a given SAPI'>
<import: OsmoGSM>
connection: aConn [
conn := aConn
]
sapi [
"Use SAPI 0 by default"
<category: 'sapi'>
^ 0
]
completeLayer3 [
| msg |
msg := IEMessage initWith: GSM0808Helper msgComplL3.
msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 8210 ci: 30000).
msg addIe: (GSMLayer3Info initWith: self initialMessage).
^ BSSAPManagement initWith: msg.
]
success [
^ success ifNil: [false]
]
success: aSuc [
success := aSuc.
]
serviceAccepted [
"TO BE implemented"
]
status [
^ self success
ifTrue: ['Success']
ifFalse: ['Failure']
]
initialMessage [
"I should return the initial message of the transaction"
self subclassResponsibility
]
connectionConfirmed [
| cm |
cm := GSM48RRClassmarkChange new.
conn nextPutData: (BSSAPDTAP initWith: cm linkIdentifier: 0).
]
]
ProcedureBase subclass: IMSIDetachProcedure [
<category: 'OsmoTestPhone'>
initialMessage [
| detach |
detach := GSM48IMSIDetachInd new.
detach mi imsi: conn phone imsi.
^ detach
]
name [
^ 'IMSI Detach Procedure'
]
status [
^ self success
ifTrue: ['IMSI Detach succeeded']
ifFalse: ['IMSI Detach failed'].
]
connectionConfirmed [
"Nothing. No classmark change needed here."
]
]
ProcedureBase subclass: LUProcedure [
<category: 'OsmoTestPhone'>
initialMessage [
| lu |
lu := GSM48LURequest new.
lu mi imsi: conn phone imsi.
^ lu
]
name [
^ 'Location Updating Procedure'
]
status [
^ self success
ifTrue: ['LUAccept nicely succeeded.']
ifFalse: ['LURejected.']
]
handleData: aMsg sapi: aSapi [
aMsg class messageType = GSM48MMMessage msgLUAcc ifTrue: [
self success: true.
].
]
]
ProcedureBase subclass: CallProcedure [
| nr |
<category: 'OsmoTestPhone'>
CallProcedure class >> initWithNr: aNr [
^ self new
nr: aNr;
yourself
]
nr: aNr [
nr := (ByteArray with: 16r91), (GSMNumberDigits encodeFrom: aNr).
]
initialMessage [
| cm |
cm := GSM48CMServiceReq new.
cm mi imsi: conn phone imsi.
cm keyAndType val: 16r21.
^ cm
]
name [
^ 'Call Procedure'
]
status [
^ self success
ifTrue: [ 'Call got accepted on the way.']
ifFalse: ['Call was never connected'].
]
serviceAccepted [
| resp |
'Accepted' printNl.
resp := GSM48CCSetup new.
resp seq: 1.
resp bearer1OrDefault data: #(16r60 16r02 0 1 4 16r85) asByteArray.
resp calledOrDefault data: nr.
conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
]
handleData: aMsg sapi: aSapi [
aMsg class messageType = GSM48CCMessage msgProceeding ifTrue: [
| resp |
resp := GSM48CCDisconnect new.
resp seq: 1.
resp cause data: #(16rE1 16r90).
conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
].
aMsg class messageType = GSM48CCMessage msgConnect ifTrue: [
| resp |
resp := GSM48CCConnectAck new.
resp seq: 1.
conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
self success: true.
].
aMsg class messageType = GSM48CCMessage msgDisconnect ifTrue: [
| resp |
resp := GSM48CCRelease new.
resp seq: 1.
resp causeOrDefault data: #(16rE1 16r90) asByteArray.
conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0)
].
aMsg class messageType = GSM48CCMessage msgRelease ifTrue: [
| resp |
resp := GSM48CCReleaseCompl new.
resp seq: 1.
conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0)
].
]
]
ProcedureBase subclass: USSDProcedure [
| nr facility |
<category: 'OsmoTestPhone'>
<import: Osmo>
USSDProcedure class >> initWithNr: aNr [
^ self new
nr: aNr;
yourself
]
USSDProcedure class >> buildProcessUnstructReq: aNr [
| req str |
req := {BERTag fromTuple: #(2 true 1). OrderedCollection
with: {BERTag integer. #(0).}
with: {BERTag integer. #(59).}
with: {BERTag fromTuple: #(0 true 16). OrderedCollection
with: {BERTag octetString. #(15).}
with: {BERTag octetString. aNr asUSSD7Bit}}}.
str := WriteStream on: (ByteArray new: 40).
(DERTLVStream on: str) nextPut: req.
^ str contents
]
USSDProcedure class >> buildReturnLast: invokeId text: aText [
| ret str |
ret := {BERTag fromTuple: #(2 true 2). OrderedCollection
with: {BERTag integer. invokeId}
with: {BERTag sequence. OrderedCollection
with: {BERTag integer. #(60)}
with: {BERTag sequence. OrderedCollection
with: {BERTag octetString. #(15).}
with: {BERTag octetString. aText asUSSD7Bit}}}}.
str := WriteStream on: (ByteArray new: 40).
(DERTLVStream on: str) nextPut: ret.
^ str contents
]
nr: aNr [
nr := aNr.
]
facility [
^ facility
]
initialMessage [
| cm |
cm := GSM48CMServiceReq new.
cm mi imsi: conn phone imsi.
cm luType val: 8.
^ cm
]
name [
^ 'USSD Procedure'
]
serviceAccepted [
| reg |
reg := GSM48SSRegister new.
reg ti: 1.
reg facility data: (self class buildProcessUnstructReq: nr).
reg ssVersionOrDefault data: #(0).
conn nextPutData: (BSSAPDTAP initWith: reg linkIdentifier: 0).
]
handleData: aMsg sapi: aSapi [
aMsg class messageType = GSM48SSMessage msgReleaseCompl ifTrue:[
facility := aMsg facility.
self success: aMsg ti = 9.
].
aMsg class messageType = GSM48SSMessage msgFacility ifTrue: [
| fac |
fac := GSM48SSFacility new.
fac ti: 1.
fac facility data: (self class buildReturnLast: #(1) text: '45050888658950').
conn nextPutData: (BSSAPDTAP initWith: fac linkIdentifier: 0).
]
]
]

1
osmo-st-testphone/README Normal file
View File

@ -0,0 +1 @@
A simple test phone to do a LU and place a call

View File

@ -0,0 +1,234 @@
"
(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].
]
]

304
osmo-st-testphone/WebApp.st Normal file
View File

@ -0,0 +1,304 @@
"
(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: 'Iliad-Core'.
PackageLoader fileInPackage: 'Iliad-More-Comet'.
PackageLoader fileInPackage: 'Iliad-More-Formula'.
PackageLoader fileInPackage: 'Iliad-Swazoo'.
PackageLoader fileInPackage: 'OsmoGSM'.
FileStream fileIn: 'GSMDriver.st'.
FileStream fileIn: 'TestPhone.st'.
Iliad.ILWidget subclass: ServerConfigWidget [
initialize [
super initialize.
]
contents [
^ [:e |
self application gsmServer isConnected
ifTrue: [
e text: 'The A link is connected to the MSC'.
]
ifFalse: [
e text: 'The A link is not connected: '.
e a
text: 'Connect';
action: [self connectServer]
].
]
]
connectServer [
(self application gsmServer)
connect;
serve.
]
]
Iliad.ILWidget subclass: PhoneConfigWidget [
configFormOn: anItem [
| form |
form := ILFormula on: anItem.
(form inputOn: #imsi)
labelContents: [:e | e span text: 'IMSI' ].
(form inputOn: #auKey)
labelContents: [:e | e span text: 'AuKey' ].
^ form
]
configurePhone [
self lightbox: ((self configFormOn: self session gsmConfig)
addMessage: [:e | e h2: 'Configure Test Phone'];
yourself)
]
contents [
^ [:e | e a text: 'Configure phone'; action: [self configurePhone]].
]
]
Iliad.ILWidget subclass: ErrorWidget [
| reason |
ErrorWidget class >> initWith: anError [
^ self new
reason: anError;
yourself
]
reason: aReason [
reason := aReason.
]
contents [
^ [:e | e text: reason ]
]
]
Iliad.ILWidget subclass: ProcedureWidget [
runProcedure: aBlock name: aName[
| conn |
[
conn := aBlock value.
conn openConnection.
self session procedures add: conn.
self application procedures markDirty.
] on: Exception do: [:e |
self lightbox: (ErrorWidget initWith: aName, ' could not be started.')
]
]
showStatus: item on: form [
| status |
status := item isComplete
ifTrue: [
item mainProc success
ifTrue: [item mainProc name, ' completed with success']
ifFalse: [item mainProc name, ' completed with failure'].
]
ifFalse: [
item mainProc name, ' in-progress'
].
form text: status.
form button
text: 'Remove';
action: [self markDirty.
item isComplete
ifFalse: [
item sendClearRequest.
].
self session procedures remove: item.].
]
contents [
^ [:e | | procs |
e a
action: [self markDirty];
text: 'Refresh Procedures'.
procs := self session procedures.
procs do: [:each |
e form build: [:form |
self showStatus: each on: form.]
]
]
]
]
ProcedureWidget subclass: IMSIDetachWidget [
contents [
^ [:e |
e a
text: 'Start IMSI Detach';
action: [self doIMSIDetach]
]
]
doIMSIDetach [
self runProcedure: [
self application gsmServer
doIMSIDetach: self session gsmConfig] name: 'IMSI Detach'.
]
]
ProcedureWidget subclass: LUWidget [
contents [
^ [:e |
e a
text: 'Start LU';
action: [self doLU]
]
]
doLU [
self runProcedure: [self application gsmServer doLU: self session gsmConfig] name: 'LU'
]
]
ProcedureWidget subclass: CallWidget [
contents [
^[:e |
e form build: [:form |
form input action: [:val | self placeCall: val].
form button text: 'Call']
]
]
placeCall: aNumber [
self runProcedure: [self application gsmServer doCallNumber: self session gsmConfig nr: aNumber] name: 'Call'
]
]
ProcedureWidget subclass: USSDWidget [
contents [
^[:e |
e form build: [:form |
form input action: [:val | self doUSSD: val].
form button text: 'USSD']
]
]
doUSSD: aNumber [
self runProcedure: [self application gsmServer doUSSD: self session gsmConfig nr: aNumber] name: 'USSD'.
]
]
Iliad.ILSession subclass: GSMTestphoneSession [
| user gsmConfig procedures |
isAuthenticated [
^ user = 'toto-user'
]
username: aUser [
user := aUser.
]
gsmConfig [ ^ gsmConfig ifNil: [gsmConfig := PhoneConfig new. ]]
procedures [ ^ procedures ifNil: [procedures := OrderedCollection new]]
]
Iliad.ILApplication subclass: GSMTestphoneApp [
| config call lu serverConfig gsmServer procedureWidget ussd imsiDetach |
GSMTestphoneApp class >> path [ ^ 'testphone' ]
GSMTestphoneApp class >> initialize [
Iliad.ILSessionManager current sessionClass: GSMTestphoneSession.
]
gsmServer [
^ gsmServer ifNil: [gsmServer := IPAConfig new]
]
phoneConfig [
^ config ifNil: [config := PhoneConfigWidget new]
]
serverConfig [
^ serverConfig ifNil: [serverConfig := ServerConfigWidget new]
]
procedures [
^ procedureWidget ifNil: [procedureWidget := ProcedureWidget new]
]
call [
^ call ifNil: [call := CallWidget new]
]
imsiDetach [
^ imsiDetach ifNil: [imsiDetach := IMSIDetachWidget new].
]
lu [
^ lu ifNil: [lu := LUWidget new]
]
ussd [
^ ussd ifNil: [ussd := USSDWidget new]
]
index [
<category: 'controllers'>
^ [:e |
e
build: self cometConnection;
build: self serverConfig;
build: self phoneConfig;
build: self imsiDetach;
build: self lu;
build: self call;
build: self ussd;
build: self procedures.
].
]
loginContents [
<category: 'building'>
^[:e |
e form build: [:form |
form input action: [:val | self login: val].
form button text: 'Login']]
]
login: aString [
<category: 'actions'>
self session username: aString.
self redirectToCurrentController
]
dispatchOverride [
<category: 'dispatching'>
^self session isAuthenticated
ifFalse: [self loginContents]
ifTrue: [super dispatchOverride]
]
]
Eval [
GSMTestphoneApp initialize.
Iliad.SwazooIliad startOn: 8080.
stdin next.
]

View File

@ -0,0 +1,15 @@
<package>
<name>OsmoTestPhone</name>
<namespace>OsmoTestPhone</namespace>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoLogging</prereq>
<prereq>OsmoGSM</prereq>
<prereq>OsmoASN1</prereq>
<prereq>Iliad</prereq>
<filein>GSMDriver.st</filein>
<filein>TestPhone.st</filein>
<file>GSMDriver.st</file>
<file>TestPhone.st</file>
</package>