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

Add 'osmo-st-msc/' from commit 'befb7a50f7c032e5ca4d8a992d6176983b5177f7'

git-subtree-dir: osmo-st-msc
git-subtree-mainline: 006536f17e
git-subtree-split: befb7a50f7
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:02 +02:00
commit 7a33a071fd
44 changed files with 3925 additions and 0 deletions

1
osmo-st-msc/.gitignore vendored Normal file
View File

@ -0,0 +1 @@
*.sw?

28
osmo-st-msc/Loader.st Normal file
View File

@ -0,0 +1,28 @@
"
(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/>.
"
"
I am helping to create a unconfigured image
"
PackageLoader fileInPackage: #OsmoMSC.
Eval [
| l |
PackageLoader flush.
ObjectMemory snapshot: Smalltalk arguments first.
]

11
osmo-st-msc/Makefile Normal file
View File

@ -0,0 +1,11 @@
GST_PACKAGE = gst-package
GST = gst
.PHONY: package image
all: package image
package:
$(GST_PACKAGE) package.xml
image: package
$(GST) -i -f Loader.st osmo_msc_ow2.img

27
osmo-st-msc/README Normal file
View File

@ -0,0 +1,27 @@
This is a simple MSC done in Smalltalk.
== Objects and their relationship ==
=== MSC ===
- MSC has a VLR, HLR, BSCConfig, MSCBSCConnectionHandler
- MSC can serve a BSC on TCP depending on the MSCConfig with
the BSCListener
=== BSCListener ===
- BSCListener will wait for incoming connections and hand them
to the MSCBSCConnectionHandlerMSC. This will try to find the
configured peer and might do the connection.
=== MSCBSCConnectionHandler ===
- Get's a new connection from the BSCListener, will fork and
serve the BSC using the BSCIPAConnection. This is done to
remember if a given system is already connected or not.
=== BSCIPAConnection ===
- Handles IPA mux/demux on the socket...
- Has a SCCPHandler
- Uses GSMProcessor to process the GSM part of it.
=== GSMProcessor ===
- Handles GSM connections, transaction and such.

27
osmo-st-msc/Start.st Normal file
View File

@ -0,0 +1,27 @@
PackageLoader fileInPackage: 'OsmoSIP'.
Eval [
FileStream
fileIn: 'src/Logging.st';
fileIn: 'src/VLR.st';
fileIn: 'src/HLR.st';
fileIn: 'src/BSCConfig.st';
fileIn: 'src/BSCListener.st';
fileIn: 'src/BSCSCCPHandler.st';
fileIn: 'src/auth/GSMAuthenticatorBase.st';
fileIn: 'src/auth/GSMIdentityAuthenticator.st';
fileIn: 'src/auth/GSMNullAuthenticator.st';
fileIn: 'src/GSMProcessor.st';
fileIn: 'src/call/Extensions.st';
fileIn: 'src/call/GSMMOCall.st';
fileIn: 'src/call/SIPMTCall.st';
fileIn: 'src/GSMLURequest.st';
fileIn: 'src/GSMCMServiceRequest.st';
fileIn: 'src/GSMEmergencySetup.st';
fileIn: 'src/BSCIPAConnection.st';
fileIn: 'src/PagingManager.st';
fileIn: 'src/MSC.st'.
"
"
]

152
osmo-st-msc/contrib/osmo-msc Executable file
View File

@ -0,0 +1,152 @@
#!/bin/sh
### BEGIN INIT INFO
# Provides: osmo-msc
# Required-Start: $network $local_fs
# Required-Stop:
# Default-Start: 2 3 4 5
# Default-Stop: 0 1 6
# Short-Description: Start the Osmo Smalltalk MSC
# Description: Simple Osmo Smalltalk MSC
### END INIT INFO
# Author: hfreyther holger@freyther.de
# PATH should only include /usr/* if it runs after the mountnfs.sh script
PATH=/sbin:/usr/sbin:/bin:/usr/bin
DESC=osmo-msc # Introduce a short description here
NAME=osmo-msc # Introduce the short server's name here
DAEMON=/usr/bin/gst-remote # Introduce the server's location here
DAEMON_ARGS="--daemon --server -I /var/lib/osmo-msc/osmo_msc.img -f /etc/default/osmo-msc.st 127.0.0.1" # Arguments to run the daemon with
PIDFILE=/var/run/$NAME.pid
SCRIPTNAME=/etc/init.d/$NAME
# Exit if the package is not installed
[ -x $DAEMON ] || exit 0
# Read configuration variable file if it is present
[ -r /etc/default/$NAME ] && . /etc/default/$NAME
# Load the VERBOSE setting and other rcS variables
. /lib/init/vars.sh
# Define LSB log_* functions.
# Depend on lsb-base (>= 3.0-6) to ensure that this file is present.
. /lib/lsb/init-functions
#
# Function that starts the daemon/service
#
do_start()
{
# Return
# 0 if daemon has been started
# 1 if daemon was already running
# 2 if daemon could not be started
start-stop-daemon --start --quiet --pidfile $PIDFILE --exec $DAEMON --test > /dev/null \
|| return 1
start-stop-daemon --start --quiet --pidfile $PIDFILE --exec $DAEMON -- \
$DAEMON_ARGS > /dev/null 2>&1 \
|| return 2
# Add code here, if necessary, that waits for the process to be ready
# to handle requests from services started subsequently which depend
# on this one. As a last resort, sleep for some time.
}
#
# Function that stops the daemon/service
#
do_stop()
{
# Return
# 0 if daemon has been stopped
# 1 if daemon was already stopped
# 2 if daemon could not be stopped
# other if a failure occurred
start-stop-daemon --stop --quiet --retry=TERM/30/KILL/5 --pidfile $PIDFILE --name $NAME
RETVAL="$?"
[ "$RETVAL" = 2 ] && return 2
# Wait for children to finish too if this is a daemon that forks
# and if the daemon is only ever run from this initscript.
# If the above conditions are not satisfied then add some other code
# that waits for the process to drop all resources that could be
# needed by services started subsequently. A last resort is to
# sleep for some time.
start-stop-daemon --stop --quiet --oknodo --retry=0/30/KILL/5 --exec $DAEMON
[ "$?" = 2 ] && return 2
# Many daemons don't delete their pidfiles when they exit.
rm -f $PIDFILE
return "$RETVAL"
}
#
# Function that sends a SIGHUP to the daemon/service
#
do_reload() {
#
# If the daemon can reload its configuration without
# restarting (for example, when it is sent a SIGHUP),
# then implement that here.
#
start-stop-daemon --stop --signal 1 --quiet --pidfile $PIDFILE --name $NAME
return 0
}
case "$1" in
start)
[ "$VERBOSE" != no ] && log_daemon_msg "Starting $DESC " "$NAME"
do_start
case "$?" in
0|1) [ "$VERBOSE" != no ] && log_end_msg 0 ;;
2) [ "$VERBOSE" != no ] && log_end_msg 1 ;;
esac
;;
stop)
[ "$VERBOSE" != no ] && log_daemon_msg "Stopping $DESC" "$NAME"
do_stop
case "$?" in
0|1) [ "$VERBOSE" != no ] && log_end_msg 0 ;;
2) [ "$VERBOSE" != no ] && log_end_msg 1 ;;
esac
;;
status)
status_of_proc "$DAEMON" "$NAME" && exit 0 || exit $?
;;
#reload|force-reload)
#
# If do_reload() is not implemented then leave this commented out
# and leave 'force-reload' as an alias for 'restart'.
#
#log_daemon_msg "Reloading $DESC" "$NAME"
#do_reload
#log_end_msg $?
#;;
restart|force-reload)
#
# If the "reload" option is implemented then remove the
# 'force-reload' alias
#
log_daemon_msg "Restarting $DESC" "$NAME"
do_stop
case "$?" in
0|1)
do_start
case "$?" in
0) log_end_msg 0 ;;
1) log_end_msg 1 ;; # Old process is still running
*) log_end_msg 1 ;; # Failed to start
esac
;;
*)
# Failed to stop
log_end_msg 1
;;
esac
;;
*)
#echo "Usage: $SCRIPTNAME {start|stop|restart|reload|force-reload}" >&2
echo "Usage: $SCRIPTNAME {start|stop|status|restart|force-reload}" >&2
exit 3
;;
esac
:

