diff --git a/GSMProcessor.st b/GSMProcessor.st index 35870a9..cc2d6c3 100644 --- a/GSMProcessor.st +++ b/GSMProcessor.st @@ -97,57 +97,94 @@ GSMTransaction subclass: GSMLURequest [ ] OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [ - | transactions | + | transactions state | + GSMProcessor class >> stateInitial [ ^ 0 ] + GSMProcessor class >> stateAcked [ ^ 1 ] + GSMProcessor class >> stateRelease [ ^ 2 ] + GSMProcessor class >> stateError [ ^ 3 ] + initialize [ + transactions := OrderedCollection new. + state := self class stateInitial. ^ super initialize. ] data: aData [ | msg bssmap data | + "The first message should be a Complete Layer3 Information" - aData data dispatchTrans: self. + [ + aData data dispatchTrans: self. + ] on: Error do: [:e | + e logException: 'Failed to dispatch: %1' % {e tag} area: #bsc. + self forceClose. + ] + ] + + bssapUnknownData: aData [ + + "This is now the GSM data" + self forceClose. + ] + + mapLayer3: bssap [ + | layer3 | + + + "Check and move state" + 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. + ]. + + + layer3 inspect. (GSMMOCall on: 0 with: 0) con: self; initial. - ] - bssapUnknownData: aData [ - - "This is now the GSM data" - self conManager critical: [self release]. - ] - - mapLayer3: aData [ - - 'MAP Layer3' printNl. + self clearCommand: 9. ] mapClearReq: aData [ 'CLEAR Request' printNl. + self verifyState: [(state > self class stateInitial) and: [state < self class stateError]]. + + self clearCommand: 0. ] mapClearCompl: aData [ - 'CLEAR COMPL' printNl. + self verifyState: [state = self class stateRelease]. + self release. ] mapCipherModeCompl: aData [ 'CIPHER MODE COMPL' printNl. + aData inspect. ] mapAssComplete: aData [ 'ASSIGNMENT COMPL' printNl. + aData inspect. ] terminate [ @@ -156,4 +193,38 @@ hosting various transactions and dispatching to them.'> transactions do: [:each | each cancel] ] + + verifyState: aBlock [ + + + aBlock value ifFalse: [ + self logError: 'GSMProc(srcref:%1) wrong state: %2.' % {self srcRef. state} area: #bsc. + ^ self error: 'Failed to verify the state.'. + ]. + ] + + forceClose [ + + sem critical: [ + state = self class stateError ifTrue: [ + "Already closing down" + ^ false + ]. + + state := self class stateError + ]. + + self release + ] + + clearCommand: aCause [ + | msg | + + + state := self class stateRelease. + + msg := OsmoGSM.IEMessage initWith: OsmoGSM.GSM0808Helper msgClear. + msg addIe: (OsmoGSM.GSMCauseIE initWith: aCause). + self nextPutData: (OsmoGSM.BSSAPManagement initWith: msg). + ] ]