summaryrefslogtreecommitdiffstats
path: root/callagent/tests/SIPParserTest.st
blob: 13fcab304c0691335e34209995881c6f479ca7db (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
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
"
 (C) 2011-2014 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/>.
"

PP.PPCompositeParserTest subclass: SIPParserTest [
    <category: 'OsmoSIP-Parser-Tests'>
    <comment: 'I excercise the SIPParser a bit'>

    SIPParserTest class >> exampleYateBye [
        ^String streamContents: [:stream |
            stream
                nextPutAll: 'SIP/2.0 401 Unauthorized'; cr; nl;
                nextPutAll: 'Via: SIP/2.0/UDP 0.0.0.0:5061;branch=z9hG4bKMzU3OTE4OTQ0Niw5NjM5Nw__;rport=5061;received=1.2.3.4'; cr; nl;
                nextPutAll: 'From: <sip:0503@1.2.3.4>;tag=MzU3OTE5NjYzOTMyODExMDEwOTE_'; cr; nl;
                nextPutAll: 'To: <sip:+1234@4.3.2.1>;tag=1176641923'; cr; nl;
                nextPutAll: 'Call-ID: NTQ5MzM3NzA4@xiaoyu'; cr; nl;
                nextPutAll: 'CSeq: 2 BYE'; cr; nl;
                nextPutAll: 'WWW-Authenticate: Digest realm="Yate", domain="1.2.3.4", nonce="b787f1fbc9a864af6975d9f59ac49ef1.1401736687", stale=FALSE, algorithm=MD5'; cr; nl;
                nextPutAll: 'Server: YATE/4.3.0'; cr; nl;
                nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
                nextPutAll: 'Content-Length: 0'; cr; nl;
                cr; nl]
    ]

    parserClass [
        <category: 'accessing'>
        ^ SIPParser
    ]

    testResponseData [
        ^ (WriteStream on: (String new))
            nextPutAll: 'SIP/2.0 480 Temporarily Unavailable'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/UDP 172.16.254.34;rport;branch=z9hG4bKMzQ4NTQzNDgxNCwyNDE1Nw__;received=172.16.254.55;ttl=123;bla=foo;maddr=www.moo.de'; cr; nl;
            nextPutAll: 'From: <sip:1000@on-waves.com>;tag=MzQ4NTQ0MTg2NzIyNDEwNjkyNjY_'; cr; nl;
            nextPutAll: 'To: <sip:9198@172.16.1.72>;tag=42eBv22Fj314N;abc=def;kbc;ajk'; cr; nl;
            nextPutAll: 'Call-ID: MzY3NzE3ODgyNw__@xiaoyu'; cr; nl;
            nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
            nextPutAll: 'User-Agent: FreeSWITCH-mod_sofia/1.0.head-git-dff41af 2011-04-20 14-11-24 +0200'; cr; nl;
            nextPutAll: 'Accept: application/sdp'; cr; nl;
            nextPutAll: 'Allow: INVITE, ACK, BYE, CANCEL, OPTIONS, MESSAGE, UPDATE, INFO, REGISTER, REFER, NOTIFY, PUBLISH, SUBSCRIBE'; cr; nl;
            nextPutAll: 'Supported: timer, precondition, path, replaces'; cr; nl;
            nextPutAll: 'Allow-Events: talk, hold, presence, dialog, line-seize, call-info, sla, include-session-description, presence.winfo, message-summary, refer'; cr; nl;
            nextPutAll: 'Reason: Q.850;cause=96;text="MANDATORY_IE_MISSING"'; cr; nl;
            nextPutAll: 'Content-Length: 0'; cr; nl;
            nextPutAll: 'Remote-Party-ID: "9198" <sip:9198@172.16.1.72>;party=calling;privacy=off;screen=no'; cr; nl; cr;nl;
            contents.
    ]

    testByeRequestData [
        ^ (WriteStream on: (String new))
            nextPutAll: 'BYE sip:osmo_st_sip@213.167.137.242:1187 SIP/2.0'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/UDP 172.16.1.72:4000;ttl=16;maddr=224.2.0.1;rport;branch=z9hG4bKvt9FDU96c89cQ'; cr;nl;
            nextPutAll: 'Max-Forwards: 70'; cr; nl;
            nextPutAll: 'From: <sip:1000@172.16.1.72>;tag=tFFg06FKH425D'; cr; nl;
            nextPutAll: 'To: <sip:1000@on-waves.com>;tag=MzQ4NzMzMjcxMTUyNDc1OTI2OA__'; cr; nl;
            nextPutAll: 'Call-ID: MzkwNzQ1NTM2Nw__@xiaoyu'; cr; nl;
            nextPutAll: 'CSeq: 14600327 BYE'; cr; nl;
            nextPutAll: 'Contact: <sip:1000@172.16.1.72:5060;transport=udp>'; cr; nl;
            nextPutAll: 'User-Agent: FreeSWITCH-mod_sofia/1.0.head-git-2e651c8 2011-07-03 22-35-44 -0500'; cr; nl;
            nextPutAll: 'Allow: INVITE, ACK, BYE, CANCEL, OPTIONS, MESSAGE, UPDATE, INFO, REGISTER, REFER, NOTIFY, PUBLISH, SUBSCRIBE'; cr; nl;
            nextPutAll: 'Supported: timer, precondition, path, replaces'; cr; nl;
            nextPutAll: 'Reason: Q.850;cause=16;text="NORMAL_CLEARING"'; cr; nl;
            nextPutAll: 'Content-Length: 0'; cr; nl;
            cr; nl; contents
    ]

    testOPTIONSRequestData [
        ^ (WriteStream on: String new)
            nextPutAll: 'OPTIONS sip:127.0.0.1:5061 SIP/2.0'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;rport;branch=z9hG4bK1492385841'; cr; nl;
            nextPutAll: 'Route: "123456" <sip:123456@127.0.0.1>;tag=oxivb'; cr; nl;
            nextPutAll: 'From: <sip:%60123456@127.0.0.1>;tag=70812965'; cr; nl;
            nextPutAll: 'To: "123456" <sip:123456@127.0.0.1>;tag=oxivb'; cr; nl;
            nextPutAll: 'Call-ID: 486321292'; cr; nl;
            nextPutAll: 'CSeq: 20 OPTIONS'; cr; nl;
            nextPutAll: 'Accept: application/sdp'; cr; nl;
            nextPutAll: 'Max-Forwards: 70'; cr; nl;
            nextPutAll: 'User-Agent: Linphone/3.4.3 (eXosip2/3.6.0)'; cr; nl;
            nextPutAll: 'Content-Length: 0'; cr; nl;
            cr; nl; contents
    ]

    testOPTIONSRequest [
          | res |

          res := self parse: self testOPTIONSRequestData.
          self assert: res asDatagram = self testOPTIONSRequestData.
    ]

    testResponse [
        | res |

        res := self parse: self testResponseData.
        self assert: res asDatagram = self testResponseData.
        self assert: (res parameter: 'Via') branch = 'z9hG4bKMzQ4NTQzNDgxNCwyNDE1Nw__'.
        self assert: (res parameter: 'CSeq') number = 1.
        self assert: (res parameter: 'CSeq') method = 'INVITE'.
        self assert: (res parameter: 'To') tag = '42eBv22Fj314N'.
        self assert: (res parameter: 'To') address = 'sip:9198@172.16.1.72'.
        self assert: ((res parameter: 'To') valueAt: 'abc') = 'def'.
        self assert: ((res parameter: 'To') valueAt: 'kbc') = nil.
        self assert: ((res parameter: 'To') valueAt: 'ajk') = nil.
        self should: [((res parameter: 'To') valueAt: 'foo')] raise: SystemExceptions.NotFound.
        self assert: (res parameter: 'From') tag = 'MzQ4NTQ0MTg2NzIyNDEwNjkyNjY_'.
        self assert: (res parameter: 'From') address = 'sip:1000@on-waves.com'.
    ]

    testSIPDialog [
        | dialog |
        dialog := SIPDialog fromMessage: (self parse: self testResponseData).
        self
            assert: dialog to = 'sip:9198@172.16.1.72';
            assert: dialog to_tag = '42eBv22Fj314N';
            assert: dialog from = 'sip:1000@on-waves.com';
            assert: dialog from_tag = 'MzQ4NTQ0MTg2NzIyNDEwNjkyNjY_';
            assert: dialog callId = 'MzY3NzE3ODgyNw__@xiaoyu';
            assert: dialog cseq = 1.
    ]

    testDialogCompatible [
        | initial_dialog dialog1 dialog2 |
        initial_dialog := (SIPDialog
                            fromUser: 'sip:1000@on-waves.com' host: '0.0.0.0' port: 5060)
                            fromTag: 'MzQ4NTQ0MTg2NzIyNDEwNjkyNjY_';
                            callId: 'MzY3NzE3ODgyNw__@xiaoyu';
                            yourself.
        self assert: initial_dialog isUnconfirmed.
        self deny: initial_dialog isConfirmed.

        dialog1 := initial_dialog newFromRequest: (self parse: self testResponseData).
        self deny: initial_dialog == dialog1.
        self assert: dialog1 isConfirmed.

        dialog2 := dialog1 newFromRequest: (self parse: self testResponseData).
        self assert: dialog1 == dialog2.
        self assert: dialog2 isConfirmed.
    ]

    testByeRequest [
        | res |

        res := SIPParser parse: self testByeRequestData.
        self
          assert: (res parameter: 'Allow' ifAbsent: []) = 'INVITE, ACK, BYE, CANCEL, OPTIONS, MESSAGE, UPDATE, INFO, REGISTER, REFER, NOTIFY, PUBLISH, SUBSCRIBE';
          assert: (res parameter: 'Via' ifAbsent: []) branch = 'z9hG4bKvt9FDU96c89cQ';
          assert: (res parameter: 'CSeq' ifAbsent: []) number = 14600327.
    ]

    statusResponseData [
        ^ (WriteStream on: String new)
            nextPutAll: 'SIP/2.0 416 Unsupported URI Scheme'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/UDP 192.168.0.101:5061;branch=z9hG4bKMzQ4ODYxODcyOCwyMDg0MA__'; cr; nl;
            nextPutAll: 'From: "abc" <sip:1000@osmocom.org>;tag=MzQ4ODYyNTkyODQxMDY0OTAxMzI_'; cr; nl;
            nextPutAll: 'To: <1000@192.168.0.106>;tag=5UtDUa1DeFa4S'; cr; nl;
            nextPutAll: 'Call-ID: MTg3NzU0Mjk2MQ__@xiaoyu'; cr; nl;
            nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
            nextPutAll: 'User-Agent: FreeSWITCH-mod_sofia/1.0.head-git-7cb0951 2011-06-24 18-28-56 -0500'; cr; nl;
            nextPutAll: 'Allow: INVITE, ACK, BYE, CANCEL, OPTIONS, MESSAGE, UPDATE, INFO, REGISTER, REFER, NOTIFY, PUBLISH, SUBSCRIBE'; cr; nl;
            nextPutAll: 'Supported: timer, precondition, path, replaces'; cr; nl;
            nextPutAll: 'Content-Length: 0'; cr; nl;
            cr; nl;
            contents
    ]

    testStatusResponse [
        | res from |
        res := SIPParser parse: self statusResponseData.
        from := (res parameter: 'From' ifAbsent: []).
        self assert: from address equals: 'sip:1000@osmocom.org'.
        self assert: from tag equals: 'MzQ4ODYyNTkyODQxMDY0OTAxMzI_'.
    ]

    resultUnauthorized [
        ^(WriteStream on: String new)
            nextPutAll: 'SIP/2.0 401 Unauthorized'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/UDP 172.16.252.198:5060;branch=z9hG4bK6cdba079-8b91-e311-8101-844bf52a8297;rport=5060;received=172.16.252.198'; cr; nl;
            nextPutAll: 'From: <sip:st@127.0.0.2>;tag=12187969-8b91-e311-8101-844bf52a8297'; cr; nl;
            nextPutAll: 'To: <sip:st@127.0.0.2>'; cr; nl;
            nextPutAll: 'Call-ID: fc0f7969-8b91-e311-8101-844bf52a8297@xiaoyu'; cr; nl;
            nextPutAll: 'CSeq: 7 REGISTER'; cr; nl;
            nextPutAll: 'WWW-Authenticate: Digest realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", stale=TRUE, algorithm=MD5'; cr; nl;
            nextPutAll: 'Proxy-Authenticate: Digest realm="07440491",qop="auth",nonce="7a7155d2bff57ffcc226f0e6819d00be68d517b3C0A4ABEB5BE0",algorithm=MD5'; cr; nl;
            nextPutAll: 'Server: YATE/5.1.0'; cr; nl;
            nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
            nextPutAll: 'Content-Length: 0'; cr; nl;
            cr; nl;
            contents
    ]

    testWWWAuthRequired [
        | res auth|
        res := self parse: self resultUnauthorized.
        auth := res parameter: 'WWW-Authenticate'.
        self assert: (auth at: 'realm') equals: 'Yate'.
        self assert: (auth at: 'nonce') equals: '373ef30b297545cbce99fad09f1409cb.1392124197'.
        self assert: (auth at: 'stale').
        self assert: (auth at: 'algorithm') equals: 'MD5'.
        self assert: (res parameter: 'cAlL-Id') equals: 'fc0f7969-8b91-e311-8101-844bf52a8297@xiaoyu'.
    ]

    testProxyAuthenticate [
        | res auth |
        res := self parse: self resultUnauthorized.
        auth := res parameter: 'Proxy-Authenticate'.
        self assert: (auth at: 'realm') equals: '07440491'.
        self assert: (auth at: 'nonce') equals: '7a7155d2bff57ffcc226f0e6819d00be68d517b3C0A4ABEB5BE0'.
        self assert: (auth at: 'algorithm') equals: 'MD5'.
        self assert: (auth at: 'qop') equals: 'auth'.
    ]

    authorizationData [
        "Shortened because we only care about Authorization"
        ^(WriteStream on: String new)
            nextPutAll: 'INVITE sip:127.0.0.1 SIP/2.0'; cr; nl;
            nextPutAll: 'Via: SIP/2.0/MOCK 127.0.0.1:5060;branch=z9hG4bKMz'; cr; nl;
            nextPutAll: 'Authorization: Digest username="st", realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", uri="sip:127.0.0.1", algorithm=MD5, response="bc8dfaa413e897863dbab4c622e4b9b4"'; cr; nl;
            cr; nl;
            contents
    ]

    testAuthorization [
        | res auth|
        res := self parse: self authorizationData.
        auth := res parameter: 'Authorization' ifAbsent: [nil].
        self deny: auth isNil.

        self assert: auth username equals: 'st'.
        self assert: auth realm equals: 'Yate'.
        self assert: auth nonce equals: '373ef30b297545cbce99fad09f1409cb.1392124197'.
        self assert: auth uri equals: 'sip:127.0.0.1'.
        self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'.
    ]

    testYateBye [
        | res |

        res := self parse: self class exampleYateBye.
        "Just check it can be parsed."
    ]
]