57
osmo-st-msc/package.xml Normal file
View File

@ -0,0 +1,57 @@
<package>
<name>OsmoMSC</name>
<namespace>OsmoMSC</namespace>
<prereq>OsmoLogging</prereq>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoGSM</prereq>
<prereq>OsmoSIP</prereq>
<filein>src/Logging.st</filein>
<filein>src/sip/SIPIdentityManager.st</filein>
<filein>src/sip/MSCSIPIdentity.st</filein>
<filein>src/VLR.st</filein>
<filein>src/HLR.st</filein>
<filein>src/BSCConfig.st</filein>
<filein>src/BSCListener.st</filein>
<filein>src/BSCSCCPHandler.st</filein>
<filein>src/GSMProcessor.st</filein>
<filein>src/GSMCMServiceRequest.st</filein>
<filein>src/GSMLURequest.st</filein>
<filein>src/PagingManager.st</filein>
<filein>src/BSCIPAConnection.st</filein>
<filein>src/MSC.st</filein>
<filein>src/call/Extensions.st</filein>
<filein>src/call/GSMMOCall.st</filein>
<filein>src/call/GSMEmergencySetup.st</filein>
<filein>src/call/SIPMTCall.st</filein>
<filein>src/auth/GSMAuthenticatorBase.st</filein>
<filein>src/auth/GSMNullAuthenticator.st</filein>
<filein>src/auth/GSMIdentityAuthenticator.st</filein>
<test>
<sunit>OsmoMSC.HLRTest</sunit>
<sunit>OsmoMSC.VLRTest</sunit>
<sunit>OsmoMSC.BSCConfigTest</sunit>
<sunit>OsmoMSC.BSCListenerTest</sunit>
<sunit>OsmoMSC.MSCBSCConnectionHandlerTest</sunit>
<sunit>OsmoMSC.BSCIPAConnectionTest</sunit>
<sunit>OsmoMSC.AuthTestNull</sunit>
<sunit>OsmoMSC.AuthTestIdentity</sunit>
<sunit>OsmoMSC.SIPIdentityManagerTest</sunit>
<filein>tests/HLRDummyResolver.st</filein>
<filein>tests/BSCConfigTest.st</filein>
<filein>tests/BSCIPAConnectionTest.st</filein>
<filein>tests/BSCListenerTest.st</filein>
<filein>tests/HLRTest.st</filein>
<filein>tests/MSCBSCConnectionHandlerTest.st</filein>
<filein>tests/VLRTest.st</filein>
<filein>tests/AuthTestIdentity.st</filein>
<filein>tests/AuthTestNull.st</filein>
<filein>tests/GSMProcessorMockBase.st</filein>
<filein>tests/GSMProcessorMockForAuthCheat.st</filein>
<filein>tests/GSMProcessorMockForAuthIMSI.st</filein>
<filein>tests/GSMProcessorMockForAuthTimeout.st</filein>
<filein>tests/MockSIPUserAgent.st</filein>
<filein>tests/SIPIdentityManagerTest.st</filein>
</test>
</package>

View File

@ -0,0 +1,126 @@
"
(C) 2010-2013 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 connection osmoExtension |
<category: 'OsmoMSC-BSC'>
<comment: 'I hold the configuration for one BSC 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;
connection: nil;
sendOsmoRSIP: false;
lac: -1;
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'>
^ connection isNil not
]
connection: aCon [
<category: 'private'>
connection := aCon.
]
connection [
<category: 'private'>
^ connection
]
sendOsmoRSIP [ <category: 'accessing'> ^ osmoExtension ]
sendOsmoRSIP: useExtension [
<category: 'private'>
osmoExtension := useExtension
]
]
Object subclass: BSCConfig [
| bscList |
<category: 'OsmoMSC-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 sendOsmoRSIP: aRSIP [
| 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)
lac: aLac;
sendOsmoRSIP: aRSIP;
yourself.
(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]]
]

View File

