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

GSM: Introduce the concept of a 'driver' and a procedure

The procedure holds the driver... everything is still very
vague and needs a better design.
This commit is contained in:
Holger Hans Peter Freyther 2010-11-29 16:53:00 +01:00
parent 5a54fe3caf
commit e73c39f5e1
5 changed files with 152 additions and 69 deletions

102
GSMDriver.st Normal file
View File

@ -0,0 +1,102 @@
Object subclass: GSMDriver [
| goal sccp proc completeSem result |
<category: 'osmo-gsm-operation'>
<comment: 'I create a SCCP connection and handle stuff on it. In the base class
I am just capable of handling BSSMAP Management and need to dispatch it to other
classes.'>
GSMDriver class >> new [
<category: 'private'>
^ super new initialize; yourself
]
GSMDriver class >> initWith: aSCCPConnection goal: aGoal [
<category: 'creation'>
^ self new
goal: aGoal;
sccp: aSCCPConnection;
yourself
]
initialize [
<category: 'private'>
completeSem := Semaphore new.
]
result [
^ result
]
waitForCompletion [
<category: 'accessing'>
^ completeSem wait
]
goal: aGoal [
<category: 'manage'>
goal := aGoal.
]
sccp: aSCCPConnection [
sccp := aSCCPConnection
]
run [
<category: 'processing'>
"Process all messages in a thread"
proc := [
[
[true] whileTrue: [
| msg |
msg := sccp next.
self dispatch: msg.
].
] on: SystemExceptions.EndOfStream do: [
completeSem signal.
].
] fork.
]
cleanUp [
<category: 'protected'>
]
dispatch: aMsg [
<category: 'protected'>
taMsg inspect.
]
]
Object subclass: LUProcedure [
| driver conn |
LUProcedure class >> initWith: aHandler [
^ self new
createConnection: aHandler;
yourself
]
createConnection: aHandler [
| lu bssap msg sccp |
lu := GSM48LURequest new.
lu mi imsi: '666666666666'.
msg := IEMessage initWith: GSM0808Helper msgComplL3.
msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 4099 ci: 40000).
msg addIe: (GSMLayer3Info initWith: lu).
bssap := BSSAPManagement initWith: msg.
conn := aHandler createConnection: bssap.
]
execute [
driver := GSMDriver initWith: conn goal: #lu.
driver run.
driver waitForCompletion.
'LUProcedure is completed' printNl.
]
]

View File

