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

invite: Verify we have a remoteSDP file and it is matching

This way we can fully handle a session once the sessionNew selector
is called by the code.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-28 11:42:33 +02:00
parent 1a3d577894
commit 8a820162d2
3 changed files with 17 additions and 8 deletions

View File

@ -71,6 +71,11 @@ Object subclass: SIPRequest [
sdp := aSDP
]
sdp [
<category: 'accessing'>
^sdp
]
addParameter: aPar value: aValue [
<category: 'accessing'>
self parameters add: (aPar -> aValue).

View File

@ -53,6 +53,7 @@ receiving an ACK?
SIPIncomingCall class >> initWith: anInvite dialog: dialog on: anAgent [
^self new
initialize;
remoteSDP: anInvite sdp;
useragent: anAgent;
confirmDialog: dialog with: anInvite;
yourself
@ -79,6 +80,14 @@ receiving an ACK?
self registerDialog.
]
remoteSDP: aSDP [
remoteSDP := aSDP
]
remoteSDP [
^remoteSDP
]
reject [
<category: 'accept'>
(self moveToState: self class stateRejected) ifFalse: [

View File

@ -39,14 +39,7 @@ TestCase subclass: SIPInviteTest [
nextPutAll: 'Content-Type: application/sdp'; cr; nl;
nextPutAll: 'Content-Length: 189'; cr; nl;
cr; nl;
nextPutAll: 'v=0'; cr; nl;
nextPutAll: 'o=yate 1401116278 1401116278 IN IP4 10.23.42.1'; cr; nl;
nextPutAll: 's=SIP Call'; cr; nl;
nextPutAll: 'c=IN IP4 10.23.42.1'; cr; nl;
nextPutAll: 't=0 0'; cr; nl;
nextPutAll: 'm=audio 16576 RTP/AVP 8 101'; cr; nl;
nextPutAll: 'a=rtpmap:8 PCMA/8000'; cr; nl;
nextPutAll: 'a=rtpmap:101 telephone-event/8000'; cr; nl;
nextPutAll: 'Shiny remote SDP file'; cr; nl;
cr; nl;
contents
]
@ -160,6 +153,8 @@ TestCase subclass: SIPInviteTest [
self assert: call state equals: call class stateAccepted.
transport inject: (self createAck: tag).
self assert: call state equals: call class stateSession.
self assert: (call remoteSDP startsWith: 'Shiny remote SDP file').
]
testConnectedCallWithRetransmission [