smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Merge commit '89e653a41aff48b9d861673affd17722744ed8cb'

This commit is contained in:
Holger Hans Peter Freyther 2015-01-23 09:39:33 +01:00
commit aba6a6f030
18 changed files with 336 additions and 101 deletions

View File

@ -36,3 +36,79 @@ General:
* 3xx, 4xx, 5xx, 6xx are final. We should not allow any other messages.
Sending multiple 503/500 messages.. they all will be acked..
* Record-Route/Route implementation needed:
SIP/2.0 200 OK
Via: SIP/2.0/UDP 192.168.0.251:3107;branch=z9hG4bK-qvgn1b;rport=3107
Record-Route: <sip:172.20.40.8;lr>
Record-Route: <sip:217.10.68.147;lr;ftag=7kypvq>
From: "sipgate" <sip:ABC@sipgate.de>;tag=7kypvq
To: "00491778116745" <sip:0049123@sipgate.de;user=phone>;tag=as10fec2f5
Call-ID: n57q3hl9l7
CSeq: 1084794278 INVITE
Allow: INVITE, ACK, CANCEL, OPTIONS, BYE, REFER, SUBSCRIBE, NOTIFY, INFO, PUBLISH
Supported: replaces
Contact: <sip:49123@217.10.77.114:5060>
Content-Type: application/sdp
Content-Length: 381
v=0
o=root 1250091314 1250091315 IN IP4 217.10.77.114
s=sipgate VoIP GW
c=IN IP4 217.10.77.114
t=0 0
m=audio 17974 RTP/AVP 8 0 3 18 2 101
a=rtpmap:8 PCMA/8000
a=rtpmap:0 PCMU/8000
a=rtpmap:3 GSM/8000
a=rtpmap:18 G729/8000
a=fmtp:18 annexb=no
a=rtpmap:2 G726-32/8000
a=rtpmap:101 telephone-event/8000
a=fmtp:101 0-16
a=silenceSupp:off - - - -
a=ptime:20
a=sendrecv
ACK sip:123@217.10.77.114:5060 SIP/2.0
Via: SIP/2.0/UDP 24.134.59.157:3107;branch=z9hG4bK-2tacy7;rport
Route: <sip:217.10.68.147;lr;ftag=7kypvq>
Route: <sip:172.20.40.8;lr>
From: "sipgate" <sip:ABC@sipgate.de>;tag=7kypvq
To: "00491778116745" <sip:0049123@sipgate.de;user=phone>;tag=as10fec2f5
Call-ID: n57q3hl9l7
CSeq: 1084794278 ACK
Max-Forwards: 70
Contact: <sip:abc@24.134.59.157:3107;transport=udp;line=i4p4q6>;reg-id=1;+sip.instance="<urn:uuid:572d1aa1-bfd5-4b8a-ab1e-f9095df386e5>"
Content-Length: 0
Reply with ACK to 401 authorized..
SIP/2.0 401 Unauthorized
Via: SIP/2.0/UDP 192.168.0.106:5060;branch=z9hG4bK4000ebad-1c1f-e411-87f8-844bf52a8297;rport=1029;received=91.66.224.184
From: <sip:5100310@8.8.8.8>;tag=e698dead-1c1f-e411-87f8-844bf52a8297
To: <sip:00123@8.8.8.8>
Call-ID: 4eaedead-1c1f-e411-87f8-844bf52a8297@xiaoyu
CSeq: 1 INVITE
WWW-Authenticate: Digest realm="Yate", nonce="cc615df915f40a7d8ae80ef28c8efba4.1407689697", stale=FALSE, algorithm=MD5
Server: YATE/5.4.0
Contact: <sip:00123@8.8.8.8:5060>
Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO
Content-Length: 0
ACK sip:00123@8.8.8.8 SIP/2.0
CSeq: 1 ACK
Via: SIP/2.0/UDP 192.168.0.106:5060;branch=z9hG4bK4000ebad-1c1f-e411-87f8-844bf52a8297;rport
From: <sip:5100310@8.8.8.8>;tag=e698dead-1c1f-e411-87f8-844bf52a8297
Call-ID: 4eaedead-1c1f-e411-87f8-844bf52a8297@xiaoyu
To: <sip:00123@8.8.8.8>
Content-Length: 0
Max-Forwards: 70

