PackageLoader fileInPackage: 'OsmoNetwork'. Object subclass: SCCPConnection [ | 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 initialize; yourself ] initialize [ state := SCCPConnection stateInitial. confirmSem := Semaphore new. queue := SharedQueue new. ] conManager: aHandler [ conManager := aHandler. ] readQueue [ ^ queue ] srcRef [ ^ src ] srcRef: aRef [ src := aRef ] dstRef: aRef [ dst := aRef ] dstRef [ ^ dst ] next [ "Read the next item. If the connection is terminated" | msg | "If we are not connected we need to wait" state = SCCPConnection stateInitial ifTrue: [ self waitForConfirmation. ]. "If we are not connected here. Send a EndOfStream signal" state = SCCPConnection stateConnected ifFalse: [ ^ SystemExceptions.EndOfStream signal ]. msg := self readQueue next. "If this is a small integer our connection is gone" (msg isKindOf: SmallInteger) ifTrue: [ ^ SystemExceptions.EndOfStream signal ]. "We do have a real message" ^ msg ] nextPutData: aMsg [ | dt1 | dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg. self nextPut: dt1 toMessage. ] 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 ]. ^ true ] "SCCP Connection state handling" terminate [ self readQueue nextPut: 0. ] confirm: aCC [ self dstRef: aCC src. state := SCCPConnection stateConnected. confirmSem signal. ] data: aDT [ self readQueue nextPut: aDT data. ] released: aRLSD [ | rlc | "Give up local resources here. We are done." state := SCCPConnection stateReleased. rlc := Osmo.SCCPConnectionReleaseComplete initWithDst: aRLSD src src: aRLSD dst. self nextPut: rlc toMessage. self terminate. ] ] 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). ]. ^ sccp ] MSGParser class >> decodeBSSAP: aData [ | bssap | bssap := BSSAPMessage decode: aData. bssap class msgType = BSSAPDTAP msgType ifTrue: [ bssap data: (GSM48MSG decode: bssap data) ] ifFalse: [ bssap data: (self decodeBSSMAP: bssap data). ]. ^ bssap ] MSGParser class >> decodeBSSMAP: aData [ | bssmap | bssmap := IEMessage decode: aData with: GSM0808IE. bssmap findIE: (GSMLayer3Info elementId) ifPresent: [:each | each data: (GSM48MSG decode: each data). ]. ^ bssmap ] ] Object subclass: SCCPHandler [ | connections last_ref connection | registerOn: aDispatcher [ aDispatcher addHandler: Osmo.IPAConstants protocolSCCP on: self with: #handleMsg:. ] connectionTimeout: aConnection [ ('SCCP Connection ', aConnection srcRef asString, ' timeout.') printNl. self connections remove: aConnection. ] forwardMessage: aMessage with: aConnection[ (aMessage isKindOf: Osmo.SCCPConnectionConfirm) ifTrue: [ aConnection confirm: aMessage. ^ true ]. (aMessage isKindOf: Osmo.SCCPConnectionData) ifTrue: [ aConnection data: aMessage. ^ true ]. (aMessage isKindOf: Osmo.SCCPConnectionReleased) ifTrue: [ aConnection released: aMessage. self connections remove: aConnection. ^ true ]. "Message is not handled here" ^ false ] dispatchMessage: aMessage [ self connections do: [:each | each srcRef = aMessage dst ifTrue: [ ^ self forwardMessage: aMessage with: each. ]. ]. 'No one has handled the connection with ', aMessage dst asString printNl. ] handleMsg: aMsg [ | sccp | [ sccp := MSGParser parse: (aMsg asByteArray). ] on: Exception do: [ self logError: 'Failed to parse message' area: #sccp. aMsg asByteArray printNl. ^ false ]. self dispatchMessage: sccp. ] connection: aConnection [ connection := aConnection. ] sendMsg: aMsg [ "Send a SCCP message." connection send: aMsg with: Osmo.IPAConstants protocolSCCP. ] createConnection: aData [ | con res| con := SCCPConnection new. con srcRef: self assignSrcRef. con conManager: self. res := Osmo.SCCPConnectionRequest initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData. self connections add: con. self sendMsg: res toMessage. ^ con ] 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. ] ] ]