aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2012-08-08 17:48:06 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2012-08-09 03:11:14 +0200
commit382a7b8e5bb7fcc355dd34ac96b9a515d36570af (patch)
treeecd2811b8edb8edb89dec151bf73a065f9889670
parentb4156fafbf0bcae58067c6a052ece14363e6e5fd (diff)
msc: Attempt to restart the existing MSC when an image is resumed
-rw-r--r--src/MSC.st67
1 files changed, 56 insertions, 11 deletions
diff --git a/src/MSC.st b/src/MSC.st
index f30ab35..c63a00a 100644
--- a/src/MSC.st
+++ b/src/MSC.st
@@ -163,6 +163,28 @@ Object subclass: MSCApplication [
<category: 'OsmoMSC-MSC'>
<comment: 'I am a MSC as I have the VLR/HLR and other instances'>
+ MSCApplication class >> new [
+ <category: 'creation'>
+ ^ super new
+ initialize;
+ yourself
+ ]
+
+ initialize [
+ <category: 'creation'>
+ ObjectMemory addDependent: self.
+ ]
+
+ update: aSymbol [
+ <category: 'initialize'>
+
+ "We need to re-initialize the sockets and state"
+ aSymbol = #returnFromSnapshot ifTrue: [
+ self returnedFromSnapshot.
+ ]
+ ]
+
+
hlr [ ^ hlr ifNil: [HLRLocalCollection new]]
vlr [ ^ vlr ifNil: [VLRLocalCollection new]]
@@ -170,6 +192,32 @@ Object subclass: MSCApplication [
bscConfig [ ^ bscConfig ifNil: [bscConfig := BSCConfig new]]
bscConHandler [ ^ bscConHandler ifNil: [bscConHandler := MSCBSCConnectionHandler initWith: self]]
+ returnedFromSnapshot [
+ <category: 'resume'>
+
+ mgcp isNil ifFalse: [
+ mgcp start
+ ].
+
+ "Stop the UDP processing and create a new transport. We might need
+ to do this in an atomic operation."
+ sip isNil ifFalse: [|old transport|
+ old := sip transport.
+ old stop.
+ transport := self newSipTransport.
+ transport start.
+ sip transport: transport].
+
+ "Make sure MGCP is running"
+ self mgcpCallAgent.
+
+ "Make sure we handle SIP"
+ self sipGateway.
+
+ self logNotice: 'Serving BSCs now' area: #msc.
+ [self serveBSC. 'MSC has exited' printNl] fork.
+ ]
+
mgcpCallAgent [
<category: 'MGCP-Audio'>
^ mgcp ifNil: [
@@ -178,11 +226,16 @@ Object subclass: MSCApplication [
yourself]
]
+ newSipTransport [
+ <category: 'private'>
+ ^ Osmo.SIPUdpTransport
+ startOn: self config sipIP port: self config sipPort.
+ ]
+
sipGateway [
<category: 'SIP-Audio'>
^ sip ifNil: [ | transport |
- transport := Osmo.SIPUdpTransport
- startOn: self config sipIP port: self config sipPort.
+ transport := self newSipTransport.
sip := Osmo.SIPUserAgent createOn: transport.
transport start.
sip]
@@ -233,15 +286,7 @@ Object subclass: MSCApplication [
addBSC: '127.0.0.1' withName: 'test1' andLac: 4711 sendOsmoRSIP: true;
addBSC: '10.240.240.1' withName: 'test2' andLac: 4712 sendOsmoRSIP: true.
- "Make sure MGCP is running"
- msc mgcpCallAgent.
-
- "Make sure we handle SIP"
- msc sipGateway.
-
- msc logNotice: 'Serving BSCs now' area: #msc.
- [msc serveBSC. 'MSC has exited' printNl] fork.
-
+ msc returnedFromSnapshot.
^ msc.
]
]