@ -0,0 +1,223 @@
"
(C) 2010-2013 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: 'OsmoCore';
fileInPackage: 'OsmoMGCP';
fileInPackage: 'OsmoNetwork'.
Osmo.IPAProtoHandler subclass: BSCIPAProtoHandler [
| bsc |
<category: 'OsmoMSC-BSC'>
BSCIPAProtoHandler class >> initWith: aBSC [
<category: 'creation'>
^ self new
instVarNamed: #bsc put: aBSC;
yourself
]
handlePong: aMsg [
<category: 'pong'>
bsc receivedPong.
]
]
Object subclass: BSCConnection [
| config msc trunk |
<category: 'OsmoMSC-BSC'>
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 to the remote BSC. Right now I force
the usage of UDP."
trunk := Osmo.MGCPDSTrunk createWithDest: config peer printString trunkNr: 1.
(trunk endpointAt: 1) tryBlock.
"Osmo Extension"
config sendOsmoRSIP ifTrue: [self sendOsmoRSIP].
]
config [
<category: 'accessing'>
^ config
]
msc [
<category: 'accessing'>
^ msc
]
trunk [
<category: 'accessing'>
^ trunk
]
sendOsmoRSIP [
<category: 'osmo-extensions'>
"Send the RSIP in a fire and forget style."
(Osmo.MGCPTransaction on: (trunk endpointAt: 2) of: msc mgcpCallAgent)
command: Osmo.MGCPOsmoRSIPCommand createRSIP;
startSingleShot.
]
sendUdt: aMsg [
| udt addr |
addr := Osmo.SCCPAddress createWith: 254.
udt := Osmo.SCCPUDT initWith: addr calling: addr data: aMsg.
^ self send: udt toMessage with:Osmo.IPAConstants protocolSCCP.
]
]
BSCConnection subclass: BSCIPAConnection [
| socket demuxer writeQueue muxer dispatcher sccp tx terminated
ipa ping_timeout pong_timeout |
<category: 'OsmoMSC-BSC'>
<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.
ipa := BSCIPAProtoHandler initWith: self.
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 := [
Processor activeProcess name: 'BTS TX queue(%1)' % {self lac}.
self sendPing.
[
[
self runTxQueueOnce
] repeat.
] ensure: [
self logNotice: 'BSC TX queue lac: %1 finished' % {self lac} area: #bsc]
] fork.
]
runTxQueueOnce [
| msg |
<category: 'private'>
msg := writeQueue next.
socket nextPutAllFlush: msg.
]
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.
pong_timeout isNil ifFalse: [pong_timeout cancel].
self class terminate: tx.
OsmoDispatcher dispatchBlock: [sccp linkSetFailed].
]
sendPing [
<category: 'ping-pong'>
"I send a ping and start a timer..."
self
send: (ByteArray with: Osmo.IPAConstants msgPing)
with: Osmo.IPAConstants protocolIPA.
self logDebug: 'BSC lac: %1 sent ping waiting now.' % {self lac} area: #bsc.
pong_timeout := (Osmo.TimerScheduler instance)
scheduleInSeconds: 5 block: [
self logNotice: 'BSC lac: %1 ping timeout.' % {self lac} area: #bsc.
socket close].
]
receivedPong [
<category: 'ping-pong'>
terminated = true ifTrue: [^false].
pong_timeout cancel.
self logDebug: 'BSC lac: %1 ponged.' % {self lac} area: #bsc.
ping_timeout := (Osmo.TimerScheduler instance)
scheduleInSeconds: 30 block: [
self sendPing].
]
]

View File

@ -0,0 +1,88 @@
"
(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 |
<category: 'OsmoMSC-BSC'>
<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 [
[socket isOpen] whileTrue: [
self handleOneConnection.
].
^ false
]
handleOneConnection [
[ | con |
socket waitForConnection.
con := socket accept.
con ifNil: [
self logNotice: 'BSC-Socket: Connection failed. Will return.' area: #bsc.
^ false
].
handler isNil
ifTrue: [
self logNotice: 'BSC-Socket: Closing connection due lack of handler.' area: #bsc.
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.
]
]

View File

@ -0,0 +1,64 @@
"
(C) 2010-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/>.
"
PackageLoader
fileInPackage: 'OsmoGSM'.
OsmoGSM.SCCPHandler subclass: BSCSCCPHandler [
| bsc msc |
<category: 'OsmoMSC-BSC'>
<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.
]
handleUDT: aMsg [
"I need to handle a reset and such"
^ super handleUDT: aMsg.
]
newConnection: aConnection [
self logNotice: 'New incoming SCCP connection %1 on the BSC %2'
% {aConnection srcRef. bsc lac} area: #bsc.
^ super newConnection: aConnection.
]
]

View File

@ -0,0 +1,108 @@
"
(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
]
]
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 [
| 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.
]
]

View File

