aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2012-12-04 15:30:06 +0100
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-03-13 09:17:37 +0100
commitb174396fe7794cc7f493229bdf1c5533b04ac658 (patch)
tree733faedd879b115a2d7051c927d0bb096985e65d
parent8f7a9ea8a5932610102065d19688989799a3cc15 (diff)
cm: Deal with CM Service Requests to a certain degree.
The CM Service Request accepts the service and then we need to wait for the real service. It could check if the requested service is matching with the 'inital' message but this is not done yet. The biggest issue is in the hand-over from CMServiceRequest to the real request. Right now a second SMS submit would break things up.
-rw-r--r--Start.st1
-rw-r--r--package.xml1
-rw-r--r--src/GSMCMServiceRequest.st93
-rw-r--r--src/GSMProcessor.st15
4 files changed, 107 insertions, 3 deletions
diff --git a/Start.st b/Start.st
index 67dcc32..c24b04f 100644
--- a/Start.st
+++ b/Start.st
@@ -10,6 +10,7 @@ Eval [
fileIn: 'src/GSMProcessor.st';
fileIn: 'src/GSMMOCall.st';
fileIn: 'src/GSMLURequest.st';
+ fileIn: 'src/GSMCMServiceRequest.st';
fileIn: 'src/BSCIPAConnection.st';
fileIn: 'src/MSC.st';
fileIn: 'src/SIPCall.st'.
diff --git a/package.xml b/package.xml
index d9bb8c7..ae51d7e 100644
--- a/package.xml
+++ b/package.xml
@@ -13,6 +13,7 @@
<filein>src/BSCSCCPHandler.st</filein>
<filein>src/GSMAuthenticator.st</filein>
<filein>src/GSMProcessor.st</filein>
+ <filein>src/GSMCMServiceRequest.st</filein>
<filein>src/GSMMOCall.st</filein>
<filein>src/GSMLURequest.st</filein>
<filein>src/BSCIPAConnection.st</filein>
diff --git a/src/GSMCMServiceRequest.st b/src/GSMCMServiceRequest.st
new file mode 100644
index 0000000..8ad724c
--- /dev/null
+++ b/src/GSMCMServiceRequest.st
@@ -0,0 +1,93 @@
+"
+ (C) 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/>.
+"
+
+OsmoGSM.GSM48CMServiceReq extend [
+ openTransactionOn: aCon sapi: aSapi [
+ | tran |
+ <category: '*-OsmoMSC-GSM'>
+
+ "This is weird. We can accept or reject the service."
+ tran := (GSMCMServiceRequest on: aSapi with: self ti)
+ con: aCon; yourself.
+ aCon openTransaction: tran with: self.
+ ]
+]
+
+OsmoGSM.GSM48MSG extend [
+ dispatchForCMOn: aCon [
+ <category: '*-OsmoMSC-GSM'>
+ self logError: '%1(srcref:%2) unknown dispatch for CM Service Request'
+ % {self class. aCon srcref} with: #bsc.
+ ^ false
+ ]
+]
+
+GSMTransaction subclass: GSMCMServiceRequest [
+ | timeout service state |
+ <category: 'OsmoMSC-GSM'>
+ <comment: 'I am used by the MS to ask for a service. I can check
+ if we want to have this service and Accept/Reject it. Atfer this
+ I need to wait a bit for the actual service to be started.'>
+
+ GSMCMServiceRequest class >> stateNull [ <category: 'states'> ^ #null ]
+ GSMCMServiceRequest class >> stateWaitService [ <category: 'states'> ^ #service ]
+
+ canHandle: aMsg sapi: aSapi [
+ "TODO: check if there are other transactions that should be called? Or
+ deal with it differently?"
+ ^ true
+ ]
+
+ initialize [
+ <category: 'creation'>
+ state := self class stateNull.
+ ]
+
+ start: aCMServiceRequest [
+ | accept |
+ state := self class stateWaitService.
+ accept := OsmoGSM.GSM48CMServiceAccept new.
+ timeout := Osmo.TimerScheduler instance
+ scheduleInSeconds: 5 block: [con takeLocks: [self timeOut]].
+ self nextPutSapi: accept.
+ ]
+
+ dispatch: aMsg [
+ | res |
+ "I am now getting the real MO-request. Let's see how we can
+ morph it into a real request."
+
+ res := aMsg dispatchForCMOn: self.
+ res ifFalse: [^self].
+
+ "We are done. Remove ourselves from the list."
+ timeout cancel.
+ con removeTransaction: self
+ ]
+
+ cancel [
+ timeout cancel.
+ ^ super cancel
+ ]
+
+ timeOut [
+ self logError: 'GSMCMServiceRequest(srcref:%1) timeout in state %2'
+ % {con srcRef. state} area: #bsc.
+ con removeTransaction: self.
+ ]
+]
diff --git a/src/GSMProcessor.st b/src/GSMProcessor.st
index 9a306af..1aa111c 100644
--- a/src/GSMProcessor.st
+++ b/src/GSMProcessor.st
@@ -79,6 +79,10 @@ GSM transaction on a given SAPI'>
yourself
]
+ canHandle: aMsg sapi: aSapi [
+ ^ self sapi = aSapi and: [self ti = aMsg ti].
+ ]
+
sapi [
<category: 'accessing'>
^ sapi
@@ -377,9 +381,12 @@ hosting various transactions and dispatching to them.'>
^ auth onData: aMsg.
].
- "Find an active transaction for this"
+ "Find an active transaction for this. TODO: For CM Service Request
+ we need to hand everything there. With multiple transactions we
+ should have a ranking. E.g. with bi-directional SMS this needs to be
+ handled specially. We need the existing transaction to take preference."
transactions do: [:each |
- (each sapi = aSapi and: [each ti = aMsg ti]) ifTrue: [
+ (each canHandle: aMsg sapi: aSapi) ifTrue: [
each dispatch: aMsg.
self checkRelease.
^ true.
@@ -714,6 +721,7 @@ hosting various transactions and dispatching to them.'>
authenticationAccepted [
<category: 'auth'>
"Must be locked"
+ "TODO: where to start the encryption? CM Service Accept/Ciphering Command?"
auth := nil.
state := self class stateAuth.
pending do: [:each |
@@ -726,7 +734,8 @@ hosting various transactions and dispatching to them.'>
"Must be locked"
"TODO"
- "Send a CM Service Reject/LU Reject to the phone"
+ "Send a CM Service Reject/LU Reject to the phone. Probably the
+ transaction should reject it."
"Close down the connection. FIXME: use a better error value"
self clearCommand: 0.