View File

@ -38,12 +38,17 @@ Object subclass: SIPResponse [
SIPResponse class >> code: code with: phrase [
<category: 'factory'>
^ self new
instVarNamed: #code put: code;
instVarNamed: #phrase put: phrase;
^ self basicNew
initialize;
code: code;
phrase: phrase;
yourself
]
initialize [
params := OrderedCollection new: 7.
]
code: aCode [
<category: 'accessing'>
code := aCode
@ -59,6 +64,10 @@ Object subclass: SIPResponse [
^ code
]
phrase: aPhrase [
phrase := aPhrase
]
phrase [
<category: 'accessing'>
^ phrase
@ -66,12 +75,12 @@ Object subclass: SIPResponse [
parameters [
<category: 'accessing'>
^ params ifNil: [params := OrderedCollection new]
^params
]
addParameter: aPar value: aValue [
<category: 'accessing'>
self parameters add: (aPar -> aValue).
params add: (Association key: aPar value: aValue).
]
parameter: aPar [
@ -79,7 +88,7 @@ Object subclass: SIPResponse [
]
parameter: aPar ifAbsent: absent [
self parameters do: [:each |
params do: [:each |
(each key sameAs: aPar) ifTrue: [^ each value]].
^absent value.
@ -105,7 +114,7 @@ Object subclass: SIPResponse [
nextPutAll: phrase;
cr; nl.
self parameters do: [:each |
params do: [:each |
out
nextPutAll: each key;
nextPutAll: ': ';

View File

@ -30,9 +30,7 @@ SIPAuthorization subclass: SIPProxyAuthorization [
]
SIPProxyAuthorization class >> new [
^super new
initialize;
yourself
^self basicNew initialize
]
initialize [

View File

@ -23,13 +23,25 @@ SIPParam subclass: SIPCSeq [
SIPCSeq class >> parseFrom: aParseDict [
<category: 'creation'>
^ self new
instVarNamed: #data put: aParseDict asFoldedString;
instVarNamed: #number put: aParseDict first asInteger;
instVarNamed: #method put: aParseDict third;
^ self basicNew
data: aParseDict asFoldedString;
number: aParseDict first asInteger;
method: aParseDict third;
yourself
]
data: aData [
data := aData
]
number: aNumber [
number := aNumber
]
method: aMethod [
method := aMethod
]
number [
<category: 'accessing'>
^ number

View File

@ -63,17 +63,14 @@ Object subclass: SIPGenericParam [
asFoldedString [
| str |
<category: 'helper'>
str := (WriteStream on: (String new))
nextPutAll: key;
yourself.
value isNil ifFalse: [
str
nextPut: $=;
nextPutAll: value.
].
^ str contents
^value isNil
ifTrue: [key]
ifFalse: [
(WriteStream on: (String new: key size + value size + 1))
nextPutAll: key;
nextPut: $=;
nextPutAll: value;
contents].
]
isGenericSIPParam [

View File

@ -31,13 +31,25 @@ SIPParam subclass: SIPToFromParam [
SIPToFromParam class >> parseFrom: anArray [
<category: 'creation'>
^ self new
instVarNamed: #addr put: anArray first third;
instVarNamed: #data put: anArray asFoldedString;
instVarNamed: #params put: (self buildParams: anArray second);
^ self basicNew
address: anArray first third;
data: anArray asFoldedString;
params: (self buildParams: anArray second);
yourself
]
address: anAddress [
addr := anAddress
]
data: aData [
data := aData
]
params: aParam [
params := aParam
]
address [
<category: 'accessing'>
^ addr

View File

@ -35,14 +35,30 @@ SIPParam subclass: SIPVia [
<category: 'creation'>
(aParseDict at: 7) second
ifNotNil: [:val | port := val second asInteger].
^ self new
instVarNamed: #data put: aParseDict asFoldedString;
instVarNamed: #address put: (aParseDict at: 7) first;
instVarNamed: #port put: port;
instVarNamed: #branch put: (self findBranch: (aParseDict at: 8));
^self basicNew
data: aParseDict asFoldedString;
address: (aParseDict at: 7) first;
port: port;
branch: (self findBranch: (aParseDict at: 8));
yourself
]
data: aData [
data := aData
]
address: anAddress [
address := anAddress
]
port: aPort [
port := aPort
]
branch: aBranch [
branch := aBranch
]
branch [
^ branch
]

View File

@ -19,7 +19,7 @@
Array extend [
asFoldedString [
<category: '*OsmoSIP-parser'>
^ (Osmo at: #SIPParser) combineUri: self.
^ Osmo.SIPParser combineUri: self.
]
]

View File

@ -36,7 +36,7 @@ SIPGrammar subclass: SIPParser [
SIPParser class >> combineUri: anArray [
| str |
str := WriteStream on: (String new).
str := WriteStream on: (String new: 20).
self addArrayRec: anArray on: str.
^ str contents
]

View File

@ -47,3 +47,11 @@ SIPACKRequest extend [
aCall sessionAcked: self dialog: aDialog.
]
]
SIPCancelRequest extend [
sipCallDispatch: aCall dialog: aDialog [
<category: '*OsmoSIP-call'>
self logDebug: ('SIPCall(<1s>) got ACK.' expandMacrosWith: aCall callId) area: #sip.
aCall sessionCanceled: self dialog: aDialog.
]
]

View File

@ -38,6 +38,7 @@ will simply ignore everything but the first dialog.'>
self stateInvite -> self stateRedirect.
self stateSession -> self stateHangup.
self stateSession -> self stateRemoteHangup.
self stateHangup -> self stateRemoteHangup.
}
]
]
@ -212,4 +213,10 @@ will simply ignore everything but the first dialog.'>
sdpResult [
^sdp_result
]
sessionAcked: anAck dialog: aDialog [
"Do nothing. E.g. this could have been a re-invite that we 200 OKed
and now get an ACK for our 200. In the future we might want to handle
the re-invitation differently."
]
]

View File

@ -133,18 +133,22 @@ receiving an ACK?
self sendResponse: 200 text: 'OK' data: localSDP.
]
sendResponse: aCode text: aText data: aFile [
respondTo: aDialog code: aCode text: aText data: aFile cseq: aCseq[
| resp |
resp := (SIPResponse code: aCode with: aText)
addParameter: 'Via' value: (ua generateVia: branch);
addParameter: 'From' value: dialog generateFrom;
addParameter: 'To' value: dialog generateTo;
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'From' value: aDialog generateFrom;
addParameter: 'To' value: aDialog generateTo;
addParameter: 'Call-ID' value: aDialog callId;
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: dialog cseq with: 'INVITE');
expandMacrosWith: aDialog cseq with: aCseq);
sdp: aFile;
yourself.
ua queueData: resp asDatagram dialog: dialog.
ua queueData: resp asDatagram dialog: aDialog.
]
sendResponse: aCode text: aText data: aFile [
^self respondTo: dialog code: aCode text: aText data: aFile cseq: 'INVITE'
]
remoteReInvite: aRequest dialog: aDialog [
@ -169,4 +173,20 @@ receiving an ACK?
"We have a new session now"
self sessionNew.
]
sessionCanceled: aCancel dialog: aDialog [
(self moveToState: self class stateFailed) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to handle cancel'
expandMacrosWith: self callId) area: #sip.
self respondTo: aDialog code: '200' text: 'OK' data: nil.
^false].
"Tell the user the session has failed. Use the existing
dialogue to say the request was terminated and to reply
to the CANCEL transaction itself."
self sessionFailed.
self sendResponse: 487 text: 'Request Terminated' data: nil.
self unregisterDialog.
self respondTo: aDialog code: '200' text: 'OK' data: nil cseq: 'CANCEL'.
]
]

View File

@ -146,7 +146,7 @@ TestCase subclass: SIPCallAgentTest [
call createCall: 'dummy-sdp'.
self assert: call state equals: SIPCall stateInvite.
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: msg class verb equals: SIPInviteRequest verb.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
@ -162,7 +162,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@ -183,7 +183,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@ -194,8 +194,12 @@ TestCase subclass: SIPCallAgentTest [
transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
self assert: sent size equals: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
@ -222,7 +226,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@ -233,8 +237,12 @@ TestCase subclass: SIPCallAgentTest [
transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
self assert: sent size equals: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
self assert: call state equals: SIPCall stateInvite.
@ -261,7 +269,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@ -272,8 +280,12 @@ TestCase subclass: SIPCallAgentTest [
transport inject: (self proxyAuthRequired: branch callId: callId tag: fromTag tag cseq: 1).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
self assert: sent size equals: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
@ -296,8 +308,8 @@ TestCase subclass: SIPCallAgentTest [
"Inject a 200 and check the ACK"
transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: 2).
self assert: sent size equals: 3.
msg := SIPParser parse: sent third data.
self assert: sent size equals: 4.
msg := agent parser parse: (sent at: 4) data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
self assert: call state equals: SIPCall stateSession.
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
@ -327,7 +339,7 @@ TestCase subclass: SIPCallAgentTest [
| call msg branch callId fromTag sentNr |
call := self setUpProxyAuthCall.
msg := SIPParser parse: sent second data.
msg := agent parser parse: sent second data.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
@ -339,10 +351,11 @@ TestCase subclass: SIPCallAgentTest [
self assert: sent size equals: sentNr + 1.
self assert: call state equals: SIPCall stateRemoteHangup.
msg := SIPParser parse: (sent at: sentNr + 1) data.
msg := agent parser parse: (sent at: sentNr + 1) data.
self assert: msg class equals: SIPResponse.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: (msg parameter: 'From' ifAbsent: [nil]) tag equals: '123'.
]
testInviteWithRedirect [
@ -353,7 +366,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
@ -369,7 +382,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: call state equals: SIPCall stateRedirect.
"Check we get the ACK"
msg := SIPParser parse: sent second data.
msg := agent parser parse: sent second data.
self assert: msg class equals: SIPACKRequest.
]
]

View File

@ -56,6 +56,19 @@ TestCase subclass: SIPInviteTest [
contents
]
createCancel [
"Without the tag..."
^String streamContents: [:stream |
stream
nextPutAll: 'CANCEL sip:+99915123456@10.23.43.2 SIP/2.0'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 10.23.43.1:5060;rport;branch=z9hG4bK1675813621'; cr; nl;
nextPutAll: 'CSeq: 5 CANCEL'; cr; nl;
nextPutAll: 'Call-ID: 726660594@10.23.43.1'; cr; nl;
nextPutAll: 'From: "00331234567" <sip:00331234567@10.23.43.1>;tag=807191241'; cr; nl;
nextPutAll: 'To: <sip:+99915123456@10.23.43.2>'; cr; nl;
cr;nl]
]
setUp [
sent := OrderedCollection new.
transport := SIPTransportMock new
@ -78,7 +91,7 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs isEmpty.
@ -99,7 +112,7 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs size equals: 1.
@ -110,7 +123,7 @@ TestCase subclass: SIPInviteTest [
transport inject: self createInvite.
self assert: call unregisterDialogIsPending.
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
msg := agent parser parse: sent second data.
secondTag := (msg parameter: 'To' ifAbsent: []) tag.
self assert: firstTag equals: secondTag.
]
@ -130,20 +143,20 @@ TestCase subclass: SIPInviteTest [
"Check the messages"
self assert: sent size equals: 3.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
tag := (msg parameter: 'To' ifAbsent: []) tag.
msg := SIPParser parse: sent second data.
msg := agent parser parse: sent second data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
msg := SIPParser parse: sent third data.
msg := agent parser parse: sent third data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: agent dialogs size equals: 1.
@ -161,7 +174,7 @@ TestCase subclass: SIPInviteTest [
"Now hangup the call"
call hangup.
self assert: call state equals: call class stateHangup.
msg := SIPParser parse: sent fourth data.
msg := agent parser parse: sent fourth data.
self assert: msg class equals: SIPByeRequest.
]
@ -180,14 +193,14 @@ TestCase subclass: SIPInviteTest [
"Send a 100 Trying to the other end"
call trying.
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
"Retransmit the INVITE to forc another trying"
transport inject: self createInvite.
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
msg := agent parser parse: sent second data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
@ -195,13 +208,13 @@ TestCase subclass: SIPInviteTest [
"Now ring and re-transmit"
call ringing.
self assert: sent size equals: 3.
msg := SIPParser parse: sent third data.
msg := agent parser parse: sent third data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
transport inject: self createInvite.
self assert: sent size equals: 4.
msg := SIPParser parse: (sent at: 4) data.
msg := agent parser parse: (sent at: 4) data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
@ -209,14 +222,58 @@ TestCase subclass: SIPInviteTest [
"Now pick-up..."
call pickUp: 'file'.
self assert: sent size equals: 5.
msg := SIPParser parse: (sent at: 5) data.
msg := agent parser parse: (sent at: 5) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
transport inject: self createInvite.
self assert: sent size equals: 6.
msg := SIPParser parse: (sent at: 6) data.
msg := agent parser parse: (sent at: 6) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
]
testCanceledCall [
| msg call tag |
agent onNewCall: [:invite :dialog |
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
trying;
yourself].
"Inject the invite"
transport inject: self createInvite.
"Check the messages"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
tag := (msg parameter: 'To' ifAbsent: []) tag.
"Now cancel and see what is happening!"
transport inject: self createCancel.
"We expect a 487 and a 200. The 487 needs to be for the old
and existign dialog."
self assert: sent size equals: 3.
self assert: agent dialogs size equals: 1.
self assert: agent dialogs first unregisterDialogIsPending.
msg := agent parser parse: sent second data.
self assert: msg code equals: '487'.
self assert: msg phrase equals: 'Request Terminated'.
self assert: (msg parameter: 'To' ifAbsent: []) tag equals: tag.
self assert: (msg parameter: 'CSeq' ifAbsent: []) number equals: 3.
self assert: (msg parameter: 'CSeq' ifAbsent: []) method equals: 'INVITE'.
msg := agent parser parse: sent third data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: (msg parameter: 'To' ifAbsent: []) tag isNil.
self assert: (msg parameter: 'CSeq' ifAbsent: []) number equals: 5.
self assert: (msg parameter: 'CSeq' ifAbsent: []) method equals: 'CANCEL'.
]
]

View File

@ -74,7 +74,7 @@ TestCase subclass: SIPRegisterTransactionTest [
yourself.
register start.
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
"Now inject an auth requirement message"
@ -82,8 +82,12 @@ TestCase subclass: SIPRegisterTransactionTest [
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
transport inject: (self createSimple401: branch callId: callId tag: fromTag tag cseq: 1).
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
self assert: sent size equals: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'REGISTER'.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
transport inject: (self createSimple200: branch callId: callId tag: fromTag tag cseq: 2).

View File

@ -179,6 +179,10 @@ Object subclass: SIPTransaction [
((auth at: 'algorithm' ifAbsent: ['MD5']) = 'MD5')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
"Respond with an ACK"
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
authorization := SIPAuthorization new
username: initial_dialog identity username;
realm: (auth at: 'realm');
@ -220,6 +224,10 @@ Object subclass: SIPTransaction [
((auth at: 'qop' ifAbsent: ['auth']) = 'auth')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
"Respond with an ACK"
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
proxy_authorization := SIPProxyAuthorization new
username: initial_dialog identity proxyUsername;
realm: (auth at: 'realm');

View File

@ -23,9 +23,7 @@ SIPUserAgentBase subclass: SIPUserAgent [
SIPUserAgent class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
^self basicNew initialize
]
initialize [
@ -160,8 +158,8 @@ SIPUserAgentBase subclass: SIPUserAgent [
resp := (SIPResponse code: aCode with: aPhrase)
addParameter: 'Via' value: (self generateVia: via branch);
addParameter: 'From' value: dialog generateTo;
addParameter: 'To' value: dialog generateFrom;
addParameter: 'From' value: dialog generateFrom;
addParameter: 'To' value: dialog generateTo;
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq number with: cseq method);

View File

@ -23,7 +23,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
message_body SIPVersion StatusCode ReasonPhrase
extension_header header_name header_value
Request RequestLine Method extension_method
RequestURI
RequestURI quoted_string token
|
"http://sofia-sip.org/repos/sofia-sip/libsofia-sip-ua/sip/GRAMMAR"
<category: 'OsmoSIP-Grammar'>
@ -226,7 +226,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
]
extension_method [
^ self token
^token
]
Response [
@ -326,7 +326,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
Via [
<category: 'via'>
^ ( 'Via' asParser / 'v' asParser), self HCOLON,
^ ( 'Via' asParser / 'v' asParser), HCOLON,
self via_parm, (COMMA, self via_parm) star
]
@ -359,7 +359,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
via_branch [
<category: 'via'>
^ 'branch' asParser, EQUAL, self token
^ 'branch' asParser, EQUAL, token
]
via_extension [
@ -391,12 +391,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
generic_param [
<category: 'generic'>
^ self token, (EQUAL, self gen_value) optional
^ token, (EQUAL, self gen_value) optional
]
gen_value [
<category: 'generic'>
^ self token / self host / self quoted_string
^token / self host / quoted_string
]
quoted_string [
@ -438,12 +438,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
protocol_name [
<category: 'via'>
^ 'SIP' asParser / self token.
^ 'SIP' asParser / token.
]
protocol_version [
<category: 'via'>
^ self token
^token
]
transport [
@ -454,7 +454,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
other_transport [
<category: 'via'>
^ self token
^token
]
From [
@ -491,7 +491,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
tag_param [
<category: 'to'>
^ 'tag' asParser, EQUAL, self token
^ 'tag' asParser, EQUAL, token
]
name_addr [
@ -501,7 +501,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
display_name [
<category: 'to-from'>
^ (self quoted_string / (self token, LWS) star) flatten
^ (quoted_string / (token, LWS) star) flatten
]
addr_spec [
@ -540,7 +540,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
username [
<category: 'WWW-Authenticate'>
^'username' asParser, EQUAL, self quoted_string
^'username' asParser, EQUAL, quoted_string
]
digest_uri [
@ -607,7 +607,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
realm_value [
<category: 'WWW-Authenticate'>
^self quoted_string
^quoted_string
]
domain [
@ -622,12 +622,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
nonce_value [
<category: 'WWW-Authenticate'>
^self quoted_string
^quoted_string
]
opaque [
<category: 'WWW-Authenticate'>
^'opaque' asParser, EQUAL, self quoted_string
^'opaque' asParser, EQUAL, quoted_string
]
stale [
@ -637,7 +637,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
algorithm [
<category: 'WWW-Authenticate'>
^'algorithm' asParser, EQUAL, ('MD5' asParser / 'MD5-sess' asParser / self token)
^'algorithm' asParser, EQUAL, ('MD5' asParser / 'MD5-sess' asParser / token)
]
qop_options [
@ -649,17 +649,17 @@ PP.PPCompositeParser subclass: SIPGrammar [
qop_value [
<category: 'WWW-Authenticate'>
^'auth' asParser / 'auth-init' asParser / self token
^'auth' asParser / 'auth-init' asParser / token
]
auth_param [
<category: 'WWW-Authenticate'>
^self auth_param_name, EQUAL, (self token / self quoted_string)
^self auth_param_name, EQUAL, (token / quoted_string)
]
auth_param_name [
<category: 'WWW-Authenticate'>
^self token
^token
]
other_response [
@ -669,7 +669,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
auth_scheme [
<category: 'WWW-Authenticate'>
^self token
^token
]
ProxyAuthenticate [
@ -737,7 +737,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
header_name [
<category: 'generic'>
"hmm 1*() should be optional but it must be star here"
^ self token
^token
]
header_value [