@ -0,0 +1,61 @@
"
(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/>.
"
PackageLoader
fileInPackage: 'OsmoCore';
fileInPackage: 'OsmoGSM'.
OsmoGSM.GSM48LURequest extend [
openTransactionOn: aCon sapi: aSapi [
| tran |
<category: '*OsmoMSC-GSM'>
'foo' printNl.
tran := (GSMLURequest on: aSapi with: self ti)
con: aCon;
yourself.
aCon openTransaction: tran with: self.
]
]
GSMTransaction subclass: GSMLURequest [
| timeout |
<category: 'OsmoMSC-GSM'>
<comment: 'I handle LU requests and do things. I am being written before
the actual code'>
initialize [
<category: 'creation'>
]
start: aCCMessage [
<category: 'start'>
self logNotice: 'GSMLURequest(srcref:%1) starting LU'
% {con srcRef} area: #bsc.
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [con takeLocks: [self timeOut]].
]
timeOut [
self logError: 'GSMLURequest(srcref:%1) timeout.' % {con srcRef} area: #bsc.
self nextPutSapi: OsmoGSM.GSM48LUReject new.
con removeTransaction: self.
]
]

View File

@ -0,0 +1,755 @@
"
(C) 2010-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/>.
"
PackageLoader fileInPackage: 'OsmoGSM'.
OsmoGSM.BSSAPMessage extend [
dispatchTrans: aCon [
<category: '*OsmoMSC-GSM'>
aCon bssapUnknownData: self
]
]
OsmoGSM.BSSAPManagement extend [
dispatchTrans: aCon [
<category: '*OsmoMSC-GSM'>
self dispatchMAP: aCon.
]
dispatchMAP: aCon [
<category: '*OsmoMSC-GSM'>
(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:.
OsmoGSM.GSM0808Helper msgCMUpdate -> #mapCMUpdate:.
}) at: self data type ifPresent: [:sel |
^ aCon perform: sel with: self.
].
^ aCon mapUnknown: self.
]
]
OsmoGSM.BSSAPDTAP extend [
dispatchTrans: aCon [
<category: '*OsmoMSC-GSM'>
aCon dispatchDTAP: self.
]
]
OsmoGSM.GSM48MSG extend [
openTransactionOn: aCon sapi: aSapi [
<category: '*OsmoMSC-GSM'>
self logError: 'Can not open transaction for %1' % {self class} area: #bsc.
]
]
Object subclass: GSMTransaction [
| sapi ti con |
<category: 'OsmoMSC-GSM'>
<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
]
canHandle: aMsg sapi: aSapi [
^ self sapi = aSapi and: [self ti = aMsg ti].
]
sapi [
<category: 'accessing'>
^ sapi
]
ti [
"TODO: This should somehow include the size of the allocation"
<category: 'accessing'>
^ ti
]
con: aCon [
<category: 'creation'>
con := aCon.
]
con [
<category: 'creation'>
^ con
]
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}.
]
]
OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [
| transactions state endp connId mgcp_trans auth pending info |
<category: 'OsmoMSC-GSM'>
<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 >> stateAuth [<category: 'states'> ^ 2 ]
GSMProcessor class >> stateRelease [<category: 'states'> ^ 3 ]
GSMProcessor class >> stateError [<category: 'states'> ^ 4 ]
GSMProcessor class >> authenticator [
<category: 'authenticator'>
^ GSMIdentityAuthenticator
]
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 speechFullRateVersion1.
GSM0808ChannelTypeIE speechFullRateVersion3.
GSM0808ChannelTypeIE speechHalfRateVersion3};
yourself);
addIe: (GSM0808CICIE initWithMultiplex: aMul timeslot: aTs).
^ ass
]
initialize [
<category: 'creation'>
transactions := OrderedCollection new.
state := self class stateInitial.
info := Dictionary new.
^ super initialize.
]
addInfo: aKey value: aValue [
<category: 'misc'>
"Store additional info about this call here."
info at: aKey put: aValue.
]
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];
releaseAudio;
releaseAuth;
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;
releaseAuth.
].
]
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.
].
]
openTransaction: aTran with: aMsg [
<category: 'transaction'>
self addTransaction: aTran.
"The authentication has happend, just start the transaction."
state = self class stateAuth ifTrue: [
^ aTran start: aMsg
].
"An authentication is pending."
auth isNil ifFalse: [
self logNotice: 'GSMProc(srcref:%1) auth pending.'
% {self srcRef} area: #bsc.
pending add: (aTran -> aMsg).
^ true.
].
"Remember to launch this transaction"
pending := OrderedCollection new
add: (aTran -> aMsg);
yourself.
auth := self class authenticator new
connection: self;
onAccept: [:auth | self authenticationAccepted];
onReject: [:auth | self authenticationRejected];
yourself.
auth start: aMsg.
]
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"
"Pass everything to the authenticator if present."
auth isNil ifFalse: [
^ auth onData: aMsg.
].
"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 canHandle: aMsg sapi: aSapi) 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
]
selectAudioRouteForEmergency: aLeg [
<category: 'call'>
^ conManager msc
selectAudioRouteForEmergency: self leg: aLeg.
]
selectAudioRoute: aPlan leg: aLeg [
<category: 'call'>
^ conManager msc
selectAudioRoute: self plan: aPlan leg: aLeg
]
releaseAuth [
<category: 'auth'>
auth isNil
ifTrue: [^true].
"Give up on the authentication."
auth cancel.
auth := nil.
]
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.]]
]
mapCMUpdate: aData [
<category: 'map-classmark'>
]
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)
addParameter: 'M' with: '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 or: [state = self class stateAuth])
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 addParameter: 'I' with: 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
addParameter: 'I' with: connId;
addParameter: 'M' with: 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 [
]
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 |
each key start: each value].
pending := nil.
]
authenticationRejected [
<category: 'auth'>
"Must be locked"
"TODO"
"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.
]
]

74
osmo-st-msc/src/HLR.st Normal file
View File

@ -0,0 +1,74 @@
"
(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: 'OsmoMSC-HLR'>
<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: 'OsmoMSC-HLR'>
<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: 'OsmoMSC-HLR'>
<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]]
]

View File

