aboutsummaryrefslogtreecommitdiffstats
path: root/GSMDriver.st
blob: d1ac40fd171689230d323ff381158631dc344d4c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
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.
    ]
]