aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2011-09-24 12:00:37 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2011-09-24 12:00:37 +0200
commita5154930574dfaa408502bbfd8531dcf6f730376 (patch)
tree376eaa2918794e03ad7f3d666b11e89b80dabb4f /src
parentf2f0b71b047ae6a5a680be054f825392801a1433 (diff)
misc: Move the sources into a subdirectory
I am still searching for a better way to group these files for their specific main functionality.
Diffstat (limited to 'src')
-rw-r--r--src/BSCConfig.st102
-rw-r--r--src/BSCIPAConnection.st183
-rw-r--r--src/BSCListener.st79
-rw-r--r--src/GSMMOCall.st284
-rw-r--r--src/GSMProcessor.st640
-rw-r--r--src/HLR.st72
-rw-r--r--src/Logging.st61
-rw-r--r--src/MSC.st242
-rw-r--r--src/SIPCall.st81
-rw-r--r--src/VLR.st109
10 files changed, 1853 insertions, 0 deletions
diff --git a/src/BSCConfig.st b/src/BSCConfig.st
new file mode 100644
index 0000000..6861c0f
--- /dev/null
+++ b/src/BSCConfig.st
@@ -0,0 +1,102 @@
+"
+ (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: #Sockets.
+
+Object subclass: BSCConfigItem [
+ | peer token name lac connected |
+ <category: 'MSC-BSC'>
+ <comment: 'I hold the configuration for one BJSC Item. It consists of the
+peer address, the lac, if it is connected'>
+
+ BSCConfigItem class >> initWith: aPeer name: aName [
+ ^ self new
+ peer: aPeer; name: aName; lac: -1; connected: false; yourself
+ ]
+
+ BSCConfigItem class >> resolveAddress: aPeer [
+ ^ aPeer isString
+ ifTrue: [Sockets.SocketAddress byName: aPeer]
+ ifFalse: [aPeer].
+ ]
+
+ peer [ <category: 'accessing'> ^ peer ]
+ peer: aPeer [
+ <category: 'private'>
+
+ peer := self class resolveAddress: aPeer.
+ ]
+
+ name [ <category: 'accessing'> ^ name ]
+ name: aName [
+ <category: 'private'>
+ name := aName.
+ ]
+
+ lac [ <category: 'accessing'> ^ lac ]
+ lac: aLac [
+ <category: 'private'>
+ lac := aLac.
+ ]
+
+ connected [ <category: 'accessing'> ^ connected ]
+ connected: aState [
+ <category: 'private'>
+ connected := aState.
+ ]
+]
+
+Object subclass: BSCConfig [
+ | bscList |
+ <category: 'MSC-BSC'>
+ <comment: 'I know the BSCs that can connect to me'>
+
+ removeBSC: aPeer [
+ | peer |
+ peer := BSCConfigItem resolveAddress: aPeer.
+ self bscList removeAllSuchThat: [:element | element peer = peer].
+ ]
+
+ removeBSCByLac: aLac [
+ self bscList removeAllSuchThat: [:element | element lac = aLac].
+ ]
+
+ addBSC: ip withName: aName andLac: aLac [
+ | addr bsc |
+ <category: 'management'>
+ "Make sure that no one with the same IP or LAC registers"
+
+ addr := Sockets.SocketAddress byName: ip.
+ bsc := BSCConfigItem initWith: addr name: aName.
+ bsc lac: aLac.
+
+ (self bscList anySatisfy: [:each | each peer = addr ])
+ ifTrue: [
+ self error: 'The address needs to be unique'.
+ ].
+
+ (self bscList anySatisfy: [:each | each lac = aLac])
+ ifTrue: [
+ self error: 'The lac needs to be unique'.
+ ].
+
+ self bscList add: bsc.
+ ]
+
+ bscList [ ^ bscList ifNil: [bscList := OrderedCollection new]]
+]
diff --git a/src/BSCIPAConnection.st b/src/BSCIPAConnection.st
new file mode 100644
index 0000000..d72e927
--- /dev/null
+++ b/src/BSCIPAConnection.st
@@ -0,0 +1,183 @@
+"
+ (C) 2010-2011 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: 'OsmoMGCP';
+ fileInPackage: 'OsmoNetwork'.
+
+OsmoGSM.SCCPHandler subclass: BSCSCCPHandler [
+ | bsc msc |
+ <comment: 'I handle SCCP for the MSC/BSC connection'>
+
+ BSCSCCPHandler class >> initWith: aBSC msc: aMSC [
+ ^ self new
+ instVarNamed: #bsc put: aBSC;
+ instVarNamed: #msc put: aMSC;
+ yourself
+ ]
+
+ connectionSpecies [
+ ^ GSMProcessor
+ ]
+
+ bsc [
+ <category: 'accessing'>
+ ^ bsc
+ ]
+
+ msc [
+ <category: 'accessing'>
+ ^ msc
+ ]
+
+ handleMsg: aMsg [
+ ^ super handleMsg: aMsg.
+ ]
+
+ newConnection: aConnection [
+ self logNotice: 'New incoming SCCP connection %1 on the BSC %2'
+ % {aConnection srcRef. bsc lac} area: #bsc.
+ ^ super newConnection: aConnection.
+ ]
+]
+
+Object subclass: BSCConnection [
+ | config msc trunk |
+
+ BSCConnection class >> createOn: aConfig msc: aMsc [
+ <category: 'creation'>
+ ^ self new
+ instVarNamed: #config put: aConfig;
+ instVarNamed: #msc put: aMsc;
+ initialize;
+ yourself
+ ]
+
+ initialize [
+ <category: 'creation'>
+ "I try to initialize the trunk. Right now I force the usage
+ of UDP to the given port and do not support the nat traversal. I
+ also hardcode the kind of audio."
+ trunk := Osmo.MGCPDSTrunk createWithDest: config peer printString trunkNr: 1.
+ (trunk endpointAt: 1) tryBlock.
+ ]
+
+ config [
+ <category: 'accessing'>
+ ^ config
+ ]
+
+ msc [
+ <category: 'accessing'>
+ ^ msc
+ ]
+
+ trunk [
+ <category: 'accessing'>
+ ^ trunk
+ ]
+]
+
+BSCConnection subclass: BSCIPAConnection [
+ | socket demuxer writeQueue muxer dispatcher sccp tx terminated ipa |
+ <comment: 'I represent one Connection to a BSC and use the IPA
+ protocol to exchange messages. I will be executed from within
+ a thread and can do a blocking read from in here.'>
+
+ BSCIPAConnection class >> createOn: aSocket withConfig: aConfig msc: aMsc [
+ ^ (self createOn: aConfig msc: aMsc)
+ socket: aSocket;
+ yourself
+ ]
+
+ BSCIPAConnection class >> terminate: aProc [
+ "Make sure it is dead!"
+ aProc ifNil: [^true].
+
+ [aProc isTerminated] whileFalse: [aProc terminate].
+ ]
+
+ lac [ ^ config lac ]
+
+ socket: aSocket [
+ socket := aSocket.
+ writeQueue := SharedQueue new.
+
+ demuxer := Osmo.IPADemuxer initOn: socket.
+ muxer := Osmo.IPAMuxer initOn: writeQueue.
+
+ dispatcher := Osmo.IPADispatcher new.
+ dispatcher initialize.
+
+ ipa := Osmo.IPAProtoHandler new.
+ ipa registerOn: dispatcher.
+ ipa muxer: muxer.
+ ipa token: 'abc'.
+
+ sccp := BSCSCCPHandler initWith: self msc: msc.
+ sccp registerOn: dispatcher.
+ sccp connection: self.
+
+ "Drain the send queue in a new process"
+ tx := [
+ [[
+ | msg |
+ msg := writeQueue next.
+ socket nextPutAllFlush: msg.
+ ] repeat.
+ ] ensure: [
+ self logNotice: 'BSC TX queue lac: %1 finished' % {self lac} area: #bsc]
+ ] fork.
+
+ ]
+
+ send: aMsg with: aType [
+ terminated = true ifTrue: [^false].
+
+ muxer nextPut: aMsg with: aType.
+ ]
+
+ process [
+ "Drive the BSC process. This will send/queue messages"
+
+ socket logNotice: 'Processing for lac %1' % {self lac} area: #bsc.
+
+ self send: {Osmo.IPAConstants msgIdAck} asByteArray with: Osmo.IPAConstants protocolIPA.
+
+ [
+ self processOne.
+ ] repeat.
+
+
+ socket close.
+ ]
+
+ processOne [
+ | msg |
+ msg := demuxer next.
+ OsmoDispatcher dispatchBlock: [dispatcher dispatch: msg first with: msg second.]
+ ]
+
+ terminateAll [
+ "Bring down everything that happens for this BSC. This is a reset"
+ terminated := true.
+ self logNotice: 'BSC lac: %1 terminating.' % {self lac} area: #bsc.
+ self class terminate: tx.
+ OsmoDispatcher dispatchBlock: [sccp linkSetFailed].
+ ]
+]
diff --git a/src/BSCListener.st b/src/BSCListener.st
new file mode 100644
index 0000000..b0e94ff
--- /dev/null
+++ b/src/BSCListener.st
@@ -0,0 +1,79 @@
+"
+ (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: 'Sockets'.
+
+Object subclass: BSCListener [
+ | ip port socket handler |
+
+ <comment: 'I listen for incoming BSC connections and will
+ authenticate them based on a definable criteria. Right now
+ this is based on IP address'>
+
+ BSCListener class >> initWith: bscIP port: bscPort handler: aHandler [
+ ^ self new
+ initSocket: bscIP port: bscPort;
+ handler: aHandler;
+ start;
+ yourself
+ ]
+
+ handler: aHandler [
+ handler := aHandler.
+ ]
+
+ initSocket: anIP port: aPort [
+ ip := anIP.
+ port := aPort.
+ ]
+
+ serve [
+ [true] whileTrue: [
+ [ | con |
+ socket waitForConnection.
+ con := socket accept.
+ con ifNil: [
+ self logNotice: 'BSC-Socket: Connection failed. Will return.' area: #bsc.
+ ^ false
+ ].
+
+ handler isNil
+ ifTrue: [con close]
+ ifFalse:[handler newConnection: con].
+ ] on: SystemExceptions.FileError do: [:each |
+ self logNotice: 'BSC-Socket: FileError on connection handling.' area: #bsc.
+ ^ false.
+ ].
+ ]
+ ]
+
+ start [
+ [
+ socket := Sockets.ServerSocket
+ port: port bindTo: (Sockets.SocketAddress byName: ip).
+ ] on: SystemExceptions.FileError do: [:e |
+ e logException: 'BSC-Socket: Failed to bind.' area: #bsc.
+ ]
+ ]
+
+ stop [
+ "The serve function will now get a FileError"
+ self logNotice: 'BSC-Socket: Asked to close the connection.' area: #bsc.
+ socket close.
+ ]
+]
diff --git a/src/GSMMOCall.st b/src/GSMMOCall.st
new file mode 100644
index 0000000..0db182a
--- /dev/null
+++ b/src/GSMMOCall.st
@@ -0,0 +1,284 @@
+"
+ (C) 2011 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.GSM48MSG extend [
+ dispatchMoCall: aCon [
+ aCon moUnknown: self.
+ ]
+]
+
+OsmoGSM.GSM48CCConnectAck extend [
+ dispatchMoCall: aCon [
+ aCon moConnectAck: self.
+ ]
+]
+
+OsmoGSM.GSM48CCDisconnect extend [
+ dispatchMoCall: aCon [
+ aCon moDisconnect: self.
+ ]
+]
+
+OsmoGSM.GSM48CCRelease extend [
+ dispatchMoCall: aCon [
+ aCon moRelease: self.
+ ]
+]
+
+OsmoGSM.GSM48CCReleaseCompl extend [
+ dispatchMoCall: aCon [
+ aCon moReleaseCompl: self.
+ ]
+]
+
+OsmoGSM.GSM48CCStatus extend [
+ dispatchMoCall: aCon [
+ aCon moStatus: self.
+ ]
+]
+
+OsmoGSM.GSM48CCSetup extend [
+ openTransactionOn: aCon sapi: aSapi [
+ | tran |
+ tran := (GSMMOCall on: aSapi with: self ti)
+ con: aCon;
+ yourself.
+ aCon addTransaction: tran.
+ tran start: self.
+ ]
+]
+
+GSMTransaction subclass: GSMMOCall [
+ | state wait_for_ass remoteLeg |
+ <comment: 'I handle Mobile-Originated calls as of 5.2.1 of GSM 04.08. I should
+ represent the states found in Figure 5.1b/3GPP TS 04.08: Overview call controll
+ protocol/Network side. Right now the set of states is incomplete and is mixed
+ for MO and MT. It is not very clear if the text and the state machine fit together.'>
+
+ GSMMOCall class >> stateNull [ <category: 'states'> ^ #null ]
+ GSMMOCall class >> stateProceeding [ <category: 'states'> ^ #proceeding ]
+ GSMMOCall class >> stateConnectInd [ <category: 'states'> ^ #connect_indication ]
+ GSMMOCall class >> stateActive [ <category: 'states'> ^ #active ]
+ GSMMOCall class >> stateDisconnInd [ <category: 'states'> ^ #disconn_ind ]
+ GSMMOCall class >> stateReleaseReq [ <category: 'states'> ^ #release_req ]
+ GSMMOCall class >> stateReleaseCompl [ <category: 'states'> ^ #release_compl ]
+
+ initialize [
+ <category: 'creation'>
+ state := self class stateNull.
+ ]
+
+ nextPutSapi: aMsg [
+ <category: 'output'>
+ aMsg ti: (ti bitOr: 8).
+ aMsg seq: 0.
+ ^ super nextPutSapi: aMsg.
+ ]
+
+ netAlerting [
+ <category: 'external'>
+ "I am called by the other side of the call"
+
+ (state = self class stateProceeding) ifTrue: [
+ con sendMDCX: remoteLeg sdpAlert state: 'recvonly'.
+ self sendAlerting.
+ ].
+ ]
+
+ netConnect [
+ <category: 'external'>
+ "I am called by the other side of the call. I will need to get
+ the SDP file of this side to send a MGCP message down the stream."
+
+ (state = self class stateProceeding) ifTrue: [
+ state := self class stateConnectInd.
+ con sendMDCX: remoteLeg sdp state: 'sendrecv'.
+ self sendConnect.
+ ].
+ ]
+
+ netTerminate [
+ <category: 'external'>
+ "The other side of the call has terminated, let
+ us do the clean up."
+ remoteLeg isNil ifFalse: [
+ remoteLeg := nil.
+ state := self class stateDisconnInd.
+ self sendDisconnect: #(16rE1 16r90)
+ ].
+ ]
+
+ moConnectAck: aMsg [
+ <category: 'mo-message'>
+ (state = self class stateConnectInd) ifTrue: [
+ self logNotice: 'GSMMOCall(srcref:%1) call is connected.'
+ % {con srcRef} area: #bsc.
+ state := self class stateActive.
+ ].
+ ]
+
+ moDisconnect: aMsg [
+ <category: 'mo-message'>
+ state := self class stateDisconnInd.
+ self sendRelease: #(16rE1 16r90).
+
+ "Disconnect the remote"
+ remoteLeg isNil ifFalse: [
+ remoteLeg netTerminate.
+ remoteLeg := nil.
+ ].
+ ]
+
+ moRelease: aMsg [
+ <category: 'mo-message'>
+ state = self class stateDisconnInd ifFalse: [
+ self logError: 'GSMMOCall(srcref:%1) release in state %2'
+ % {con srcRef. self state} area: #bsc.
+ ].
+
+ self releaseComplete.
+ ]
+
+ moReleaseCompl: aMsg [
+ <category: 'mo-message'>
+ self cancel.
+ con removeTransaction: self.
+ ]
+
+ moUnknown: aMsg [
+ <category: 'mo-message'>
+ ^ self logUnknown: aMsg.
+ ]
+
+ moStatus: aMsg [
+ <category: 'mo-message'>
+ "We did something wrong, just give up and see how it can be fixed."
+ self logError: 'GSMOCall(srcref:%1) something wrong with call state.'
+ % {con srcRef} area: #bsc.
+ self cancel.
+ con removeTransaction: self.
+ ]
+
+ dispatch: aMsg [
+ aMsg dispatchMoCall: self.
+ ]
+
+ sendReleaseComplete: aCause [
+ | rlc |
+ <category: 'gsm-routines'>
+
+ rlc := OsmoGSM.GSM48CCReleaseCompl new.
+ rlc causeOrDefault data: aCause.
+ self nextPutSapi: rlc.
+ ]
+
+ sendRelease: aCause [
+ | rel |
+ <category: 'gsm-routines'>
+ rel := OsmoGSM.GSM48CCRelease new.
+ rel causeOrDefault data: aCause.
+ self nextPutSapi: rel.
+ ]
+
+ sendProceeding [
+ | msg |
+ <category: 'gsm-routines'>
+
+ msg := OsmoGSM.GSM48CCProceeding new.
+ self nextPutSapi: msg.
+ ]
+
+ sendAlerting [
+ | msg |
+ <category: 'gsm-routines'>
+
+ msg := OsmoGSM.GSM48CCAlerting new.
+ self nextPutSapi: msg.
+ ]
+
+ sendConnect [
+ | msg |
+ <category: 'gsm-routines'>
+ msg := OsmoGSM.GSM48CCConnect new.
+ self nextPutSapi: msg.
+ ]
+
+ sendDisconnect: aCause [
+ | msg |
+ <category: 'gsm-routines'>
+
+ msg := OsmoGSM.GSM48CCDisconnect new.
+ msg cause data: aCause.
+ self nextPutSapi: msg.
+ ]
+
+ releaseComplete [
+ <category: 'transaction'>
+
+ state := self class stateReleaseCompl.
+ self sendReleaseComplete: #(16rE1 16r83).
+ self cancel.
+ con removeTransaction: self.
+ ]
+
+ start: aCCMessage [
+ <category: 'transaction'>
+
+ "select route for this call, or release the call"
+ remoteLeg := con selectAudioRoute: aCCMessage calledOrDefault leg: self.
+ remoteLeg isNil ifTrue: [
+ self logError:
+ 'GSMMOCall(srcref:%1) failed to select audio route.'
+ % {con srcRef} area: #bsc.
+ self releaseComplete.
+ ^ self
+ ].
+
+ "Failed to allocate an endpoint"
+ con allocateEndpoint isNil ifTrue: [
+ self releaseComplete.
+ ^ self
+ ].
+
+ "We are waiting for an assignment"
+ wait_for_ass := true.
+ state := self class stateProceeding.
+ self sendProceeding.
+
+ con sendAssignment.
+ ]
+
+ cancel [
+ remoteLeg ifNotNil: [remoteLeg netTerminate].
+ ^ super cancel
+ ]
+
+ assignmentFailure [
+ "The assignment failed, let's see if it could be for us"
+ wait_for_ass ifTrue: [
+ remoteLeg := nil.
+ self releaseComplete.
+ ]
+ ]
+
+ assignmentSuccess [
+ wait_for_ass := false.
+ remoteLeg createCall: con sdpFile.
+ ]
+]
+
diff --git a/src/GSMProcessor.st b/src/GSMProcessor.st
new file mode 100644
index 0000000..9b7a0b8
--- /dev/null
+++ b/src/GSMProcessor.st
@@ -0,0 +1,640 @@
+"
+ (C) 2010-2011 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: 'OsmoGSM'.
+
+OsmoGSM.BSSAPMessage extend [
+ dispatchTrans: aCon [
+ aCon bssapUnknownData: self
+ ]
+]
+
+OsmoGSM.BSSAPManagement extend [
+ dispatchTrans: aCon [
+ self dispatchMAP: aCon.
+ ]
+
+ dispatchMAP: aCon [
+ (Dictionary from: {
+ OsmoGSM.GSM0808Helper msgComplL3 -> #mapLayer3:.
+ OsmoGSM.GSM0808Helper msgClearReq -> #mapClearReq:.
+ OsmoGSM.GSM0808Helper msgClearComp -> #mapClearCompl:.
+ OsmoGSM.GSM0808Helper msgCipherModeCmpl -> #mapCipherModeCompl:.
+ OsmoGSM.GSM0808Helper msgAssComplete -> #mapAssComplete:.
+ OsmoGSM.GSM0808Helper msgAssFailure -> #mapAssFailure:.
+ }) at: self data type ifPresent: [:sel |
+ ^ aCon perform: sel with: self.
+ ].
+
+ ^ aCon mapUnknown: self.
+ ]
+]
+
+OsmoGSM.BSSAPDTAP extend [
+ dispatchTrans: aCon [
+ aCon dispatchDTAP: self.
+ ]
+]
+
+OsmoGSM.GSM48MSG extend [
+ openTransactionOn: aCon sapi: aSapi [
+ self logError: 'Can not open transaction for %1' % {self class} area: #bsc.
+ ]
+]
+
+Object subclass: GSMTransaction [
+ | sapi ti con |
+ <comment: 'I am the base for everything that goes on in a
+GSM transaction on a given SAPI'>
+
+ GSMTransaction class >> on: sapi with: ti [
+ <category: 'creation'>
+ ^ self new
+ instVarNamed: #sapi put: sapi;
+ instVarNamed: #ti put: ti;
+ initialize;
+ yourself
+ ]
+
+ sapi [
+ <category: 'accessing'>
+ ^ sapi
+ ]
+
+ ti [
+ "TODO: This should somehow include the size of the allocation"
+ <category: 'accessing'>
+ ^ ti
+ ]
+
+ con: aCon [
+ <category: 'creation'>
+ con := aCon.
+ ]
+
+ assignmentFailure [
+ "The audio assignment has failed."
+ ]
+
+ assignmentSuccess [
+ "The assignment succeeded and there is now a specific channel"
+ ]
+
+ cancel [
+ ]
+
+ dispatch: aMsg [
+ self subclassResponsibility
+ ]
+
+ nextPutSapi: aMsg [
+ <category: 'output'>
+ ^ self nextPut: (OsmoGSM.BSSAPDTAP initWith: aMsg linkIdentifier: sapi)
+ ]
+
+ nextPut: aMsg [
+ <category: 'output'>
+ con nextPutData: aMsg
+ ]
+
+ logUnknown: aMsg [
+ <category: 'logging'>
+ self logError: 'Unknown message %1' % {aMsg class}.
+ ]
+]
+
+GSMTransaction subclass: GSMLURequest [
+ <comment: 'I handle a Location Updating Request'>
+]
+
+OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [
+ | transactions state endp connId mgcp_trans |
+
+ <comment: 'I am driving a SCCP Connection. This consists of being
+hosting various transactions and dispatching to them.'>
+ <import: OsmoGSM>
+
+ GSMProcessor class >> stateInitial [<category: 'states'> ^ 0 ]
+ GSMProcessor class >> stateAcked [<category: 'states'> ^ 1 ]
+ GSMProcessor class >> stateRelease [<category: 'states'> ^ 2 ]
+ GSMProcessor class >> stateError [<category: 'states'> ^ 3 ]
+
+ GSMProcessor class >> createAssignment: aMul timeslot: aTs [
+ | ass |
+ <category: 'audio-connect'>
+ ass := IEMessage initWith: GSM0808Helper msgAssRequest.
+ ass
+ addIe: ((GSM0808ChannelTypeIE
+ initWith: GSM0808ChannelTypeIE speechSpeech
+ audio: GSM0808ChannelTypeIE chanSpeechFullPref)
+ audioCodecs: {GSM0808ChannelTypeIE speechFullRateVersion3.
+ GSM0808ChannelTypeIE speechHalfRateVersion3};
+ yourself);
+ addIe: (GSM0808CICIE initWithMultiplex: aMul timeslot: aTs).
+ ^ ass
+ ]
+
+ initialize [
+ <category: 'creation'>
+ transactions := OrderedCollection new.
+ state := self class stateInitial.
+ ^ super initialize.
+ ]
+
+ data: aData [
+ | msg bssmap data |
+ <category: 'input'>
+
+ "The first message should be a Complete Layer3 Information"
+ [
+ aData data dispatchTrans: self.
+ ] on: Error do: [:e |
+ e logException: 'Failed to dispatch: %1' % {e tag} area: #bsc.
+ self forceClose.
+ ]
+ ]
+
+ bssapUnknownData: aData [
+ <category: 'BSSMAP'>
+ "This is now the GSM data"
+ self forceClose.
+ ]
+
+ mapLayer3: bssap [
+ | layer3 |
+ <category: 'BSSMAP'>
+
+ "Check and move state"
+ 'Dispatching GSM' printNl.
+ sem critical: [
+ self verifyState: [state = self class stateInitial].
+ state := self class stateAcked.
+ ].
+
+ "TODO: Add verifications"
+ bssap data findIE: OsmoGSM.GSMCellIdentifier elementId ifAbsent: [
+ ^ self logError: 'CellIdentifier not present on %1' % {self srcRef} area: #msc.
+ ].
+
+ layer3 := bssap data findIE: OsmoGSM.GSMLayer3Info elementId ifAbsent: [
+ ^ self logError: 'Layer3Infor not present on %1' % {self srcRef} area: #msc.
+ ].
+
+ 'Dispatching GSM' printNl.
+ sem critical: [self dispatchGSM: layer3 data sapi: 0].
+ ]
+
+ mapClearReq: aData [
+ <category: 'BSSMAP'>
+ 'CLEAR Request' printNl.
+
+ sem critical: [
+ self verifyState:
+ [(state > self class stateInitial) and: [state < self class stateError]].
+ self clearCommand: 0.
+ ]
+ ]
+
+ mapClearCompl: aData [
+ <category: 'BSSMAP'>
+ sem critical: [
+ self verifyState: [state = self class stateRelease].
+ self releaseAudio.
+ self release.
+ ].
+ ]
+
+ mapCipherModeCompl: aData [
+ <category: 'BSSMAP'>
+ 'CIPHER MODE COMPL' printNl.
+ aData inspect.
+ ]
+
+ terminate [
+ <category: 'private'>
+ "Cancel all transactions"
+ sem critical: [
+ transactions do: [:each |
+ [each cancel] on: Error do: [:e |
+ e logException: 'GSMProc(srcref:%1) failed cancel: %2' %
+ {self srcRef. each class} area: #bsc.
+ ]
+ ].
+
+ transactions := OrderedCollection new.
+ self releaseAudio.
+ ].
+ ]
+
+ verifyState: aBlock [
+ <category: 'private'>
+ "Must be locked."
+
+ aBlock value ifFalse: [
+ self logError: 'GSMProc(srcref:%1) wrong state: %2.' % {self srcRef. state} area: #bsc.
+ ^ self error: 'Failed to verify the state.'.
+ ].
+ ]
+
+ forceClose [
+ <category: 'private'>
+ sem critical: [
+ state = self class stateError ifTrue: [
+ "Already closing down"
+ ^ false
+ ].
+
+ state := self class stateError.
+ self release
+ ].
+ ]
+
+ clearCommand: aCause [
+ | msg |
+ <category: 'private'>
+ "Must be locked"
+
+ "Already clearing it once"
+ state >= self class stateRelease ifTrue: [
+ ^ true.
+ ].
+
+ state := self class stateRelease.
+
+ msg := OsmoGSM.IEMessage initWith: OsmoGSM.GSM0808Helper msgClear.
+ msg addIe: (OsmoGSM.GSMCauseIE initWith: aCause).
+ self nextPutData: (OsmoGSM.BSSAPManagement initWith: msg).
+ ]
+
+ checkRelease [
+ "Check if things can be released now"
+ <category: 'private'>
+ "Must be locked"
+
+ "No more transactions, clean things up"
+ transactions isEmpty ifTrue: [
+ self clearCommand: 9.
+ ].
+ ]
+
+ addTransaction: aTran [
+ <category: 'private'>
+ "Must be locked"
+ self logDebug: 'GSMProc(srcref:%1) adding transaction %2' % {self srcRef. aTran class} area: #bsc.
+ transactions add: aTran.
+ ]
+
+ removeTransaction: aTran [
+ <category: 'private'>
+ "Must be locked"
+ self logDebug: 'GSMProc(srcref:%1) removing transaction %2' % {self srcRef. aTran class} area: #bsc.
+ transactions remove: aTran ifAbsent: [
+ self logError: 'GSMProc(srcref:%1) trans not found %2' % {self srcRef. aTran class} area: #bsc.
+ ].
+
+ self checkRelease.
+ ]
+
+ dispatchDTAP: aMsg [
+ <category: 'private'>
+ sem critical: [self dispatchGSM: aMsg data sapi: aMsg sapi]
+ ]
+
+ dispatchGSM: aMsg sapi: aSapi [
+ <category: 'private'>
+ "Must be locked"
+
+ "Find an active transaction for this"
+ transactions do: [:each |
+ (each sapi = aSapi and: [each ti = aMsg ti]) ifTrue: [
+ each dispatch: aMsg.
+ self checkRelease.
+ ^ true.
+ ].
+ ].
+
+ aMsg openTransactionOn: self sapi: 0.
+ self checkRelease.
+ ]
+
+ "Audio handling"
+ allocateEndpoint [
+ <category: 'audio'>
+ "The endpoint allocation is a complicated and async process. It
+ starts with picking a timeslot to the BSC, it continues with trying
+ to assign the timeslot via MGCP, then will send the ASSIGNMENT
+ COMMAND. This means even with multiple phone calls there will be
+ only one assigned timeslot.
+
+ To make things more complicated we might have a CRCX or such
+ pending while we need to tear things down. This means we will
+ need to check in the transaction complete/timeout what we need to
+ do next and also keep a list of transactions."
+
+
+ "Right now only one call is allowed. we have no support of switching
+ calls during the call."
+
+ self trunk critical: [
+ endp ifNotNil: [
+ self logError: 'GSMProc(srcref:%1) already has endpoint.'
+ % {self srcRef} area: #bsc.
+ ^ nil].
+
+ endp := self trunk allocateEndpointIfFailure: [
+ self logError: 'GSMProc(srcref:%1) no endpoint availabble.'
+ % {self srcRef} area: #bsc.
+ ^ nil].
+ ].
+ ]
+
+ generateCallId [
+ <category: 'audio'>
+ "I can be up to 32 chars of hexdigits. No need to be globally unique"
+ ^ (Random between: 10000000 and: 999999999) asString
+ ]
+
+ trunk [
+ <category: 'audio'>
+ ^ conManager bsc trunk.
+ ]
+
+ callAgent [
+ <category: 'audio'>
+ ^ conManager msc mgcpCallAgent
+ ]
+
+ selectAudioRoute: aPlan leg: aLeg [
+ ^ conManager msc
+ selectAudioRoute: self plan: aPlan leg: aLeg
+ ]
+
+ releaseAudio [
+ "I try to release things right now."
+ <category: 'audio'>
+ self trunk critical: [
+ endp ifNil: [^self].
+ endp isUnused ifTrue: [^self].
+
+ "Check if we have ever sent a CRCX, if not release it"
+ endp isReserved ifTrue: [
+ endp callId isNil
+ ifTrue: [
+ self logDebug:
+ 'GSMProc(srcref:%1) MGCP CRCX never sent.'
+ % {self srcRef} area: #bsc.
+ endp used. endp free]
+ ifFalse: [
+ self logDebug:
+ 'GSMProc(srcref:%1) MGCP pending CallID:%2. no release.'
+ % {self srcRef. endp callId} area: #bsc.].
+ ^ self
+ ].
+
+ (endp isUsed and: [endp callId isNil not]) ifTrue: [
+ self sendDLCX.
+ ].
+ ].
+ ]
+
+ sendAssignment [
+ | ass |
+ <category: 'audio-connect'>
+
+ "TODO: Maybe start a timer but we are guarded here anyway."
+ ass := self class createAssignment: endp multiplex timeslot: endp timeslot - 1.
+ self nextPutData: (BSSAPManagement initWith: ass).
+ ]
+
+ mapAssComplete: aData [
+ <category: 'audio-connect'>
+
+ sem critical: [self trunk critical: [
+ endp callId isNil ifTrue: [self sendCRCX].
+ ]].
+ ]
+
+ mapAssFailure: aData [
+ <category: 'audio-connect'>
+ sem critical: [self trunk critical: [
+ self logError: 'GSMProc(srcref:%1) GSM0808 Assignment failed.'
+ % {self srcRef} area: #bsc.
+ self assignmentFailure.]]
+ ]
+
+ assignmentSuccess [
+ <category: 'audio-connect'>
+
+ transactions do: [:each |
+ each assignmentSuccess.
+ ]
+ ]
+
+ assignmentFailure [
+ <category: 'audio-connect'>
+ "Tell the transactions that there will be no audio."
+
+ transactions do: [:each |
+ each assignmentFailure.
+ ]
+ ]
+
+ takeLocks: aBlock [
+ <category: 'audio-locking'>
+ "Take the locks in lock-order for audio callbacks"
+ conManager critical: [
+ sem critical: [
+ self trunk critical: [
+ aBlock value]]]
+ ]
+
+ mgcpQueueTrans: aTrans [
+ <category: 'audio-connect'>
+ mgcp_trans add: aTrans.
+ mgcp_trans size = 1 ifTrue: [
+ aTrans start.]
+ ]
+
+ mgcpTransFinished: aTrans [
+ <category: 'audio-connect'>
+ mgcp_trans first = aTrans ifFalse: [
+ self logError: 'GSMProc(srcref:%1) wrong MGCP transaction finished.'
+ % {self srcRef} area: #bsc.
+ ^false].
+
+ mgcp_trans removeFirst.
+ mgcp_trans isEmpty ifFalse: [
+ mgcp_trans first start.
+ ].
+ ]
+
+ sendCRCX [
+ | trans crcx |
+ <category: 'audio-connect'>
+ endp callId: self generateCallId.
+ trans := Osmo.MGCPTransaction on: endp of: self callAgent.
+ crcx := (Osmo.MGCPCRCXCommand createCRCX: endp callId: endp callId)
+ parameterAdd: 'M: recvonly';
+ yourself.
+ trans command: crcx.
+ trans onResult: [:endp :result |
+ self takeLocks: [self crcxResult: result. self mgcpTransFinished: trans]].
+ trans onTimeout: [:endp |
+ self takeLocks: [self crcxTimeout. self mgcpTransFinished: trans]].
+ mgcp_trans := OrderedCollection with: trans.
+ trans start.
+
+ self logDebug: 'GSMProc(srcref:%1) CRCX on %2 with CallID: %3'
+ % {self srcRef. endp endpointName. endp callId} area: #bsc.
+ ]
+
+ crcxResult: aResult [
+ <category: 'audio-connect'>
+
+ "save the sdp and callId"
+ endp used.
+
+ "Did this succeed?"
+ aResult isSuccess ifFalse: [
+ self logError: 'GSMProc(srcref:%1) CRCX failed aCode: %2'
+ % {self srcRef. aResult code} area: #bsc.
+ self freeEndpoint.
+ self assignmentFailure.
+ ^ self
+ ].
+
+ "Check if there is a connId"
+ connId := aResult parameterAt: 'I' ifAbsent: [
+ self logError: 'GSMProc(srcref:%1) CRCX lacks connId'
+ % {self srcRef} area: #bsc.
+ self freeEndpoint.
+ self assignmentFailure.
+ ^ self
+ ].
+
+ "Assign the current SDP file"
+ endp sdp: aResult sdp.
+
+ "Check what to do next"
+ state = self class stateAcked
+ ifTrue: [
+ self logDebug: 'GSMProc(srcref:%1) CRCX compl(%2) Code: %3.'
+ % {self srcRef. endp callId. aResult code} area: #bsc.
+ self assignmentSuccess.
+ ]
+ ifFalse: [
+ self logDebug: 'GSMProc(srcref:%1) CRCX compl(%2), call gone.'
+ % {self srcRef. endp callId} area: #bsc.
+ self releaseAudio.
+ ].
+ ]
+
+ crcxTimeout [
+ <category: 'audio-connect'>
+
+ self logDebug: 'GSMProc(srcref:%1) CRCX timeout on %2 with CallID: %3.'
+ % {self srcRef. endp endpointName. endp callId} area: #bsc.
+
+ "Free the endpoint"
+ endp used.
+ self freeEndpoint.
+
+ "tell transactions. in case we get this late then there are no
+ transactions left and this is a no-op."
+ self assignmentFailure.
+ ]
+
+ freeEndpoint [
+ <category: 'audio-release'>
+
+ endp free.
+ endp := nil.
+ connId := nil.
+ ]
+
+ sdpFile [
+ <category: 'audio-sdp'>
+ ^ endp sdp
+ ]
+
+ sendDLCX [
+ | trans dlcx |
+ <category: 'audio-release'>
+ "I sent the DLCX, I also make the endpoint forget the callid. As this
+ is our indicator that things have been cleared or will be cleared."
+
+ trans := Osmo.MGCPTransaction on: endp of: self callAgent.
+ dlcx := Osmo.MGCPDLCXCommand createDLCX: endp callId: endp callId.
+ endp clearCallId.
+ connId isNil ifFalse: [dlcx parameterAdd: 'I: %1' % {connId}].
+ trans command: dlcx.
+ trans onResult: [:endp :result |
+ self takeLocks: [self dlcxResult: result. self mgcpTransFinished: trans]].
+ trans onTimeout: [:endp |
+ self takeLocks: [self dlcxTimeout. self mgcpTransFinished: trans]].
+ self mgcpQueueTrans: trans.
+ ]
+
+ dlcxResult: aResult [
+ <category: 'audio-release'>
+
+ aResult isSuccess
+ ifTrue: [
+ self logError: 'GSMProc(srcref:%1) DLCX succeeded on endp(%2).'
+ % {self srcRef. endp endpointName} area: #bsc.
+ self freeEndpoint.]
+ ifFalse: [
+ self logError: 'GSMProc(srcref:%1) DLCX failed on endp(%2).'
+ % {self srcRef. endp endpointName} area: #bsc.].
+ ]
+
+ dlcxTimeout [
+ <category: 'audio-release'>
+
+ self logError: 'GSMProc(srcref:%1) DLCX timedout Endp(%2) stays blocked.'
+ % {self srcRef. endp endpointName} area: #bsc.
+ endp := nil.
+ connId := nil.
+ ]
+
+ sendMDCX: aSDPRecord state: aState [
+ | trans mdcx |
+ <category: 'audio-modify'>
+
+ trans := Osmo.MGCPTransaction on: endp of: self callAgent.
+ mdcx := Osmo.MGCPMDCXCommand createMDCX: endp callId: endp callId.
+ mdcx
+ parameterAdd: 'I: %1' % {connId};
+ parameterAdd: 'M: %1' % {aState};
+ sdp: aSDPRecord.
+
+ trans
+ command: mdcx;
+ onResult: [:endp :result |
+ self takeLocks: [self mdcxResult: result. self mgcpTransFinished: trans]];
+ onTimeout: [:endp |
+ self takeLocks: [self mdcxTimeout. self mgcpTransFinished: trans]].
+ self mgcpQueueTrans: trans.
+ ]
+
+ mdcxResult: aResult [
+ ]
+
+ mdcxTimeout: aTimeout [
+ ]
+]
diff --git a/src/HLR.st b/src/HLR.st
new file mode 100644
index 0000000..1e5f3d9
--- /dev/null
+++ b/src/HLR.st
@@ -0,0 +1,72 @@
+"
+ (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/>.
+"
+"
+This is the interface to the local HLR. It consists out of simple
+data that will be used inside the HLR.
+"
+
+Object subclass: HLRSubscriber [
+ |imsi msisdn vlrnumber auKey name |
+ <category: 'osmo-msc'>
+ <comment: 'I am one subscriber in the HLR'>
+
+ imsi [ <category: 'accessing'> ^ imsi ]
+ msisdn [ <category: 'accessing'> ^ msisdn ]
+ vlrnumber [ <category: 'accessing'> ^ vlrnumber ]
+ aukey [ <category: 'accessing'> ^ auKey ]
+ name [ <category: 'accessing'> ^ name ]
+]
+
+Object subclass: HLR [
+ <category: 'osmo-msc'>
+ <comment: 'I am a HLR and I can find subscribers'>
+
+ findSubscriberByIMSI: aIMSI [
+ <category: 'accessing'>
+ ^ self subclassResponsibility
+ ]
+
+ updateVLRNumber: aIMSI number: aNumber [
+ ^ self subclassResponsibility
+ ]
+]
+
+HLR subclass: HLRLocalCollection [
+ | subs |
+ <category: 'osmo-msc-simple'>
+ <comment: 'I am a very simple local HLR'>
+
+ findSubscriberByIMSI: aIMSI [
+ <category: 'accessing'>
+ self subs do: [:each |
+ (each imsi = aIMSI)
+ ifTrue: [^each]].
+
+ ^ nil
+ ]
+
+ addSubscriber: aIMSI [
+ | sub |
+ sub := HLRSubscriber new.
+ sub instVarNamed: #imsi put: aIMSI.
+
+ self subs add: sub.
+ ]
+
+ subs [<category: 'private'> ^subs ifNil: [subs := OrderedCollection new]]
+]
diff --git a/src/Logging.st b/src/Logging.st
new file mode 100644
index 0000000..73378db
--- /dev/null
+++ b/src/Logging.st
@@ -0,0 +1,61 @@
+"
+ (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: 'OsmoLogging'.
+
+Osmo.LogArea subclass: LogAreaBSC [
+ <category: 'osmo-msc-logging'>
+ LogAreaBSC class >> areaName [ ^ #bsc ]
+ LogAreaBSC class >> areaDescription [ ^ 'BSC Connectivty' ]
+ LogAreaBSC class >> default [
+ ^ self new
+ enabled: true;
+ minLevel: Osmo.LogLevel debug;
+ yourself
+ ]
+]
+
+Osmo.LogArea subclass: LogAreaHLR [
+ <category: 'osmo-msc-logging'>
+ LogAreaHLR class >> areaName [ ^ #hlr ]
+ LogAreaHLR class >> areaDescription [ ^ 'HLR work' ]
+ LogAreaHLR class >> default [
+ ^ self new
+ enabled: true; minLevel: Osmo.LogLevel debug; yourself.
+ ]
+]
+
+Osmo.LogArea subclass: LogAreaVLR [
+ <category: 'osmo-msc-logging'>
+ LogAreaVLR class >> areaName [ ^ #vlr ]
+ LogAreaVLR class >> areaDescription [ ^ 'VLR work' ]
+ LogAreaVLR class >> default [
+ ^ self new
+ enabled: true; minLevel: Osmo.LogLevel debug; yourself.
+ ]
+]
+
+Osmo.LogArea subclass: LogAreaMSC [
+ <category: 'osmo-msc-logging'>
+ LogAreaMSC class >> areaName [ ^ #msc ]
+ LogAreaMSC class >> areaDescription [ ^ 'MSC work' ]
+ LogAreaMSC class >> default [
+ ^ self new
+ enabled: true; minLevel: Osmo.LogLevel debug; yourself.
+ ]
+]
diff --git a/src/MSC.st b/src/MSC.st
new file mode 100644
index 0000000..be2f3e0
--- /dev/null
+++ b/src/MSC.st
@@ -0,0 +1,242 @@
+"
+ (C) 2010-2011 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: 'OsmoMGCP';
+ fileInPackage: 'OsmoSIP'.
+
+Object subclass: MSCConfig [
+ | ip port mgcp sip_ip sip_port |
+ <category: 'MSC-IP'>
+ <comment: 'I contain a very simple MSC config for IP based BSCs'>
+
+ bscIP: aIP [
+ <category: 'config'>
+ ip := aIP
+ ]
+
+ bscIP [
+ <category: 'accessing'>
+ ^ ip
+ ]
+
+ bscPort: aPort [
+ <category: 'config'>
+ port := aPort
+ ]
+
+ bscPort [
+ <category: 'accessing'>
+ ^ port
+ ]
+
+ mgcpIP: aIP [
+ <category: 'config'>
+ mgcp := aIP
+ ]
+
+ mgcpIP [
+ <category: 'accessing'>
+ ^ mgcp ifNil: [ip]
+ ]
+
+ sipIP: aIP [
+ <category: 'config'>
+ sip_ip := aIP
+ ]
+
+ sipIP [
+ <category: 'accessing'>
+ ^ sip_ip ifNil: [ip]
+ ]
+
+ sipPort: aPort [
+ <category: 'config'>
+ sip_port := aPort
+ ]
+
+ sipPort [
+ <category: 'accessing'>
+ ^ sip_port ifNil: [5061]
+ ]
+]
+
+Object subclass: MSCBSCConnectionHandler [
+ | msc connections |
+
+ <comment: 'I take incoming connections, find a handler for them and
+ will register them. I will be passed to the BSCListener'>
+
+ MSCBSCConnectionHandler class >> initWith: aMSC [
+ ^ self new
+ instVarNamed: #msc put: aMSC; yourself
+ ]
+
+ connections [ ^ connections ifNil: [connections := OrderedCollection new]]
+
+ setupConnection: aConnection on: aConfig [
+ | bsc |
+ self logNotice: 'BSC-Socket: New Connection for lac', (aConfig lac asString)
+ area: #bsc.
+
+ "Create the BSC first and then assume it is present"
+ [
+ bsc := BSCIPAConnection createOn: aConnection withConfig: aConfig msc: msc.
+ ] on: Exception do: [:ex |
+ ex logException: 'BSC: Creating a handler failed.' area: #bsc.
+ aConnection close.
+ ^ false
+ ].
+
+
+ [
+ [[
+ aConfig connected: true.
+ self connections add: bsc.
+ bsc process.
+ ] on: SystemExceptions.EndOfStream do: [:ex |
+ aConfig connected: false.
+ self logNotice: 'BSC disconnected for lac: %1' % {aConfig lac}
+ area: #bsc.
+ ] on: Exception do: [:ex |
+ self logError: 'Unexpected exception for lac: %1' % {aConfig lac}
+ area: #bsc.
+ thisContext backtraceOn: Transcript.
+ ]] ensure: [
+ self logNotice: 'BSC being disconnected for lac: %1' % {aConfig lac}
+ area: #bsc.
+ bsc terminateAll.
+ self connections remove: bsc ifAbsent: [
+ self logError: 'BSC was never added on lac: %1?' % {aConfig lac}
+ area: #bsc].
+
+ aConfig connected: false.
+ aConnection close.
+ ].
+ ] fork.
+ ]
+
+ newConnection: aConnection [
+ | peer |
+ <category: 'handling'>
+
+ peer := aConnection remoteAddress.
+ msc bscConfig bscList do: [:each |
+ each peer = peer ifTrue: [
+ each connected ifTrue: [
+ self logError: 'BSC-Socket: Still connected for lac: %1' % {each lac}
+ area: #bsc.
+ aConnection close.
+ ^ false
+ ].
+
+ self setupConnection: aConnection on: each.
+ ^ true
+ ].
+ ].
+
+ self logError: 'BSC-Socket: Unknown connection from %1' % {peer} area: #bsc.
+ aConnection close.
+ ]
+]
+
+Object subclass: MSCApplication [
+ | hlr vlr config bscListener bscConfig bscConHandler mgcp sip |
+ <comment: 'I am a MSC as I have the VLR/HLR and other instances'>
+
+ hlr [ ^ hlr ifNil: [HLRLocalCollection new]]
+ vlr [ ^ vlr ifNil: [VLRLocalCollection new]]
+
+ config [ ^ config ifNil: [config := MSCConfig new]]
+ bscConfig [ ^ bscConfig ifNil: [bscConfig := BSCConfig new]]
+ bscConHandler [ ^ bscConHandler ifNil: [bscConHandler := MSCBSCConnectionHandler initWith: self]]
+
+ mgcpCallAgent [
+ <category: 'MGCP-Audio'>
+ ^ mgcp ifNil: [
+ mgcp := (Osmo.MGCPCallAgent startOn: config bscIP)
+ start;
+ yourself]
+ ]
+
+ sipGateway [
+ <category: 'SIP-Audio'>
+ ^ sip ifNil: [ | transport |
+ transport := Osmo.SIPUdpTransport
+ startOn: self config sipIP port: self config sipPort.
+ sip := Osmo.SIPUserAgent createOn: transport.
+ transport start.
+ sip]
+ ]
+
+ selectAudioRoute: aCon plan: aPlan leg: aLeg [
+ | nr |
+ "TODO: Very simple and hardcoded rule"
+ nr := aPlan number.
+
+ "No number, let us return"
+ nr isEmpty ifTrue: [^nil].
+
+ "No special number"
+ nr first = $* ifFalse: [^nil].
+
+
+ ^ (SIPMTCall
+ fromUser: 'sip:1000@sip.zecke.osmocom.org'
+ host: '127.0.0.1'
+ port: 5060
+ to: 'sip:1%1@127.0.0.1' % {nr allButFirst}
+ on: self sipGateway)
+ remoteLeg: aLeg;
+ yourself
+ ]
+
+ serveBSC [
+ "I will start to listen for BSCs"
+ bscListener ifNotNil: [bscListener stop.].
+ bscListener := BSCListener
+ initWith: config bscIP
+ port: config bscPort
+ handler: self bscConHandler.
+ bscListener serve.
+ ]
+
+
+ MSCApplication class >> startExample [
+ | msc |
+
+ msc := MSCApplication new.
+ msc config
+ bscIP: '0.0.0.0';
+ bscPort: 5000;
+ sipIP: '192.168.0.101'.
+ msc bscConfig
+ addBSC: '127.0.0.1' withName: 'test' andLac: 4711.
+
+ "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.
+ ]
+]
diff --git a/src/SIPCall.st b/src/SIPCall.st
new file mode 100644
index 0000000..8fec1f9
--- /dev/null
+++ b/src/SIPCall.st
@@ -0,0 +1,81 @@
+"
+ (C) 2010-2011 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: 'OsmoSIP'.
+
+Osmo.SIPCall subclass: SIPMTCall [
+ | remoteLeg sdp_alert |
+ <category: 'sip'>
+ <comment: 'I represent a SIP terminated call. It is called Mobile
+ Terminated to stay with the GSM speech.'>
+
+ remoteLeg: aLeg [
+ <category: 'creation'>
+ remoteLeg := aLeg.
+ ]
+
+ netTerminate [
+ <category: 'external'>
+ "The other side of the call has terminated, we need to
+ clean up things."
+
+ remoteLeg := nil.
+ self terminate.
+ ]
+
+ sessionNew [
+ "We now have connected call, tell the other side."
+ remoteLeg isNil
+ ifFalse: [remoteLeg netConnect]
+ ifTrue: [self terminate].
+ ]
+
+ sessionFailed [
+ "We have failed to connect things, tell the other side."
+ self terminateRemote.
+ ]
+
+ sessionEnd [
+ "The session is now disconnected, tell the other side."
+ self terminateRemote.
+ ]
+
+ sessionNotification: aNot [
+ "The session has some information. We will use it to tell
+ the other leg of the connection."
+ (aNot code asInteger = 183) ifTrue: [
+ remoteLeg isNil ifFalse: [
+ sdp_alert := aNot sdp.
+ remoteLeg netAlerting]].
+ ]
+
+ terminateRemote [
+ remoteLeg isNil
+ ifFalse: [remoteLeg netTerminate. remoteLeg := nil].
+ ]
+
+ sdp [
+ <category: 'audio'>
+ ^ sdp_result
+ ]
+
+ sdpAlert [
+ <category: 'audio'>
+ ^ sdp_alert
+ ]
+]
diff --git a/src/VLR.st b/src/VLR.st
new file mode 100644
index 0000000..cf9d403
--- /dev/null
+++ b/src/VLR.st
@@ -0,0 +1,109 @@
+"
+ (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/>.
+"
+"
+This is the interface to the VLR
+"
+
+Object subclass: VLRSubscriber [
+ |imsi tmsi msisdn lac|
+ <category: 'osmo-msc'>
+ <comment: 'I am one subscriber in the VLR'>
+
+
+ imsi [ <category: 'accessing'> ^ imsi ]
+ tmsi [ <category: 'accessing'> ^ tmsi ]
+ msisdn [ <category: 'accessing'> ^ msisdn ]
+ lac [ <category: 'accessing'> ^ lac ]
+]
+
+Object subclass: VLR [
+ <category: 'osmo-msc'>
+ <comment: 'I hold the active subscribers'>
+
+ activeSubscribers [
+ <category: 'accessing'>
+ ^ self subclassResponsibility
+ ]
+
+ activeSubscribersByLAC: aLac [
+ <category: 'accessing'>
+ ^ self activeSubscribers
+ reject: [:each | each ~= aLac ].
+ ]
+
+ findSubscriber: aMatch ifAbsent: aBlock [
+ <category: 'private'>
+
+ self activeSubscribers do: [:each |
+ (aMatch value: each)
+ ifTrue: [^each].
+ ].
+
+ ^ aBlock value.
+ ]
+
+ findSubscriberByIMSI: aIMSI ifAbsent: aBlock [
+ <category: 'accessing'>
+ ^ self findSubscriber: [:each | each imsi = aIMSI] ifAbsent: aBlock.
+ ]
+
+ findSubscriberByTMSI: aTMSI ifAbsent: aBlock [
+ <category: 'accessing'>
+ ^ self findSubscriber: [:each | each tmsi = aTMSI] ifAbsent: aBlock.
+ ]
+
+ insertSubscriber: aIMSI [
+ ^ self subclassResponsibility
+ ]
+]
+
+Object subclass: HLRResolver [
+ insertSubscriber: aIMSI [
+ ^ self subclassResponsibility
+ ]
+]
+
+VLR subclass: VLRLocalCollection [
+ | subs resolver |
+
+ VLRLocalCollection class >> initWith: aResolver [
+ ^ self new
+ instVarNamed: #resolver put: aResolver;
+ yourself.
+ ]
+
+ insertSubscriber: aIMSI [
+ | hlr sub |
+ hlr := resolver insertSubscriber: aIMSI.
+ hlr ifNil: [^false].
+
+ sub := self findSubscriberByIMSI: aIMSI
+ ifAbsent: [ | sub |
+ sub := VLRSubscriber new
+ instVarNamed: #imsi put: aIMSI; yourself.
+ self subs add: sub].
+ ^ true
+ ]
+
+ activeSubscribers [
+ <category: 'accessing'>
+ ^ self subs
+ ]
+
+ subs [ <category: 'private'> ^ subs ifNil: [subs := OrderedCollection new]]
+]