@ -0,0 +1,78 @@
"
(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: 'OsmoMSC-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: 'OsmoMSC-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: 'OsmoMSC-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: 'OsmoMSC-Logging'>
LogAreaMSC class >> areaName [ ^ #msc ]
LogAreaMSC class >> areaDescription [ ^ 'MSC work' ]
LogAreaMSC class >> default [
^ self new
enabled: true; minLevel: Osmo.LogLevel debug; yourself.
]
]
Osmo.LogArea subclass: LogAreaMSCSIP [
<category: 'OsmoMSC-Logging'>
LogAreaMSCSIP class >> areaName [^ #mscSIP]
LogAreaMSCSIP class >> areaDescription [^'MSC SIP']
LogAreaMSCSIP class >> default [
^self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]

323
osmo-st-msc/src/MSC.st Normal file
View File

@ -0,0 +1,323 @@
"
(C) 2010-2013 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: 'OsmoMSC-MSC'>
<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 |
<category: 'OsmoMSC-MSC'>
<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
].
[
Processor activeProcess name: 'MSCBSCConnectionHandler(%1)' % {aConfig lac}.
[[
aConfig connection: bsc.
self connections add: bsc.
bsc process.
] on: SystemExceptions.EndOfStream do: [:ex |
aConfig connection: nil.
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 connection: nil.
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 paging |
<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]]
pagingManager [ ^ paging ifNil: [paging := PagingManager initWith: self]]
config [ ^ config ifNil: [config := MSCConfig new]]
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.
[
Processor activeProcess name: 'BSC Listener'.
self serveBSC. 'MSC has exited' printNl] fork.
]
mgcpCallAgent [
<category: 'MGCP-Audio'>
^ mgcp ifNil: [
mgcp := (Osmo.MGCPCallAgent startOn: config bscIP)
start;
yourself]
]
newSipTransport [
<category: 'private'>
^ Osmo.SIPUdpTransport
startOn: self config sipIP port: self config sipPort.
]
sipGateway [
<category: 'SIP-Audio'>
^ sip ifNil: [ | transport |
transport := self newSipTransport.
sip := Osmo.SIPUserAgent createOn: transport.
transport start.
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;
msc: self;
yourself
]
selectRedirectFor: aSipCall to: aSipContact [
^ (SIPMTCall
fromUser: 'sip:1000@sip.zecke.osmocom.org'
host: '127.0.0.1'
port: 5060
to: aSipContact
on: self sipGateway)
remoteLeg: aSipCall remoteLeg;
msc: self;
yourself
]
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;
msc: self;
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: '127.0.0.1'.
msc bscConfig
addBSC: '127.0.0.1' withName: 'test1' andLac: 8210 sendOsmoRSIP: true;
addBSC: '10.240.240.1' withName: 'test2' andLac: 4712 sendOsmoRSIP: true.
msc returnedFromSnapshot.
^ msc.
]
]

View File

@ -0,0 +1,68 @@
"
(C) 2013 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/>.
"
Object subclass: PagingManager [
| msc |
<category: 'OsmoMSC-GSM'>
PagingManager class >> initWith: aMsc [
^ self new
instVarNamed: #msc put: aMsc;
yourself.
]
pageAll: anImsi [
<category: 'paging'>
"Page a subscriber on all LACs of all BSCs"
msc bscConfig bscList do: [:bscConfig |
"This can race with a disconnect but that is fine."
bscConfig connected ifTrue: [
OsmoDispatcher dispatchBlock: [
self pageBSC: bscConfig with: anImsi]]].
]
pageBSC: aBscConfig with: anImsi [
| connection cmd |
<category: 'paging'>
"Page a single BSC"
"Is the bsc still connected?"
connection := aBscConfig connection.
connection ifNil: [
^ false
].
cmd := self createPagingCommand: aBscConfig lac with: anImsi.
connection sendUdt: cmd toMessage asByteArray.
]
createPagingCommand: aLac with: anImsi [
| cmd |
cmd := OsmoGSM.IEMessage initWith: OsmoGSM.GSM0808Helper msgPaging.
cmd
addIe: (OsmoGSM.GSM0808IMSI initWith: anImsi);
addIe: (OsmoGSM.GSM0808CellIdentifierList new
ident: OsmoGSM.GSM0808CellIdentifierList cellLocationAreaCode;
cells: (Array with: aLac);
yourself);
yourself.
^ OsmoGSM.BSSAPManagement initWith: cmd toMessage
]
]

113
osmo-st-msc/src/VLR.st Normal file
View File

@ -0,0 +1,113 @@
"
(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: 'OsmoMSC-VLR'>
<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: 'OsmoMSC-VLR'>
<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 [
<category: 'OsmoMSC-HLR'>
insertSubscriber: aIMSI [
^ self subclassResponsibility
]
]
VLR subclass: VLRLocalCollection [
| subs resolver |
<category: 'OsmoMSC-VLR'>
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]]
]

View File

@ -0,0 +1,86 @@
"
(C) 2010-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/>.
"
Object subclass: GSMAuthenticatorBase [
| connection onAccept onReject |
<category: 'OsmoMSC-GSM-Auth'>
<comment: 'I am the base class for authenticating a given
subscriber. My subclasses can either allow everyone, store
the IMSI and IMEI or be fully GSM compliant and ask a HLR
for an authentication tuple.
When calling the callbacks make sure to go through the
connection>>#takeLocks: selector to take the required locks.'>
<import: OsmoGSM>
LegalMessages := {OsmoGSM.GSM48CMServiceReq.
OsmoGSM.GSM48RRPagingResponse.
OsmoGSM.GSM48LURequest.
"As part of Local-Call-Routing deal with CC Setup"
OsmoGSM.GSM48CCSetup.
}.
appropriateInitialMessage: aMsg [
"Check if the message is one of the allowed initial messages."
^ LegalMessages includes: aMsg class
]
connection: aCon [
<category: 'creation'>
connection := aCon.
]
connection [
<category: 'access'>
^ connection
]
onAccept: aBlock [
<category: 'creation'>
"Called when the connection is accepted"
onAccept := aBlock
]
onReject: aBlock [
<category: 'creation'>
"Called when the connection is rejected"
onReject := aBlock
]
start: aMsg [
<category: 'auth'>
"Start authentication with the initial message."
^ self subclassResponsibility
]
onData: aMsg [
<category: 'auth'>
"Called with data from the GSM connection"
^ self subclassResponsibility
]
cancel [
<category: 'auth'>
"The GSM Connection has failed cancel everything."
^ self subclassResponsibility
]
nextPut: aMsg [
connection nextPutData: (BSSAPDTAP initWith: aMsg
linkIdentifier: 0).
]
]

View File

@ -0,0 +1,88 @@
"
(C) 2010-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/>.
"
GSMAuthenticatorBase subclass: GSMIdentityAuthenticator [
| state timeout |
<category: 'OsmoMSC-GSM-Auth'>
<comment: 'I query for the IMSI and IMEI but do this in an insecure
way and will never switch on the crypto. I will ask for the IMSI and
IMEI'>
cancel [
"Cancel all timers"
timeout ifNotNil: [timeout cancel. timeout := nil].
]
reject: aMsg [
<category: 'reject'>
self logError: 'GSMIdentityAuthenticator(srcref:%1) rejecting type %2'
% {connection srcRef. aMsg class} area: #bsc.
state := #rejected:.
onReject value: self.
]
start: aMsg [
"TODO we could take the IMSI from the first message but this
is mostly for educational purpose."
(self appropriateInitialMessage: aMsg)
ifTrue: [self askForIMSI]
ifFalse: [self reject: aMsg].
]
askForIMSI [
| req |
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [self timeOut].
"I ask for the IMSI."
req := GSM48IdentityReq new.
req idType type: GSM48IdentityType typeIMSI.
state := #askForIMSI:.
self nextPut: req toMessage.
]
askForIMSI: aIdResponse [
connection
addInfo: 'IMSI'
value: aIdResponse mi imsi.
self logNotice: 'GSMIdentityAuthenticator(srcref:%1) got IMSI(%2).'
% {connection srcRef. aIdResponse mi imsi} area: #bsc.
timeout cancel.
onAccept value: self.
]
onData: aMsg [
[
self perform: state with: aMsg.
] on: Error do: [:e |
e logException: 'GSMIdentityAuthenticator(srcref:%1) failed dispatch.'
% {connection srcRef} area: #bsc.
timeout cancel.
onReject value: self.
].
]
timeOut [
self logError: 'GSMIdentityAuthenticator(srcref:%1) no reply to %2'
% {connection srcRef. state} area: #bsc.
state := #timedout:.
connection takeLocks: [onReject value: self].
]
]