@ -1,7 +1,12 @@
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
| src dst queue conManager confirmSem proc |
| src dst queue conManager confirmSem proc state |
SCCPConnection class >> stateInitial [ ^ 0 ]
SCCPConnection class >> stateConnected [ ^ 1 ]
SCCPConnection class >> stateReleased [ ^ 2 ]
SCCPConnection class >> stateTimeout [ ^ 3 ]
SCCPConnection class >> new [
^ super new
@ -9,7 +14,9 @@ Object subclass: SCCPConnection [
]
initialize [
state := SCCPConnection stateInitial.
confirmSem := Semaphore new.
queue := SharedQueue new.
]
conManager: aHandler [
@ -19,7 +26,7 @@ Object subclass: SCCPConnection [
readQueue [
<category: 'private'>
^ queue ifNil: [ queue := SharedQueue new. ]
^ queue
]
srcRef [
@ -41,44 +48,44 @@ Object subclass: SCCPConnection [
^ dst
]
cleanUp [
"I get called at the end of a SCCP connection"
<category: 'connection-handling'>
next [
"Read the next item. If the connection is terminated"
| msg |
('Cleaningup the SCCP connection: ', dst asString) printNl.
conManager := nil.
queue := nil.
proc := nil.
]
handleMessages [
proc := [
[
"Wait for the connection or return"
"If we are not connected we need to wait"
state = SCCPConnection stateInitial
ifTrue: [
self waitForConfirmation.
].
'SCCP Connection Confirmed' printNl.
"If we are not connected here. Send a EndOfStream signal"
state = SCCPConnection stateConnected
ifFalse: [
^ SystemExceptions.EndOfStream signal
].
[true] whileTrue: [
| msg |
msg := self readQueue next.
msg := self readQueue next.
msg inspect.
].
] ensure: [
"An exception? an error?"
self cleanUp.
]
] fork.
"If this is a small integer our connection is gone"
(msg isKindOf: SmallInteger)
ifTrue: [
^ SystemExceptions.EndOfStream signal
].
"We do have a real message"
^ msg
]
nextPut: aMsg [
conManager sendMsg: aMsg.
]
waitForConfirmation [
"Wait for the connection to be confirmed and then exit"
((Delay forSeconds: 10) timedWaitOn: confirmSem)
ifTrue: [
state := SCCPConnection stateTimeout.
conManager connectionTimeout: self.
^ false
].
@ -86,9 +93,16 @@ Object subclass: SCCPConnection [
^ true
]
"SCCP Connection state handling"
terminate [
self readQueue nextPut: 0.
]
confirm: aCC [
<category: 'connection-handling'>
self dstRef: aCC src.
state := SCCPConnection stateConnected.
confirmSem signal.
]
@ -100,21 +114,12 @@ Object subclass: SCCPConnection [
| rlc |
"Give up local resources here. We are done."
state := SCCPConnection stateReleased.
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self sendMsg: rlc toMessage.
self nextPut: rlc toMessage.
self terminate.
]
terminate [
proc ifNotNil: [
proc terminate.
].
]
sendMsg: aMsg [
conManager sendMsg: aMsg.
]
]
Object subclass: MSGParser [
@ -169,7 +174,6 @@ Object subclass: SCCPHandler [
connectionTimeout: aConnection [
('SCCP Connection ', aConnection srcRef asString, ' timeout.') printNl.
aConnection terminate.
self connections remove: aConnection.
]
@ -239,9 +243,9 @@ Object subclass: SCCPHandler [
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self connections add: con.
con handleMessages.
self sendMsg: res toMessage.
^ res
^ con
]
referenceIsFree: aRef [

View File

@ -97,26 +97,9 @@ Object subclass: IPAConfig [
semaphore [ ^ sem ]
sendLU [
| msg |
msg := MessageTests createLU: (connection sccpHandler).
connection send: msg with: Osmo.IPAConstants protocolSCCP.
| proc |
proc := LUProcedure initWith: (connection sccpHandler).
proc execute.
]
]
Object subclass: MessageTests [
MessageTests class >> createLU: aHandler [
| lu bssap msg sccp |
lu := GSM48LURequest new.
lu mi imsi: '666666666666'.
msg := IEMessage initWith: GSM0808Helper msgComplL3.
msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 4099 ci: 40000).
msg addIe: (GSMLayer3Info initWith: lu).
bssap := BSSAPManagement initWith: msg.
sccp := aHandler createConnection: bssap.
^ sccp toMessage.
]
]

View File

@ -210,14 +210,6 @@ SCCPHandler subclass: TestSCCPHandler [
]
TestCase subclass: TestMessages [
testLU [
| sccp handler |
handler := TestSCCPHandler new.
sccp := MessageTests createLU: handler.
self assert: sccp asByteArray = #(1 154 2 0 2 2 4 2 66 254 15 32 0 30 87 5 8 0 114 244 128 16 3 156 64 23 17 5 8 112 0 240 0 0 0 51 7 97 102 102 102 102 102 246 0 ) asByteArray.
]
testMsgParser [
| msg bssap bssmap ies l3 gsm48 inp |

View File

@ -9,6 +9,7 @@
<filein>BSSMAP.st</filein>
<filein>GSM48.st</filein>
<filein>SCCPHandler.st</filein>
<filein>GSMDriver.st</filein>
<filein>TestPhone.st</filein>
<test>
@ -24,6 +25,7 @@
<file>Messages.st</file>
<file>SCCPHandler.st</file>
<file>GSM48.st</file>
<file>GSMDriver.st</file>
<file>TestPhone.st</file>
<file>Tests.st</file>
</package>