Object subclass: GSMDriver [ | sccp proc sapis completeSem phoneConfig | GSMDriver class >> new [ ^ super new initialize; yourself ] GSMDriver class >> initWith: aSCCPConnection sapi: aSapi on: aProc phone: aPhone[ ^ self new sapi: aSapi on: aProc; sccp: aSCCPConnection; phone: aPhone; yourself ] initialize [ completeSem := Semaphore new. sapis := Dictionary new. ] waitForCompletion [ ^ completeSem wait ] waitWithTimeout: aTimeout [ | delay | delay := Delay forSeconds: aTimeout. delay timedWaitOn: completeSem. ] sapi: aSapi on: aProc [ sapis at: aSapi put: aProc. ] phone: aPhone [ phoneConfig := aPhone. ] sccp: aSCCPConnection [ sccp := aSCCPConnection ] run [ "Process all messages in a thread" proc := [ [ [ [true] whileTrue: [ | msg | msg := sccp next. self dispatch: msg. ]. ] on: SystemExceptions.EndOfStream do: [ 'SCCP Connection is now disconnected' printNl. ]. ] ensure: [ completeSem signal. ]. ] fork. ] cleanUp [ ] dispatchMan: aMsg [ aMsg type = GSM0808Helper msgClear ifTrue: [ | resp | resp := IEMessage initWith: GSM0808Helper msgClearComp. sccp nextPutData: (BSSAPManagement initWith: resp). ^ true ]. aMsg type = GSM0808Helper msgCipherModeCmd ifTrue: [ | resp | resp := IEMessage initWith: GSM0808Helper msgCipherModeCmpl. resp addIe: (GSM0808ChosenEncrIE initWith: 1). sccp 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). sccp nextPutData: (BSSAPManagement initWith: resp). ^ true ]. 'Unhandled message' printNl. aMsg inspect. ] auKey [ ^ phoneConfig auKey. ] imsi [ ^ phoneConfig imsi. ] dispatchDTAP: aMsg sapi: aSapi [ aMsg class messageType = GSM48MMMessage msgAuReq ifTrue: [ | auth resp | auth := A3A8 COMP128_v3: self auKey rand: aMsg auth data. resp := GSM48AuthResp new. resp sres data: (auth copyFrom: 1 to: 4). sccp 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. ]. aMsg inspect. ] dispatchCMAccept [ sapis do: [:each | each serviceAccepted. ]. ] ] Object subclass: ProcedureBase [ | driver conn success | ProcedureBase class >> initWith: aHandler phone: aPhone [ ^ self new createConnection: aHandler phone: aPhone; yourself ] openConnection: aMsg sapi: aSapi phone: aPhone handler: aHandler [ | msg bssap | msg := IEMessage initWith: GSM0808Helper msgComplL3. msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 4099 ci: 40000). msg addIe: (GSMLayer3Info initWith: aMsg). bssap := BSSAPManagement initWith: msg. conn := aHandler createConnection: bssap. driver := GSMDriver initWith: conn sapi: aSapi on: self phone: aPhone. 'Created the driver' printNl. ] run [ driver run. ] execute [ driver run. driver waitForCompletion. ] success [ ^ success ifNil: [false] ] success: aSuc [ success := aSuc. ] serviceAccepted [ "TO BE implemented" ] ] ProcedureBase subclass: LUProcedure [ createConnection: aHandler phone: aPhone [ | lu | lu := GSM48LURequest new. lu mi imsi: aPhone imsi. 'LU proc started' printNl. self openConnection: lu sapi: 0 phone: aPhone handler: aHandler. ] execute [ super execute. self success ifTrue: [ 'LUAccept nicely succeeded.' printNl. ] ifFalse: [ 'LURejected.' printNl. ] ] handleData: aMsg sapi: aSapi [ aMsg class messageType = GSM48MMMessage msgLUAcc ifTrue: [ self success: true. ]. ] ] ProcedureBase subclass: CallProcedure [ createConnection: aHandler phone: aPhone [ | cm | cm := GSM48CMServiceReq new. cm mi imsi: aPhone imsi. cm keyAndType val: 16r21. self openConnection: cm sapi: 0 phone: aPhone handler: aHandler. ] execute [ super execute. self success ifTrue: [ 'Call got accepted on the way' printNl. ] ifFalse: [ 'Call was never connected' printNl. ]. ] serviceAccepted [ | resp | 'Accepted' printNl. resp := GSM48CCSetup new. resp bearer1OrDefault data: #(16r60 16r02 0 1 4 16r85) asByteArray. resp calledOrDefault data: #(16r91 54 25 8 6 4 16) asByteArray. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). ] handleData: aMsg sapi: aSapi [ aMsg class messageType = GSM48CCMessage msgConnect ifTrue: [ | resp | resp := GSM48CCConnectAck new. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0). self success: true. ]. aMsg class messageType = GSM48CCMessage msgDisconnect ifTrue: [ | resp | resp := GSM48CCRelease new. resp causeOrDefault data: #(16rE1 16r90) asByteArray. conn nextPutData: (BSSAPDTAP initWith: resp linkIdentifier: 0) ]. ] ]