View File

@ -0,0 +1,37 @@
"
(C) 2010-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/>.
"
GSMAuthenticatorBase subclass: GSMNullAuthenticator [
<category: 'OsmoMSC-GSM-Auth'>
<comment: 'I accept everything...'>
start: aMsg [
(self appropriateInitialMessage: aMsg)
ifTrue: [onAccept value: self]
ifFalse: [onReject value: self].
]
onData: aMsg [
^ self shouldNotImplement
]
cancel [
"Nothing"
]
]

View File

@ -0,0 +1,71 @@
"
(C) 2011-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.GSM48MSG extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-Call'>
aCon moUnknown: self.
]
]
OsmoGSM.GSM48CCConnectAck extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-Call'>
aCon moConnectAck: self.
]
]
OsmoGSM.GSM48CCDisconnect extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-GSM'>
aCon moDisconnect: self.
]
]
OsmoGSM.GSM48CCRelease extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-GSM'>
aCon moRelease: self.
]
]
OsmoGSM.GSM48CCReleaseCompl extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-GSM'>
aCon moReleaseCompl: self.
]
]
OsmoGSM.GSM48CCStatus extend [
dispatchMoCall: aCon [
<category: '*OsmoMSC-GSM'>
aCon moStatus: self.
]
]
OsmoGSM.GSM48CCSetup extend [
openTransactionOn: aCon sapi: aSapi [
| tran |
<category: '*OsmoMSC-GSM'>
tran := (GSMMOCall on: aSapi with: self ti)
con: aCon;
yourself.
aCon openTransaction: tran with: self.
]
]

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

@ -0,0 +1,252 @@
"
(C) 2011-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/>.
"
GSMTransaction subclass: GSMMOCall [
| state wait_for_ass remoteLeg |
<category: 'OsmoMSC-Call'>
<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.
]
changeRemoteLeg: aLeg [
self logNotice:
'GSMMOCall(srcref:%1) changing remote leg'
% {con srcRef} area: #bsc.
remoteLeg := aLeg.
remoteLeg createCall: con sdpFile.
]
selectAudioRoute: aCCMessage [
"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.
].
]
start: aCCMessage [
<category: 'transaction'>
self selectAudioRoute: aCCMessage.
remoteLeg isNil ifTrue: [^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. remoteLeg := nil].
^ 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.
]
]

View File

@ -0,0 +1,121 @@
"
(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/>.
"
Osmo.SIPCall subclass: SIPMTCall [
| remoteLeg sdp_alert msc mscIdentity |
<category: 'OsmoMSC-Call'>
<comment: 'I represent a SIP terminated call. It is called Mobile
Terminated to stay with the GSM speech.'>
msc: aMsc [
<category: 'creation'>
msc := aMsc
]
mscIdentity: anIdentity [
mscIdentity := anIdentity
mscIdentity usedBy: self.
]
remoteLeg: aLeg [
<category: 'creation'>
remoteLeg := aLeg.
]
remoteLeg [
^remoteLeg
]
netTerminate [
<category: 'external'>
"The other side of the call has terminated, we need to
clean up things."
remoteLeg := nil.
self releaseMscIdentity.
self terminate.
]
sessionRedirect: aContact [
| newLeg |
remoteLeg ifNil: [^self].
self releaseMscIdentity.
newLeg := msc selectRedirectFor: self to: aContact.
newLeg isNil
ifTrue: [
self terminateRemote]
ifFalse: [
remoteLeg changeRemoteLeg: newLeg
remoteLeg := nil].
]
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.
]
terminate [
self releaseMscIdentity.
^super terminate
]
sessionNotification: aNot [
| code |
"The session has some information. We will use it to tell
the other leg of the connection."
code := aNot code asInteger.
((code = 180) or: [code = 183]) ifTrue: [
remoteLeg isNil ifFalse: [
sdp_alert := aNot sdp.
remoteLeg netAlerting]].
]
terminateRemote [
remoteLeg isNil
ifFalse: [remoteLeg netTerminate. remoteLeg := nil].
self releaseMscIdentity.
]
sdp [
<category: 'audio'>
^ sdp_result
]
sdpAlert [
<category: 'audio'>
^ sdp_alert
]
releaseMscIdentity [
mscIdentity ifNotNil: [mscIdentity usedBy: nil. mscIdentity := nil].
]
]

View File

