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

emergency: Be able to set-up an emergency call

Re-use the GSMMOCall for the emergency call setup. Add a special
route for the emergency setup as there is no number.
This commit is contained in:
Holger Hans Peter Freyther 2012-12-04 19:24:53 +01:00 committed by Holger Hans Peter Freyther
parent b174396fe7
commit bb38dd32ea
7 changed files with 81 additions and 4 deletions

View File

@ -11,6 +11,7 @@ Eval [
fileIn: 'src/GSMMOCall.st'; fileIn: 'src/GSMMOCall.st';
fileIn: 'src/GSMLURequest.st'; fileIn: 'src/GSMLURequest.st';
fileIn: 'src/GSMCMServiceRequest.st'; fileIn: 'src/GSMCMServiceRequest.st';
fileIn: 'src/GSMEmergencySetup.st';
fileIn: 'src/BSCIPAConnection.st'; fileIn: 'src/BSCIPAConnection.st';
fileIn: 'src/MSC.st'; fileIn: 'src/MSC.st';
fileIn: 'src/SIPCall.st'. fileIn: 'src/SIPCall.st'.

View File

@ -16,6 +16,7 @@
<filein>src/GSMCMServiceRequest.st</filein> <filein>src/GSMCMServiceRequest.st</filein>
<filein>src/GSMMOCall.st</filein> <filein>src/GSMMOCall.st</filein>
<filein>src/GSMLURequest.st</filein> <filein>src/GSMLURequest.st</filein>
<filein>src/GSMEmergencySetup.st</filein>
<filein>src/BSCIPAConnection.st</filein> <filein>src/BSCIPAConnection.st</filein>
<filein>src/MSC.st</filein> <filein>src/MSC.st</filein>
<filein>src/SIPCall.st</filein> <filein>src/SIPCall.st</filein>

View File

@ -37,6 +37,21 @@ OsmoGSM.GSM48MSG extend [
] ]
] ]
OsmoGSM.GSM48CCEmergencySetup extend [
dispatchForCMOn: aCM [
| call |
<category: '*-OsmoMSC-GSM'>
"Start the Emergency Call"
call := (GSMEmergencyCall on: 0 with: self ti)
con: aCM con; yourself.
aCM con openTransaction: call with: self.
"The CMServiceRequest transaction can go away now."
^ true
]
]
GSMTransaction subclass: GSMCMServiceRequest [ GSMTransaction subclass: GSMCMServiceRequest [
| timeout service state | | timeout service state |
<category: 'OsmoMSC-GSM'> <category: 'OsmoMSC-GSM'>

33
src/GSMEmergencySetup.st Normal file
View File

@ -0,0 +1,33 @@
"
(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/>.
"
GSMMOCall subclass: GSMEmergencyCall [
<category: 'OsmoMSC-GSM'>
<comment: 'I handle emergency calls'>
selectAudioRoute: aCCMessage [
"select route for this call, or release the call"
remoteLeg := con selectAudioRouteForEmergency: self.
remoteLeg isNil ifTrue: [
self logError:
'GSMEmergencyCall(srcref:%1) failed to select audio route.'
% {con srcRef} area: #bsc.
self releaseComplete.
].
]
]

View File

@ -244,9 +244,7 @@ GSMTransaction subclass: GSMMOCall [
con removeTransaction: self. con removeTransaction: self.
] ]
start: aCCMessage [ selectAudioRoute: aCCMessage [
<category: 'transaction'>
"select route for this call, or release the call" "select route for this call, or release the call"
remoteLeg := con selectAudioRoute: aCCMessage calledOrDefault leg: self. remoteLeg := con selectAudioRoute: aCCMessage calledOrDefault leg: self.
remoteLeg isNil ifTrue: [ remoteLeg isNil ifTrue: [
@ -254,8 +252,14 @@ GSMTransaction subclass: GSMMOCall [
'GSMMOCall(srcref:%1) failed to select audio route.' 'GSMMOCall(srcref:%1) failed to select audio route.'
% {con srcRef} area: #bsc. % {con srcRef} area: #bsc.
self releaseComplete. self releaseComplete.
^ self
]. ].
]
start: aCCMessage [
<category: 'transaction'>
self selectAudioRoute: aCCMessage.
remoteLeg isNil ifTrue: [^self].
"Failed to allocate an endpoint" "Failed to allocate an endpoint"
con allocateEndpoint isNil ifTrue: [ con allocateEndpoint isNil ifTrue: [

View File

@ -99,6 +99,11 @@ GSM transaction on a given SAPI'>
con := aCon. con := aCon.
] ]
con [
<category: 'creation'>
^ con
]
assignmentFailure [ assignmentFailure [
"The audio assignment has failed." "The audio assignment has failed."
] ]
@ -444,6 +449,12 @@ hosting various transactions and dispatching to them.'>
^ conManager msc mgcpCallAgent ^ conManager msc mgcpCallAgent
] ]
selectAudioRouteForEmergency: aLeg [
<category: 'call'>
^ conManager msc
selectAudioRouteForEmergency: self leg: aLeg.
]
selectAudioRoute: aPlan leg: aLeg [ selectAudioRoute: aPlan leg: aLeg [
<category: 'call'> <category: 'call'>
^ conManager msc ^ conManager msc

View File

@ -245,6 +245,18 @@ Object subclass: MSCApplication [
sip] sip]
] ]
selectAudioRouteForEmergency: aCon leg: aLeg [
^ (SIPMTCall
fromUser: 'sip:1000@sip.zecke.osmocom.org'
host: '127.0.0.1'
port: 5060
to: 'sip:911@127.0.0.1'
on: self sipGateway)
remoteLeg: aLeg;
yourself
]
selectAudioRoute: aCon plan: aPlan leg: aLeg [ selectAudioRoute: aCon plan: aPlan leg: aLeg [
| nr | | nr |
"TODO: Very simple and hardcoded rule" "TODO: Very simple and hardcoded rule"