aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2011-06-16 01:45:47 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2011-06-16 16:23:19 +0200
commit527a29ced2ba5bbc29c675065aa138c1175987ac (patch)
tree68ccc00159e74ba1f9d1022bce401ac409951c1a
parent6a07c7387817f1a12fdff334798686aa39b083ff (diff)
sccp: Big structural change of how we handle SCCP connection
GSMConnection is the base class it will have - ProcedureBase (probably be renamed to TransactionBase) hanging off it, there is the concept of the main transaction that has started this connection. It is mostly there for having an easy way to judge if this connection was a success and the only time this soft phone will have multiple transactions is when we get MT-SMS while doing something else. This is not fully tested due the lack of free internet access the KEF airport.
-rw-r--r--GSMDriver.st221
-rw-r--r--TestPhone.st18
-rw-r--r--WebApp.st22
3 files changed, 118 insertions, 143 deletions
diff --git a/GSMDriver.st b/GSMDriver.st
index fcc115a..631b238 100644
--- a/GSMDriver.st
+++ b/GSMDriver.st
@@ -18,30 +18,24 @@
PackageLoader fileInPackage: #OsmoASN1.
-Object subclass: GSMDriver [
- | sccp proc sapis completeSem phoneConfig |
+OsmoGSM.SCCPConnectionBase subclass: GSMConnection [
+ | sapis completeSem phoneConfig mainProc |
<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.'>
<import: OsmoGSM>
- GSMDriver class >> new [
- <category: 'private'>
- ^ super new initialize; yourself
- ]
-
- GSMDriver class >> initWith: aSCCPConnection sapi: aSapi on: aProc phone: aPhone[
+ GSMConnection class >> on: aHandler withPhone: aPhone [
<category: 'creation'>
- ^ self new
- sapi: aSapi on: aProc;
- sccp: aSCCPConnection;
+ ^ (self on: aHandler)
phone: aPhone;
yourself
]
initialize [
<category: 'private'>
+ super initialize.
completeSem := Semaphore new.
sapis := Dictionary new.
]
@@ -50,22 +44,31 @@ classes.'>
^ completeSem
]
- waitForCompletion [
+ isComplete [
+ ^ completeSem signals > 0
+ ]
+
+ waitForTermination [
+ "I wait until the connection is closed"
<category: 'accessing'>
^ completeSem wait
]
- waitWithTimeout: aTimeout [
- | delay |
- <category: 'accessing'>
+ setProc: aProc [
+ <category: 'manage'>
- delay := Delay forSeconds: aTimeout.
- delay timedWaitOn: completeSem.
+ mainProc := aProc.
+ mainProc connection: self.
+ sapis at: aProc sapi put: aProc.
]
- sapi: aSapi on: aProc [
- <category: 'manage'>
- sapis at: aSapi put: aProc.
+ openConnection [
+ self connectionRequest: mainProc completeLayer3.
+ ]
+
+ mainProc [
+ <category: 'accessing'>
+ ^ mainProc
]
phone: aPhone [
@@ -73,46 +76,29 @@ classes.'>
phoneConfig := aPhone.
]
- sccp: aSCCPConnection [
- sccp := aSCCPConnection
+ phone [
+ <category: 'accessing'>
+ ^ phoneConfig
]
-
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.
+ 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 [
@@ -124,7 +110,7 @@ classes.'>
aMsg type = GSM0808Helper msgClear ifTrue: [
| resp |
resp := IEMessage initWith: GSM0808Helper msgClearComp.
- sccp nextPutData: (BSSAPManagement initWith: resp).
+ self nextPutData: (BSSAPManagement initWith: resp).
^ true
].
@@ -132,7 +118,7 @@ classes.'>
| resp |
resp := IEMessage initWith: GSM0808Helper msgCipherModeCmpl.
resp addIe: (GSM0808ChosenEncrIE initWith: 1).
- sccp nextPutData: (BSSAPManagement initWith: resp).
+ self nextPutData: (BSSAPManagement initWith: resp).
self dispatchCMAccept.
^ true
@@ -146,7 +132,7 @@ classes.'>
resp addIe: (GSM0808ChosenChannel initWith: 16r98).
resp addIe: (GSM0808ChosenEncrIE initWith: 1).
resp addIe: (GSM0808SpeechVerIE initWith: 16r25).
- sccp nextPutData: (BSSAPManagement initWith: resp).
+ self nextPutData: (BSSAPManagement initWith: resp).
^ true
].
@@ -166,12 +152,13 @@ classes.'>
<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).
- sccp nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
+ self nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0).
^ true
].
@@ -209,44 +196,27 @@ classes.'>
]
Object subclass: ProcedureBase [
- | driver conn success |
+ | success conn |
+ <comment: 'I provide a transaction base class for a given SAPI'>
<import: OsmoGSM>
- ProcedureBase class >> initWith: aHandler phone: aPhone [
- ^ self new
- createConnection: aHandler phone: aPhone;
- yourself
+ connection: aConn [
+ conn := aConn
+ ]
+
+ sapi [
+ "Use SAPI 0 by default"
+ <category: 'sapi'>
+ ^ 0
]
- openConnection: aMsg sapi: aSapi phone: aPhone handler: aHandler [
- | msg bssap |
+ completeLayer3 [
+ | msg |
msg := IEMessage initWith: GSM0808Helper msgComplL3.
msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 8210 ci: 30000).
- 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
+ msg addIe: (GSMLayer3Info initWith: self initialMessage).
+ ^ BSSAPManagement initWith: msg.
]
success [
@@ -260,34 +230,37 @@ Object subclass: ProcedureBase [
serviceAccepted [
"TO BE implemented"
]
+
+ status [
+ ^ self success
+ ifTrue: ['Success']
+ ifFalse: ['Failure']
+ ]
+
+ initialMessage [
+ "I should return the initial message of the transaction"
+ self subclassResponsibility
+ ]
]
ProcedureBase subclass: LUProcedure [
- createConnection: aHandler phone: aPhone [
+ initialMessage [
| lu |
lu := GSM48LURequest new.
- lu mi imsi: aPhone imsi.
-
- 'LU proc started' printNl.
- self openConnection: lu sapi: 0 phone: aPhone handler: aHandler.
+ lu mi imsi: conn phone imsi.
+ ^ lu
]
name [
^ 'Location Updating Procedure'
]
- execute [
- super execute.
-
- self success
- ifTrue: [
- 'LUAccept nicely succeeded.' printNl.
- ]
- ifFalse: [
- 'LURejected.' printNl.
- ]
+ status [
+ ^ self success
+ ifTrue: ['LUAccept nicely succeeded.']
+ ifFalse: ['LURejected.']
]
handleData: aMsg sapi: aSapi [
@@ -300,38 +273,33 @@ ProcedureBase subclass: LUProcedure [
ProcedureBase subclass: CallProcedure [
| nr |
- CallProcedure class >> initWith: aConn phone: aPhone nr: aNr [
- ^ (super initWith: aConn phone: aPhone)
- nr: aNr; yourself
+ CallProcedure class >> initWithNr: aNr [
+ ^ self new
+ nr: aNr;
+ yourself
]
nr: aNr [
nr := (ByteArray with: 16r91), (GSMNumberDigits encodeFrom: aNr).
]
- createConnection: aHandler phone: aPhone [
+ initialMessage [
| cm |
cm := GSM48CMServiceReq new.
- cm mi imsi: aPhone imsi.
+ cm mi imsi: conn phone imsi.
cm keyAndType val: 16r21.
- self openConnection: cm sapi: 0 phone: aPhone handler: aHandler.
+ ^ cm
]
name [
^ 'Call Procedure'
]
- execute [
- super execute.
-
- self success
- ifTrue: [
- 'Call got accepted on the way' printNl.
- ]
- ifFalse: [
- 'Call was never connected' printNl.
- ].
+ status [
+ ^ self success
+ ifTrue: [ 'Call got accepted on the way.']
+ ifFalse: ['Call was never connected'].
]
serviceAccepted [
@@ -367,9 +335,10 @@ ProcedureBase subclass: USSDProcedure [
<import: Osmo>
- USSDProcedure class >> initWith: aConn phone: aPhone nr: aNr [
- ^ (super initWith: aConn phone: aPhone)
- nr: aNr; yourself
+ USSDProcedure class >> initWithNr: aNr [
+ ^ self new
+ nr: aNr;
+ yourself
]
USSDProcedure class >> buildProcessUnstructReq: aNr [
@@ -411,13 +380,13 @@ ProcedureBase subclass: USSDProcedure [
^ facility
]
- createConnection: aHandler phone: aPhone [
+ initialMessage [
| cm |
cm := GSM48CMServiceReq new.
- cm mi imsi: aPhone imsi.
+ cm mi imsi: conn phone imsi.
cm keyAndType val: 8.
- self openConnection: cm sapi: 0 phone: aPhone handler: aHandler.
+ ^ cm
]
name [
diff --git a/TestPhone.st b/TestPhone.st
index 3de13f6..50787fc 100644
--- a/TestPhone.st
+++ b/TestPhone.st
@@ -132,26 +132,32 @@ Object subclass: IPAConfig [
semaphore [ ^ sem ]
doLU: aPhone [
- ^ LUProcedure initWith: (connection sccpHandler) phone: aPhone.
+ ^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
+ setProc: LUProcedure new;
+ yourself
]
sendLU: aPhone [
- (self doLU: aPhone) execute.
+ (self doLU: aPhone) waitForTermination.
]
doCallNumber: aPhone nr: aNr [
- ^ CallProcedure initWith: (connection sccpHandler) phone: aPhone nr: aNr.
+ ^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
+ setProc: (CallProcedure initWithNr: aNr);
+ yourself
]
callNumber: aPhone nr: aNumber [
- ^ (self doCallNumber: aPhone nr: aNumber) execute
+ ^ (self doCallNumber: aPhone nr: aNumber) waitForTermination.
]
doUSSD: aPhone nr: aNr [
- ^ USSDProcedure initWith: (connection sccpHandler) phone: aPhone nr: aNr.
+ ^ (GSMConnection on: connection sccpHandler withPhone: aPhone)
+ setProc: (USSDProcedure initWithNr: aNr);
+ yourself
]
sendUSSD: aPhone nr: aNr [
- ^ (self doUSSD: aPhone nr: aNr) execute
+ ^ (self doUSSD: aPhone nr: aNr) waitForTermination.
]
]
diff --git a/WebApp.st b/WebApp.st
index 28de113..b476c77 100644
--- a/WebApp.st
+++ b/WebApp.st
@@ -110,11 +110,11 @@ Iliad.ILWidget subclass: ErrorWidget [
Iliad.ILWidget subclass: ProcedureWidget [
runProcedure: aBlock name: aName[
- | proc |
+ | conn |
[
- proc := aBlock value.
- proc run.
- self session procedures add: proc.
+ 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.')
@@ -167,23 +167,23 @@ ProcedureWidget subclass: USSDWidget [
Iliad.ILWidget subclass: ProcedureWidget [
showStatus: item on: form [
| status |
- status := item complete
+ status := item isComplete
ifTrue: [
- item success
- ifTrue: [item name, ' completed with success']
- ifFalse: [item name, ' completed with failure'].
+ item mainProc success
+ ifTrue: [item mainProc name, ' completed with success']
+ ifFalse: [item mainProc name, ' completed with failure'].
]
ifFalse: [
- item name, ' in-progress'
+ item mainProc name, ' in-progress'
].
form text: status.
form button
text: 'Remove';
action: [self markDirty.
- item complete
+ item isComplete
ifFalse: [
- item driver sendClearRequest.
+ item sendClearRequest.
].
self session procedures remove: item.].
]