aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-12-15 12:38:46 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-12-16 21:25:17 +0100
commit6f210e29068cbdefa550a3d7bea0979d9d5bfd9d (patch)
treeb402f3da41ce49e66fa188a0120b007b7424965a
parent1b56da9dfbe67cebf024422a4e816366046eb284 (diff)
Create osmo-gsm based on the old testphone code.
-rw-r--r--GSMDriver.st357
-rw-r--r--README2
-rw-r--r--TestPhone.st178
-rw-r--r--WebApp.st284
-rw-r--r--package.xml16
5 files changed, 7 insertions, 830 deletions
diff --git a/GSMDriver.st b/GSMDriver.st
deleted file mode 100644
index 531cff0..0000000
--- a/GSMDriver.st
+++ /dev/null
@@ -1,357 +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: GSMDriver [
- | sccp proc sapis completeSem phoneConfig |
- <category: 'osmo-gsm-operation'>
- <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.'>
-
- GSMDriver class >> new [
- <category: 'private'>
- ^ super new initialize; yourself
- ]
-
- GSMDriver class >> initWith: aSCCPConnection sapi: aSapi on: aProc phone: aPhone[
- <category: 'creation'>
- ^ self new
- sapi: aSapi on: aProc;
- sccp: aSCCPConnection;
- phone: aPhone;
- yourself
- ]
-
- initialize [
- <category: 'private'>
- completeSem := Semaphore new.
- sapis := Dictionary new.
- ]
-
- completeSem [
- ^ completeSem
- ]
-
- waitForCompletion [
- <category: 'accessing'>
- ^ completeSem wait
- ]
-
- waitWithTimeout: aTimeout [
- | delay |
- <category: 'accessing'>
-
- delay := Delay forSeconds: aTimeout.
- delay timedWaitOn: completeSem.
- ]
-
- sapi: aSapi on: aProc [
- <category: 'manage'>
- sapis at: aSapi put: aProc.
- ]
-
- phone: aPhone [
- <category: 'private'>
- phoneConfig := aPhone.
- ]
-
- sccp: aSCCPConnection [
- sccp := aSCCPConnection
- ]
-
-
- sendClearRequest [
- | clear |
- clear := IEMessage initWith: GSM0808Helper msgClearReq.
- clear addIe: (GSMCauseIE initWith: 0).
- sccp nextPutData: (BSSAPManagement initWith: clear).
- ]
-
- run [
- | connected |
- <category: 'processing'>
- "Process all messages in a thread"
-
- connected := true.
- proc := [
- [
- [
- [true] whileTrue: [
- | msg |
- msg := sccp next.
- self dispatch: msg.
- ].
- ] on: SystemExceptions.EndOfStream do: [
- connected := false.
- 'SCCP Connection is now disconnected' printNl.
- ].
- ] ensure: [
- connected ifTrue: [
- 'SCCP Cleaning up connection' printNl.
- connected := false.
- self sendClearRequest.
- ].
-
- completeSem signal.
- ].
- ] fork.
- ]
-
- cleanUp [
- <category: 'protected'>
- ]
-
- dispatchMan: aMsg [
- <category: 'private'>
- aMsg type = GSM0808Helper msgClear ifTrue: [
- | resp |
- resp := IEMessage initWith: GSM0808Helper msgClearComp.
- sccp nextPutData: (BSSAPManagement initWith: resp).
- ^ true
- ].
-
- aMsg type = GSM0808Helper msgCipherModeCmd ifTrue: [
- | resp |
- resp := IEMessage initWith: GSM0808Helper msgCipherModeCmpl.
- resp addIe: (GSM0808ChosenEncrIE initWith: 1).
- sccp 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).
- sccp 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 |
- auth := A3A8 COMP128_v3: self auKey rand: aMsg auth data.
- resp := GSM48AuthResp new.
- resp sres data: (auth copyFrom: 1 to: 4).
-
- sccp 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 dispatchMan: aMsg data.
- ]
- ifFalse: [
- self dispatchDTAP: aMsg data sapi: aMsg sapi.
- ].
- aMsg inspect.
- ]
-
- dispatchCMAccept [
- sapis do: [:each |
- each serviceAccepted.
- ].
- ]
-]
-
-Object subclass: ProcedureBase [
- | driver conn success |
-
- ProcedureBase class >> initWith: aHandler phone: aPhone [
- ^ self new
- createConnection: aHandler phone: aPhone;
- yourself
- ]
-
- openConnection: aMsg sapi: aSapi phone: aPhone handler: aHandler [
- | msg bssap |
- msg := IEMessage initWith: GSM0808Helper msgComplL3.
- msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 4099 ci: 40000).
- msg addIe: (GSMLayer3Info initWith: aMsg).
-
- bssap := BSSAPManagement initWith: msg.
-
- conn := aHandler createConnection: bssap.
- driver := GSMDriver initWith: conn sapi: aSapi on: self phone: aPhone.
- 'Created the driver' printNl.
- ]
-
- run [
- driver run.
- ]
-
- execute [
- driver run.
- driver waitForCompletion.
- ]
-
- driver [
- ^ driver
- ]
-
- complete [
- ^ driver completeSem signals > 0
- ]
-
- success [
- ^ success ifNil: [false]
- ]
-
- success: aSuc [
- success := aSuc.
- ]
-
- serviceAccepted [
- "TO BE implemented"
- ]
-]
-
-
-ProcedureBase subclass: LUProcedure [
- createConnection: aHandler phone: aPhone [
- | lu |
-
- lu := GSM48LURequest new.
- lu mi imsi: aPhone imsi.
-
- 'LU proc started' printNl.
- self openConnection: lu sapi: 0 phone: aPhone handler: aHandler.
- ]
-
- name [
- ^ 'Location Updating Procedure'
- ]
-
- execute [
- super execute.
-
- self success
- ifTrue: [
- 'LUAccept nicely succeeded.' printNl.
- ]
- ifFalse: [
- 'LURejected.' printNl.
- ]
- ]
-
- handleData: aMsg sapi: aSapi [
- aMsg class messageType = GSM48MMMessage msgLUAcc ifTrue: [
- self success: true.
- ].
- ]
-]
-
-ProcedureBase subclass: CallProcedure [
- | nr |
-
- CallProcedure class >> initWith: aConn phone: aPhone nr: aNr [
- ^ (super initWith: aConn phone: aPhone)
- nr: aNr; yourself
- ]
-
- nr: aNr [
- nr := (ByteArray with: 16r80), (GSMNumberDigits encodeFrom: aNr).
- ]
-
- createConnection: aHandler phone: aPhone [
- | cm |
-
- cm := GSM48CMServiceReq new.
- cm mi imsi: aPhone imsi.
- cm keyAndType val: 16r21.
- self openConnection: cm sapi: 0 phone: aPhone handler: aHandler.
- ]
-
- name [
- ^ 'Call Procedure'
- ]
-
- execute [
- super execute.
-
- self success
- ifTrue: [
- 'Call got accepted on the way' printNl.
- ]
- ifFalse: [
- 'Call was never connected' printNl.
- ].
- ]
-
- serviceAccepted [
- | resp |
- 'Accepted' printNl.
-
- resp := GSM48CCSetup new.
- 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 msgConnect ifTrue: [
- | resp |
- resp := GSM48CCConnectAck new.
- conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
-
- self success: true.
- ].
-
- aMsg class messageType = GSM48CCMessage msgDisconnect ifTrue: [
- | resp |
- resp := GSM48CCRelease new.
- resp causeOrDefault data: #(16rE1 16r90) asByteArray.
- conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0)
- ].
- ]
-]
diff --git a/README b/README
index 4b572b7..ccb7449 100644
--- a/README
+++ b/README
@@ -1 +1 @@
-A simple test phone to do a LU and place a call
+GSM utilities based on osmo-network for SCCP,BSSAP,BSSMAP,GSM48
diff --git a/TestPhone.st b/TestPhone.st
deleted file mode 100644
index 4bb3106..0000000
--- a/TestPhone.st
+++ /dev/null
@@ -1,178 +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: 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);
- setup: aToken;
- yourself
- ]
-
- 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.
- dispatcher initialize.
-
- 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.EndOfStream do: [:e | ^ false ]
- ]
- ]
-
- drainSendQueue [
- sem critical: [
- [queue isEmpty] whileFalse: [
- | msg |
- msg := queue next.
- socket nextPutAllFlush: msg.
- ]
- ]
- ]
-
- send: aMsg with: aType [
- muxer nextPut: aMsg with: aType.
- self drainSendQueue.
- ]
-
- sccpHandler [
- ^ sccp
- ]
-]
-
-Object subclass: IPAConfig [
- | socket addr port token connection sem |
-
- 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 ]
-
- doLU: aPhone [
- ^ LUProcedure initWith: (connection sccpHandler) phone: aPhone.
- ]
- sendLU: aPhone [
- (self doLU: aPhone) execute.
- ]
-
- doCallNumber: aPhone nr: aNr [
- ^ CallProcedure initWith: (connection sccpHandler) phone: aPhone nr: aNr.
- ]
-
- callNumber: aPhone nr: aNumber [
- ^ (self doCallNumber: aPhone nr: aNumber) execute
- ]
-]
-
-Object subclass: PhoneConfig [
- | imsi auKey |
-
- <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 ]
- auKey: anAuKey [
- auKey := anAuKey.
- ]
-
- 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].
- ]
-]
diff --git a/WebApp.st b/WebApp.st
deleted file mode 100644
index 716e97b..0000000
--- a/WebApp.st
+++ /dev/null
@@ -1,284 +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: 'Iliad-Core'.
-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'.
-FileStream fileIn: 'GSMDriver.st'.
-FileStream fileIn: 'TestPhone.st'.
-
-Iliad.ILCometEvent subclass: PhoneRefresh [
-]
-
-Iliad.ILWidget subclass: ServerConfigWidget [
- initialize [
- super initialize.
- self subscribeToCometEvent: PhoneRefresh.
- ]
-
- 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 [
- | context |
- (self application gsmServer)
- connect;
- serve.
-
- context := self context.
- [
- ILCurrentContext processVariable value: context.
-
- (Delay forSeconds: 5) wait.
- self session cometHandler
- handleEvent: PhoneRefresh new.
- ] fork.
- ]
-
-]
-
-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[
- | proc |
- [
- proc := aBlock value.
- proc run.
- self session procedures add: proc.
- self application procedures markDirty.
- ] on: Exception do: [:e |
- self lightbox: (ErrorWidget initWith: aName, ' could not be started.')
- ]
- ]
-]
-
-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'
- ]
-]
-
-Iliad.ILWidget subclass: ProcedureWidget [
- showStatus: item on: form [
- | status |
- status := item complete
- ifTrue: [
- item success
- ifTrue: [item name, ' completed with success']
- ifFalse: [item name, ' completed with failure'].
- ]
- ifFalse: [
- item name, ' in-progress'
- ].
-
- form text: status.
- form button
- text: 'Remove';
- action: [self markDirty.
- item complete
- ifFalse: [
- item driver 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.]
- ]
- ]
- ]
-]
-
-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 |
- 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]
- ]
-
- lu [
- ^ lu ifNil: [lu := LUWidget new]
- ]
-
- index [
- <category: 'controllers'>
- ^ [:e |
- e
- build: self cometConnection;
- build: self serverConfig;
- build: self phoneConfig;
- build: self lu;
- build: self call;
- 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.
-]
diff --git a/package.xml b/package.xml
index 15274a5..f958e73 100644
--- a/package.xml
+++ b/package.xml
@@ -1,6 +1,6 @@
<package>
- <name>OsmoTestPhone</name>
- <namespace>OsmoTestPhone</namespace>
+ <name>OsmoGSM</name>
+ <namespace>OsmoGSM</namespace>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoLogging</prereq>
@@ -9,14 +9,12 @@
<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>
+ <sunit>OsmoGSM.GSM0808Test</sunit>
+ <sunit>OsmoGSM.BSSAPTest</sunit>
+ <sunit>OsmoGSM.GSM48Test</sunit>
+ <sunit>OsmoGSM.TestMessages</sunit>
<filein>Tests.st</filein>
</test>
@@ -25,7 +23,5 @@
<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>