" (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 . " PackageLoader fileInPackage: #OsmoASN1. OsmoGSM.SCCPConnectionBase subclass: GSMConnection [ | sapis completeSem phoneConfig mainProc | GSMConnection class >> on: aHandler withPhone: aPhone [ ^ (self on: aHandler) phone: aPhone; yourself ] initialize [ super initialize. completeSem := Semaphore new. sapis := Dictionary new. ] completeSem [ ^ completeSem ] isComplete [ ^ completeSem signals > 0 ] waitForTermination [ "I wait until the connection is closed" ^ completeSem wait ] setProc: aProc [ mainProc := aProc. mainProc connection: self. sapis at: aProc sapi put: aProc. ] openConnection [ self connectionRequest: mainProc completeLayer3. ] mainProc [ ^ mainProc ] phone: aPhone [ phoneConfig := aPhone. ] phone [ ^ phoneConfig ] sendClearRequest [ | clear | clear := IEMessage initWith: GSM0808Helper msgClearReq. clear addIe: (GSMCauseIE initWith: 0). self nextPutData: (BSSAPManagement initWith: clear). ] data: aDT [ [ self dispatch: aDT data. ] on: Error do: [:e | 'SCCP Cleaning up connection' printNl. self sendClearRequest. ] ] terminate [ completeSem signal. ] cleanUp [ ] dispatchMan: aMsg [ aMsg type = GSM0808Helper msgClear ifTrue: [ | resp | resp := IEMessage initWith: GSM0808Helper msgClearComp. self nextPutData: (BSSAPManagement initWith: resp). ^ true ]. aMsg type = GSM0808Helper msgCipherModeCmd ifTrue: [ | resp | resp := IEMessage initWith: GSM0808Helper msgCipherModeCmpl. resp addIe: (GSM0808ChosenEncrIE initWith: 1). self nextPutData: (BSSAPManagement initWith: resp). self dispatchCMAccept. ^ true ]. aMsg type = GSM0808Helper msgAssRequest ifTrue: [ | resp | "Reply with a AMR halfrate statement" resp := IEMessage initWith: GSM0808Helper msgAssComplete. resp addIe: (GSM0808CauseIE initWith: 0). resp addIe: (GSM0808ChosenChannel initWith: 16r98). resp addIe: (GSM0808ChosenEncrIE initWith: 1). resp addIe: (GSM0808SpeechVerIE initWith: 16r25). self nextPutData: (BSSAPManagement initWith: resp). ^ true ]. 'Unhandled message' printNl. aMsg inspect. ] auKey [ ^ phoneConfig auKeyByteArray. ] imsi [ ^ phoneConfig imsi. ] dispatchDTAP: aMsg sapi: aSapi [ aMsg class messageType = GSM48MMMessage msgAuReq ifTrue: [ | auth resp | 'Authentication....' printNl. auth := A3A8 COMP128: phoneConfig auVer ki: self auKey rand: aMsg auth data. resp := GSM48AuthResp new. resp sres data: (auth copyFrom: 1 to: 4). self nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). ^ true ]. aMsg class messageType = GSM48MMMessage msgCMAccept ifTrue: [ self dispatchCMAccept. ^ true ]. sapis at: aSapi ifPresent: [:handler | handler handleData: aMsg sapi: aSapi. ]. 'Unhandled DTAP message' printNl. aMsg inspect. ] dispatch: aMsg [ aMsg class msgType = BSSAPHelper msgManagemnt ifTrue: [ self dispatchMan: aMsg data. ] ifFalse: [ self dispatchDTAP: aMsg data sapi: aMsg sapi. ]. ] dispatchCMAccept [ sapis do: [:each | each serviceAccepted. ]. ] onConnectionConfirmed [ mainProc connectionConfirmed. ] ] Object subclass: ProcedureBase [ | success conn | connection: aConn [ conn := aConn ] sapi [ "Use SAPI 0 by default" ^ 0 ] completeLayer3 [ | msg | msg := IEMessage initWith: GSM0808Helper msgComplL3. msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 8210 ci: 30000). msg addIe: (GSMLayer3Info initWith: self initialMessage). ^ BSSAPManagement initWith: msg. ] success [ ^ success ifNil: [false] ] success: aSuc [ success := aSuc. ] serviceAccepted [ "TO BE implemented" ] status [ ^ self success ifTrue: ['Success'] ifFalse: ['Failure'] ] initialMessage [ "I should return the initial message of the transaction" self subclassResponsibility ] connectionConfirmed [ | cm | cm := GSM48RRClassmarkChange new. conn nextPutData: (BSSAPDTAP initWith: cm linkIdentifier: 0). ] ] ProcedureBase subclass: LUProcedure [ initialMessage [ | lu | lu := GSM48LURequest new. lu mi imsi: conn phone imsi. ^ lu ] name [ ^ 'Location Updating Procedure' ] status [ ^ self success ifTrue: ['LUAccept nicely succeeded.'] ifFalse: ['LURejected.'] ] handleData: aMsg sapi: aSapi [ aMsg class messageType = GSM48MMMessage msgLUAcc ifTrue: [ self success: true. ]. ] ] ProcedureBase subclass: CallProcedure [ | nr | CallProcedure class >> initWithNr: aNr [ ^ self new nr: aNr; yourself ] nr: aNr [ nr := (ByteArray with: 16r91), (GSMNumberDigits encodeFrom: aNr). ] initialMessage [ | cm | cm := GSM48CMServiceReq new. cm mi imsi: conn phone imsi. cm keyAndType val: 16r21. ^ cm ] name [ ^ 'Call Procedure' ] status [ ^ self success ifTrue: [ 'Call got accepted on the way.'] ifFalse: ['Call was never connected']. ] serviceAccepted [ | resp | 'Accepted' printNl. resp := GSM48CCSetup new. resp seq: 1. resp bearer1OrDefault data: #(16r60 16r02 0 1 4 16r85) asByteArray. resp calledOrDefault data: nr. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). ] handleData: aMsg sapi: aSapi [ aMsg class messageType = GSM48CCMessage msgProceeding ifTrue: [ | resp | resp := GSM48CCDisconnect new. resp seq: 1. resp cause data: #(16rE1 16r90). conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). ]. aMsg class messageType = GSM48CCMessage msgConnect ifTrue: [ | resp | resp := GSM48CCConnectAck new. resp seq: 1. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). self success: true. ]. aMsg class messageType = GSM48CCMessage msgDisconnect ifTrue: [ | resp | resp := GSM48CCRelease new. resp seq: 1. resp causeOrDefault data: #(16rE1 16r90) asByteArray. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0) ]. aMsg class messageType = GSM48CCMessage msgRelease ifTrue: [ | resp | resp := GSM48CCReleaseCompl new. resp seq: 1. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0) ]. ] ] ProcedureBase subclass: USSDProcedure [ | nr facility | USSDProcedure class >> initWithNr: aNr [ ^ self new nr: aNr; yourself ] USSDProcedure class >> buildProcessUnstructReq: aNr [ | req str | req := {BERTag fromTuple: #(2 true 1). OrderedCollection with: {BERTag integer. #(0).} with: {BERTag integer. #(59).} with: {BERTag fromTuple: #(0 true 16). OrderedCollection with: {BERTag octetString. #(15).} with: {BERTag octetString. aNr asUSSD7Bit}}}. str := WriteStream on: (ByteArray new: 40). (DERTLVStream on: str) nextPut: req. ^ str contents ] USSDProcedure class >> buildReturnLast: invokeId text: aText [ | ret str | ret := {BERTag fromTuple: #(2 true 2). OrderedCollection with: {BERTag integer. invokeId} with: {BERTag sequence. OrderedCollection with: {BERTag integer. #(60)} with: {BERTag sequence. OrderedCollection with: {BERTag octetString. #(15).} with: {BERTag octetString. aText asUSSD7Bit}}}}. str := WriteStream on: (ByteArray new: 40). (DERTLVStream on: str) nextPut: ret. ^ str contents ] nr: aNr [ nr := aNr. ] facility [ ^ facility ] initialMessage [ | cm | cm := GSM48CMServiceReq new. cm mi imsi: conn phone imsi. cm luType val: 8. ^ cm ] name [ ^ 'USSD Procedure' ] serviceAccepted [ | reg | reg := GSM48SSRegister new. reg ti: 1. reg facility data: (self class buildProcessUnstructReq: nr). reg ssVersionOrDefault data: #(0). conn nextPutData: (BSSAPDTAP initWith: reg linkIdentifier: 0). ] handleData: aMsg sapi: aSapi [ aMsg class messageType = GSM48SSMessage msgReleaseCompl ifTrue:[ facility := aMsg facility. self success: aMsg ti = 9. ]. aMsg class messageType = GSM48SSMessage msgFacility ifTrue: [ | fac | fac := GSM48SSFacility new. fac ti: 1. fac facility data: (self class buildReturnLast: #(1) text: '45050888658950'). conn nextPutData: (BSSAPDTAP initWith: fac linkIdentifier: 0). ] ] ]