smalltalk
/
osmo-st-gsm
Archived
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-gsm/GSMDriver.st

153 lines
3.6 KiB
Smalltalk

Object subclass: GSMDriver [
| goal sccp proc completeSem result 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.'>
GSMDriver class >> new [
<category: 'private'>
^ super new initialize; yourself
]
GSMDriver class >> initWith: aSCCPConnection goal: aGoal phone: aPhone [
<category: 'creation'>
^ self new
goal: aGoal;
sccp: aSCCPConnection;
phone: aPhone;
yourself
]
initialize [
<category: 'private'>
completeSem := Semaphore new.
]
result [
^ result
]
waitForCompletion [
<category: 'accessing'>
^ completeSem wait
]
goal: aGoal [
<category: 'manage'>
goal := aGoal.
]
phone: aPhone [
<category: 'private'>
phoneConfig := aPhone.
]
sccp: aSCCPConnection [
sccp := aSCCPConnection
]
run [
<category: 'processing'>
"Process all messages in a thread"
proc := [
[
[true] whileTrue: [
| msg |
msg := sccp next.
self dispatch: msg.
].
] on: SystemExceptions.EndOfStream do: [
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
].
'Unhandled message' printNl.
aMsg inspect.
]
auKey [
^ phoneConfig auKey.
]
imsi [
^ phoneConfig imsi.
]
dispatchDTAP: aMsg [
<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
].
'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.
].
aMsg inspect.
]
]
Object subclass: LUProcedure [
| driver conn |
LUProcedure class >> initWith: aHandler phone: aPhone [
^ self new
createConnection: aHandler phone: aPhone;
yourself
]
createConnection: aHandler phone: aPhone [
| lu bssap msg sccp |
lu := GSM48LURequest new.
lu mi imsi: aPhone imsi.
msg := IEMessage initWith: GSM0808Helper msgComplL3.
msg addIe: (GSMCellIdentifier initWith: 274 mnc: 8 lac: 4099 ci: 40000).
msg addIe: (GSMLayer3Info initWith: lu).
bssap := BSSAPManagement initWith: msg.
conn := aHandler createConnection: bssap.
driver := GSMDriver initWith: conn goal: #lu phone: aPhone.
]
execute [
driver run.
driver waitForCompletion.
'LUProcedure is completed' printNl.
]
]