@ -0,0 +1,93 @@
"
(C) 2014 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/>.
"
Osmo.SIPIdentity subclass: MSCSIPIdentity [
| available manager registerTimer usedBy |
<category: 'OsmoMSC-SIP'>
<comment: 'I add timers and others to the plain identity. This
way we can keep track if something is available or not.'>
MSCSIPIdentity class >> new [
^super new
initialize;
yourself
]
initialize [
available := false.
]
manager: aManager [
manager := aManager
]
startRegistration [
| register dialog |
dialog := (Osmo.SIPDialog fromUser: 'sip:', username host: hostname port: 5060)
identity: self;
yourself.
register := (Osmo.SIPRegisterTransaction createWith: dialog on: manager useragent cseq: 1)
destination: 'sip:', hostname;
onTimeout: [self registrationTimedOut];
onFailure: [:response :dialog | self registrationFailed];
onSuccess: [:response :dialog | self registrationSuccess];
yourself.
register start.
]
registrationTimedOut [
self logNotice: 'SIPIdentity(%1@%2) registration timed-out' % {username. hostname}
area: #mscSIP.
available := false.
self reRegisterIn: 10.
]
registrationFailed [
self logNotice: 'SIPIdentity(%1@%2) registration timed-out' % {username. hostname}
area: #mscSIP.
available := false.
self reRegisterIn: 10.
]
registrationSuccess [
self logNotice: 'SIPIdentity(%1@%2) registered' % {username. hostname}
area: #mscSIP.
available := true.
self reRegisterIn: 3590.
]
reRegisterIn: seconds [
"Re-register the identity..."
registerTimer ifNotNil: [registerTimer cancel].
registerTimer := (Osmo.TimerScheduler instance)
scheduleInSeconds: seconds block: [self startRegistration].
]
isAvailable [
^available
]
usedBy: aCall [
"A SIPCall is using this identity right now."
usedBy := aCall
]
isUnused [
^usedBy isNil
]
]

View File

@ -0,0 +1,66 @@
"
(C) 2014 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/>.
"
Object subclass: SIPIdentityManager [
| identities useragent |
<category: 'OsmoMSC-SIP'>
<comment: 'I help in managing and registering different
SIPIdentities. This includes running the register transaction,
re-running it shortly before the expiration and helping to
keep track which one is used and not.'>
SIPIdentityManager class >> new [
^super new
initialize;
yourself
]
SIPIdentityManager class >> initWith: aUseragent [
^self new
useragent: aUseragent;
yourself
]
initialize [
identities := OrderedCollection new.
]
useragent [
^useragent
]
useragent: aUseragent [
useragent := aUseragent
]
addIdentity: anIdentity [
identities add: anIdentity.
anIdentity
manager: self;
startRegistration.
]
available [
^identities select: [:each | each isAvailable]
]
availableAndUnused [
^identities select: [:each | each isAvailable and: [each isUnused]]
]
]

66
osmo-st-msc/start.st Normal file
View File

@ -0,0 +1,66 @@
"
Copyright (C) 2012 Holger Hans Peter Freyther
Configure and start a MSC
"
"Load the MSC code"
PackageLoader fileInPackage: #OsmoMSC.
"Fix some defaults in the openbsc"
OsmoMSC.GSMProcessor class extend [
createAssignment: aMul timeslot: aTs [
| ass |
<category: 'audio-connect'>
ass := IEMessage initWith: GSM0808Helper msgAssRequest.
ass
addIe: ((GSM0808ChannelTypeIE
initWith: GSM0808ChannelTypeIE speechSpeech
audio: GSM0808ChannelTypeIE chanSpeechFullPref)
audioCodecs: {GSM0808ChannelTypeIE speechFullRateVersion1};
yourself);
addIe: (GSM0808CICIE initWithMultiplex: aMul timeslot: aTs).
^ ass
]
]
OsmoMSC.MSCApplication extend [
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
]
]
"Now start the application"
Eval [
| msc |
msc := OsmoMSC.MSCApplication new.
msc config
bscIP: '0.0.0.0';
bscPort: 5000;
sipIP: '127.0.0.1'.
msc bscConfig
addBSC: '127.0.0.1' withName: 'test1' andLac: 4711 sendOsmoRSIP: true;
addBSC: '10.240.240.1' withName: 'test2' andLac: 4712 sendOsmoRSIP: true.
"Start processing now"
msc returnedFromSnapshot.
Smalltalk at: #MSC put: msc.
]

View File

@ -0,0 +1,89 @@
"
(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/>.
"
TestCase subclass: AuthTestIdentity [
<category: 'OsmoMSC-Tests'>
<comment: 'I test various aspects of the IMSI requestor.'>
testWrongResponse [
| auth rejected wait |
Transcript nextPutAll: 'Going to send a wrong response leading to an exception.'; nl.
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockForAuthCheat initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
]
testTimeout [
| auth rejected wait |
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockForAuthTimeout initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
]
testIMSI [
| auth accept wait |
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | self assert: a = auth. accept := true. wait signal];
onReject: [:a | ^self error: 'This should not be rejected'];
yourself.
auth
connection: (GSMProcessorMockForAuthIMSI initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: accept.
self assert: (auth connection getInfo: 'IMSI') = auth connection usedIMSI.
]
testWrongInitialMessage [
| auth rejected wait |
Transcript nextPutAll: 'Going to send an initial message'; nl.
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockBase initWith: auth);
start: OsmoGSM.GSM48IdentityReq new.
wait wait.
self assert: rejected.
]
]

View File

