" (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 . " PackageLoader fileInPackage: 'OsmoCore'; fileInPackage: 'OsmoNetwork'. Object subclass: SCCPConnectionState [ | src dst conManager confirmSem proc state sem | SCCPConnectionState class >> stateInitial [ ^ 0 ] SCCPConnectionState class >> stateRequested [ ^ 1 ] SCCPConnectionState class >> stateConnected [ ^ 2 ] SCCPConnectionState class >> stateReleased [ ^ 3 ] SCCPConnectionState class >> stateReleaseComplete [ ^ 4 ] SCCPConnectionState class >> stateTimeout [ ^ 5 ] SCCPConnectionState class >> new [ ^ self shouldNotImplement ] SCCPConnectionState class >> on: aHandler [ ^(self basicNew) initialize; conManager: aHandler; yourself ] initialize [ state := self class stateInitial. confirmSem := Semaphore new. sem := RecursionLock new. ] conManager: aHandler [ "Check if it is not there otherwise bad things happen" conManager ifNotNil: [ ^ self error: 'Can only be set once.'. ]. conManager := aHandler. conManager addConnection: self ] critical: aBlock [ sem critical: [aBlock value] ] state [ ^ state ] conManager [ ^ conManager ] srcRef [ ^ src ] srcRef: aRef [ src := aRef ] dstRef: aRef [ dst := aRef ] dstRef [ ^ dst ] changeState: newState do: aBlock [ sem critical: [ state := newState. aBlock value. ] ] connectionRequest: aData [ | res | "Send the confirmation now" self changeState: self class stateRequested do: [ self startConnEstTimer. res := Osmo.SCCPConnectionRequest initWith: (self srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData. self nextPut: res toMessage. ]. ] confirm: aCC [ self changeState: self class stateConnected do: [ self dstRef: aCC src. self startConfirmTimer. confirmSem signal. ]. self onConnectionConfirmed. ] release [ | rlsd | self changeState: self class stateReleased do: [ self startReleaseTimer. rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0. self nextPut: rlsd toMessage. ] ] releaseComplete: aMSG [ "TODO: verify that we are in the right state" self changeState: self class stateReleaseComplete do: [ self finish. ] ] released: aRLSD [ | rlc | "Give up local resources here. We are done." self changeState: self class stateReleaseComplete do: [ rlc := Osmo.SCCPConnectionReleaseComplete initWithDst: aRLSD src src: aRLSD dst. self nextPut: rlc toMessage. self finish. ] ] nextPutData: aMsg [ | dt1 | dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg. sem critical: [ self startTias. self nextPut: dt1 toMessage]. ] nextPut: aMsg [ conManager sendMsg: aMsg. ] onConnectionConfirmed [ "Re-implement to deal with notifications. There are no locks held." ] ] SCCPConnectionState subclass: SCCPConnectionBase [ | t_conn_est t_ias t_iar t_rel t_repeat_rel t_int | SCCPConnectionBase class [ tconnEstTime [ ^ 60 ] tiasTime [ ^ 5 * 60 ] tiarTime [ ^ 15 * 60 ] trelTime [ ^ 15 ] trepeatRelTime [ ^ 15 ] tintTime [ ^ 60 ] ] stopAllTimers [ sem critical: [ t_conn_est ifNotNil: [t_conn_est cancel. t_conn_est := nil]. t_ias ifNotNil: [t_ias cancel. t_ias := nil]. t_iar ifNotNil: [t_iar cancel. t_iar := nil]. t_rel ifNotNil: [t_rel cancel. t_rel := nil]. t_repeat_rel ifNotNil: [t_repeat_rel cancel. t_repeat_rel := nil]. t_int ifNotNil: [t_int cancel. t_int := nil]. ] ] finish [ self stopAllTimers; terminate. ] schedule: aTime block: aBlock [ "I make sure that the SCCPConnManager and SCCPCon locks are held" ^ Osmo.TimerScheduler instance scheduleInSeconds: aTime block: [ conManager critical: [sem critical: [aBlock value]]]. ] startConnEstTimer [ self stopAllTimers. t_conn_est := self schedule: self class tconnEstTime block: [self conTimeout]. ] conTimeout [ conManager connectionTimeout: self. ] startConfirmTimer [ t_conn_est ifNotNil: [t_conn_est cancel. t_conn_est := nil]. self startTias. self startTiar. ] startTias [ t_ias ifNotNil: [t_ias cancel. t_ias := nil]. state = self class stateConnected ifTrue: [ t_ias := self schedule: self class tiasTime block: [self sendInactivty]]. ] startTiar [ t_iar ifNotNil: [t_iar cancel. t_iar := nil]. state = self class stateConnected ifTrue: [ t_iar := self schedule: self class tiarTime block: [self sendRelease]]. ] sendInactivty [ | it | it := Osmo.SCCPInactivityTest initWithDst: self dstRef src: self srcRef. sem critical: [ self startTias. self nextPut: it toMessage]. ] sendRelease [ (state = self class stateConnected) ifTrue: [ self logError: 'SCCP(srcref:%1) rel con due inactivity.' % {self srcRef} area: #sccp. self release. ] ] startReleaseTimer [ "We might be called multiple times and we use some variables to figure out if we are the one or the other." t_ias ifNotNil: [t_ias cancel]. t_iar ifNotNil: [t_iar cancel]. t_rel isNil ifTrue: [ t_rel := self schedule: self class trelTime block: [self releaseTimeout]] ifFalse: [ self startReleaseRepeatTimer.]. ] releaseTimeout [ self logError: 'SCCP(srcref:%1) RLC timeout.' % {self srcRef} area: #sccp. t_int := self schedule: self class tintTime block: [self forceRelease]. self release. ] startReleaseRepeatTimer [ t_repeat_rel ifNotNil: [t_repeat_rel cancel. t_repeat_rel := nil]. t_repeat_rel := self schedule: self class trepeatRelTime block: [self release]. ] forceRelease [ conManager addToFreezeList: self. conManager connectionTimeout: self. ] ] SCCPConnectionBase subclass: SCCPConnection [ data: aDT [ "nothing implemented" ] terminate [ "noting implemented" ] ] Object subclass: MSGParser [ MSGParser class >> parse: aByteArray [ | sccp | "Return a completely decoded subtree" sccp := Osmo.SCCPMessage decode: aByteArray. (sccp respondsTo: #data) ifTrue: [ sccp data: (self decodeBSSAP: sccp data readStream). ]. ^ sccp ] MSGParser class >> decodeBSSAP: aStream [ | bssap | bssap := BSSAPMessage decode: aStream. bssap class msgType = BSSAPDTAP msgType ifTrue: [ bssap data: (GSM48MSG decode: bssap data readStream) ] ifFalse: [ bssap data: (self decodeBSSMAP: bssap data readStream). ]. ^ bssap ] MSGParser class >> decodeBSSMAP: aStream [ | bssmap | bssmap := IEMessage decode: aStream with: GSM0808IE. bssmap findIE: (GSMLayer3Info elementId) ifPresent: [:each | each data: (GSM48MSG decode: each data readStream). ]. ^ bssmap ] ] Osmo.SCCPMessage extend [ sccpInitialDispatch: aHandler [ ^ aHandler dispatchMessage: self. ] sccpHandlerDispatchOn: aCon [ "Message is not handled here" self logError: 'Unhandled SCCP packet %1' % {self class} area: #sccp. ^ false ] ] Osmo.SCCPUDT extend [ sccpInitialDispatch: aHandler [ aHandler handleUDT: self. ^ true ] ] Osmo.SCCPConnectionRequest extend [ sccpInitialDispatch: aHandler [ self logNotice: 'New incoming connection' area: #sccp. aHandler confirmConnection: self. ^ true ] ] Osmo.SCCPConnectionConfirm extend [ sccpHandlerDispatchOn: aCon [ aCon confirm: self. ^ true ] ] Osmo.SCCPConnectionData extend [ sccpHandlerDispatchOn: aCon [ aCon critical: [aCon startTiar]. aCon data: self. ^ true ] ] Osmo.SCCPConnectionReleased extend [ sccpHandlerDispatchOn: aCon [ aCon released: self. aCon conManager removeConnection: aCon. ^ true ] ] Osmo.SCCPConnectionReleaseComplete extend [ sccpHandlerDispatchOn: aCon [ aCon releaseComplete: self. aCon conManager removeConnection: aCon. ^ true ] ] Osmo.SCCPInactivityTest extend [ sccpHandlerDispatchOn: aCon [ aCon critical: [aCon startTiar]. ] ] Object subclass: SCCPHandler [ | connections connection sem | SCCPHandler class >> dissectMSG: aMsg [ ^ MSGParser parse: (aMsg asByteArray). ] SCCPHandler class >> new [ ^self basicNew initialize ] initialize [ sem := Semaphore forMutualExclusion. ] registerOn: aDispatcher [ aDispatcher addHandler: Osmo.IPAConstants protocolSCCP on: self with: #handleMsg:. ] connection: aConnection [ connection := aConnection. ] critical: aBlock [ ^ sem critical: aBlock ] addConnection: aConnection [ sem critical: [ self connections add: aConnection. aConnection srcRef: self assignSrcRef. ]. ] dispatchMessage: aMessage [ sem critical: [ self connections do: [:each | each srcRef = aMessage dst ifTrue: [ ^ aMessage sccpHandlerDispatchOn: each. ]. ] ]. self logError: 'No one handled connection %1' % {aMessage dst} area: #sccp. ] linkSetFailed [ "The underlying has failed, invalidate all connections" sem critical: [ self connections do: [:each | self doTerminate: each]. connections := nil. ] ] newConnection: aCon [ "Interesting for subclasses" ] connectionSpecies [ "Interesting for subclasses" ^ SCCPConnection ] handleUDT: aSCCP [ self logNotice: 'Incoming UDT message' area: #sccp. ] removeConnection: aConnection [ self connections remove: aConnection. ] addToFreezeList: aConnection [ "TODO: Implement the freeze list so some SCCP SRCREF will not be assigned for a given time." ] connectionTimeout: aConnection [ self logError: 'SCCP(srcref:%1) conn timedout' % {aConnection srcRef} area: #sccp. self doTerminate: aConnection. self removeConnection: aConnection. ] confirmConnection: aMsg [ | con res | con := self connectionSpecies on: self. "Confirm it without sending any new data bad" con confirm: aMsg. self newConnection: con. res := Osmo.SCCPConnectionConfirm initWithSrc: (con srcRef) dst: (con dstRef). self sendMsg: res toMessage. "Confirm the message now and send any data" sem critical: [ aMsg data ifNotNil: [ con data: aMsg. ]]. ^ con. ] handleMsg: aMsg [ | sccp | "I am called from the dispatcher for SCCP" [ sccp := self class dissectMSG: aMsg. ] on: Exception do: [:e | self logNotice: 'Failed to dissect SCCP payload' area: #sccp. ^ false ]. sccp sccpInitialDispatch: self. ] sendMsg: aMsg [ "Send a SCCP message." connection send: aMsg with: Osmo.IPAConstants protocolSCCP. ] referenceIsFree: aRef [ self connections do: [:each | each srcRef = aRef ifTrue: [ ^ false ]. ]. ^ true ] assignSrcRef [ "Find a free SCCP reference" 1 to: 16rFFFFFE do: [:dummy | | ref | ref := Random between: 1 and: 16rFFFFFE. (self referenceIsFree: ref) ifTrue: [ ^ ref. ]. ]. self error: 'No free SCCP Connection. Close some'. ] connections [ ^ connections ifNil: [ connections := OrderedCollection new. ] ] doTerminate: aCon [ "I kill the SCCP Connection." [ aCon finish. ] on: Error do: [:each | each logException: 'Failed to finish %1' % {aCon srcRef} area: #sccp. ] ] ]