1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-testphone/GSMDriver.st

423 lines
11 KiB
Smalltalk

"
(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 <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: #OsmoASN1.
Object subclass: GSMDriver [
| sccp proc sapis completeSem phoneConfig |
<category: 'osmo-gsm-operation'>
<comment: 'I create a SCCP connection and handle stuff on it. In the base class
I am just capable of handling BSSMAP Management and need to dispatch it to other
classes.'>
<import: OsmoGSM>
GSMDriver class >> new [
<category: 'private'>
^ super new initialize; yourself
]
GSMDriver class >> initWith: aSCCPConnection sapi: aSapi on: aProc phone: aPhone[
<category: 'creation'>
^ self new
sapi: aSapi on: aProc;
sccp: aSCCPConnection;
phone: aPhone;
yourself
]
initialize [
<category: 'private'>
completeSem := Semaphore new.
sapis := Dictionary new.
]
completeSem [
^ completeSem
]
waitForCompletion [
<category: 'accessing'>
^ completeSem wait
]
waitWithTimeout: aTimeout [
| delay |
<category: 'accessing'>
delay := Delay forSeconds: aTimeout.
delay timedWaitOn: completeSem.
]
sapi: aSapi on: aProc [
<category: 'manage'>
sapis at: aSapi put: aProc.
]
phone: aPhone [
<category: 'private'>
phoneConfig := aPhone.
]
sccp: aSCCPConnection [
sccp := aSCCPConnection
]
sendClearRequest [
| clear |
clear := IEMessage initWith: GSM0808Helper msgClearReq.
clear addIe: (GSMCauseIE initWith: 0).
sccp nextPutData: (BSSAPManagement initWith: clear).
]
run [
| connected |
<category: 'processing'>
"Process all messages in a thread"
connected := true.
proc := [
[
[
[true] whileTrue: [
| msg |
msg := sccp next.
self dispatch: msg.
].
] on: SystemExceptions.EndOfStream do: [
connected := false.
'SCCP Connection is now disconnected' printNl.
].
] ensure: [
connected ifTrue: [
'SCCP Cleaning up connection' printNl.
connected := false.
self sendClearRequest.
].
completeSem signal.
].
] fork.
]
cleanUp [
<category: 'protected'>
]
dispatchMan: aMsg [
<category: 'private'>
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 auKeyByteArray.
]
imsi [
^ phoneConfig imsi.
]
dispatchDTAP: aMsg sapi: aSapi [
<category: 'private'>
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 [
<category: 'protected'>
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 |
<import: OsmoGSM>
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.
]
driver [
^ driver
]
complete [
^ driver completeSem signals > 0
]
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.
]
name [
^ 'Location Updating Procedure'
]
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 [
| nr |
CallProcedure class >> initWith: aConn phone: aPhone nr: aNr [
^ (super initWith: aConn phone: aPhone)
nr: aNr; yourself
]
nr: aNr [
nr := (ByteArray with: 16r80), (GSMNumberDigits encodeFrom: aNr).
]
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.
]
name [
^ 'Call Procedure'
]
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: nr.
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)
].
]
]
ProcedureBase subclass: USSDProcedure [
| nr |
<import: Osmo>
USSDProcedure class >> initWith: aConn phone: aPhone nr: aNr [
^ (super initWith: aConn phone: aPhone)
nr: aNr; yourself
]
USSDProcedure class >> buildProcessUnstructReq: aNr [
| req str |
req := {BERTag fromTuple: #(2 true 1). OrderedCollection
with: {BERTag integer. #(4).}
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
]
nr: aNr [
nr := aNr.
]
createConnection: aHandler phone: aPhone [
| cm |
cm := GSM48CMServiceReq new.
cm mi imsi: aPhone imsi.
cm keyAndType val: 8.
self openConnection: cm sapi: 0 phone: aPhone handler: aHandler.
]
name [
^ 'USSD Procedure'
]
serviceAccepted [
| reg |
reg := GSM48SSRegister new.
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:[
aMsg inspect.
self success: true.
]
]
]