@ -0,0 +1,51 @@
"
(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/>.
"
TestCase subclass: AuthTestNull [
<category: 'OsmoMSC-Tests'>
<comment: 'I smoke-test the null authenticator and that it
fires an accept callback right away.'>
testImmediateAccept [
| auth accepted |
auth := GSMNullAuthenticator new
onAccept: [:a| self assert: a = auth. accepted := true];
onReject: [:a| self shouldNotImplement];
yourself.
auth start: OsmoGSM.GSM48CMServiceReq new.
self assert: accepted.
]
testWrongInitialMessage [
| auth rejected wait |
Transcript nextPutAll: 'Going to send an initial message'; nl.
wait := Semaphore new.
auth := GSMNullAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: nil;
start: OsmoGSM.GSM48IdentityReq new.
wait wait.
self assert: rejected.
]
]

View File

@ -0,0 +1,67 @@
"
(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/>.
"
TestCase subclass: BSCConfigTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I will test the BSCConfig'>
testConfigItem [
| item1 item2 addr |
addr := Sockets.SocketAddress byName: '127.0.0.1'.
item1 := BSCConfigItem initWith: '127.0.0.1' name: 'test1'.
item2 := BSCConfigItem initWith: addr name: 'test2'.
self assert: item1 name = 'test1'.
self assert: item1 peer = addr.
self assert: item1 lac = -1.
self deny: item1 connected.
self assert: item2 name = 'test2'.
self assert: item2 peer = addr.
self assert: item2 lac = -1.
self deny: item2 connected.
]
testConfig [
| cfg |
"Test that adding stuff again is refused"
cfg := BSCConfig new.
self shouldnt:
[cfg addBSC: '127.0.0.1' withName: 'abc1' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Simply adding it'.
self should:
[cfg addBSC: '127.0.0.1' withName: 'abc2' andLac: 1123 sendOsmoRSIP: false]
raise: Exception description: 'Same IP is forbidden'.
self should:
[cfg addBSC: '127.0.0.2' withName: 'abc3' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Different IP same lac'.
self shouldnt:
[cfg addBSC: '127.0.0.2' withName: 'abc4' andLac: 1123 sendOsmoRSIP: false]
raise: Exception description: 'Different IP, different lac'.
self assert: cfg bscList size = 2 description: 'Two BSCs should be registered'.
cfg removeBSC: '127.0.0.1'.
self assert: cfg bscList size = 1 description: 'One BSC should be gone'.
cfg removeBSCByLac: 1123.
self assert: cfg bscList size = 0 description: 'All BSCsshould be removed'.
]
]

View File

@ -0,0 +1,30 @@
"
(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/>.
"
TestCase subclass: BSCIPAConnectionTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I just do some simple smoke testing here'>
testSmoke [
| ipa |
ipa := BSCIPAConnection
createOn: 'hi' writeStream
withConfig: (BSCConfigItem initWith: '0.0.0.0' name: 'foo')
msc: nil.
]
]

View File

@ -0,0 +1,47 @@
"
(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/>.
"
TestCase subclass: BSCListenerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'Test some basic socket functionality'>
testListenAndStop [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
'Will attempt to stop the connection' printNl.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
"Test that it will work again"
'Will attempt to stop the connection2' printNl.
listener start.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
]
testListenOnDeadSocket [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
listener stop.
res := listener serve.
self deny: res.
]
]

View File

@ -0,0 +1,45 @@
"
(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/>.
"
Object subclass: GSMProcessorMockBase [
| auth dict |
<category: 'OsmoMSC-Tests'>
GSMProcessorMockBase class >> initWith: anAuth [
^ self new
instVarNamed: #auth put: anAuth;
instVarNamed: #dict put: Dictionary new;
yourself.
]
addInfo: aName value: aValue [
dict at: aName put: aValue.
]
getInfo: aName [
^ dict at: aName
]
srcRef [
^ 1
]
takeLocks: aBlock [
aBlock value
]
]

View File

@ -0,0 +1,32 @@
"
(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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthCheat [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imei: '234324234234'.
auth onData: msg.]
]
]

View File

@ -0,0 +1,36 @@
"
(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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthIMSI [
<category: 'OsmoMSC-Tests'>
usedIMSI [
^ '234324234234'
]
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imsi: self usedIMSI.
auth onData: msg.]
]
]

View File

@ -0,0 +1,25 @@
"
(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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthTimeout [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Do nothing"
]
]

View File

@ -0,0 +1,23 @@
"
(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/>.
"
HLRResolver subclass: HLRDummyResolver [
<category: 'OsmoMSC-Tests'>
insertSubscriber: aIMSI [ ^ true ]
]

View File

@ -0,0 +1,35 @@
"
(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/>.
"
TestCase subclass: HLRTest [
<category: 'OsmoMSC-Tests'>
testHLRFind [
| hlr sub |
hlr := HLRLocalCollection new.
hlr addSubscriber: '123456'.
hlr addSubscriber: '345677'.
self deny: (hlr findSubscriberByIMSI: '123456') isNil.
self deny: (hlr findSubscriberByIMSI: '345677') isNil.
self assert: (hlr findSubscriberByIMSI: '432432') isNil.
sub := hlr findSubscriberByIMSI: '123456'.
self assert: sub imsi = '123456'.
]
]

View File

@ -0,0 +1,37 @@
"
(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/>.
"
TestCase subclass: MSCBSCConnectionHandlerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I should test the feature that each config can only
be connected once but that is not done yet. It requires some work
on socket code. TODO!!!'>
testOnlyOnce [
"
| msc socket bsc |
msc := MSCApplication new.
msc bscConfig addBSC: '127.0.0.1' withName: 'foo' andLac: 4711.
bsc := msc bscConfig bscList first.
socket := DummySocket new.
socket instVarNamed: #peer put: bsc peer.
socket instVarNamed: #closed put: false.
"
]
]

View File

@ -0,0 +1,38 @@
"
(C) 2014 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/>.
"
Object subclass: MockSIPUserAgent [
MockSIPUserAgent class >> generateBranch [
^'z9hG4bK776asdhds'
]
generateVia: aBranch [
^'SIP/2.0/UDP pc33.atlanta.com;branch=', aBranch
]
addTransaction: aTransaction [
]
injectDefaults: aRequest [
aRequest addParameter: 'Max-Forwards' value: '70'.
aRequest addParameter: 'User-Agent' value: 'mock'.
]
queueData: aData dialog: aDialog [
]
]

View File

@ -0,0 +1,35 @@
"
(C) 2014 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/>.
"
TestCase subclass: SIPIdentityManagerTest [
testEmpty [
| manager |
manager := SIPIdentityManager new.
self assert: manager available isEmpty.
]
testAvailable [
| manager |
manager := SIPIdentityManager initWith: MockSIPUserAgent new.
manager addIdentity: (MSCSIPIdentity new
username: 'user';
hostname: 'localhost';
yourself).
self assert: manager available isEmpty.
]
]

View File

@ -0,0 +1,38 @@
"
(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/>.
"
TestCase subclass: VLRTest [
<category: 'OsmoMSC-Tests'>
testVLRFind [
| vlr sub1 sub2 |
vlr := VLRLocalCollection initWith: HLRDummyResolver new.
self assert: (vlr insertSubscriber: '123456').
sub1 := vlr findSubscriberByIMSI: '123456' ifAbsent: [2342].
self assert: sub1 imsi = '123456'.
self assert: sub1 tmsi isNil.
sub2 := vlr findSubscriberByTMSI: 2342 ifAbsent: [true].
self assert: (sub2 isKindOf: True).
sub1 instVarNamed: #tmsi put: 2342.
sub2 := vlr findSubscriberByTMSI: 2342 ifAbsent: [false].
self assert: sub1 = sub2.
]
]