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

transaction: Make the callbacks pass the dialog

The transaction now work on something called an initial dialog, e.g.
during a INVITE we go from an initial dialog to a confirmed dialog and
maybe create a session. Prepare the code to support this.

It is still not clear how callbacks, dialog confirmation and session
creation will be handled but it will somehow fit together.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-30 12:07:50 +02:00
parent 276fdb54b3
commit f720f9ea0a
1 changed files with 41 additions and 36 deletions

View File

@ -21,7 +21,7 @@ PackageLoader
fileInPackage: 'Sockets'.
Object subclass: SIPTransaction [
| sem useragent dialog state timeout success failure notification
| sem useragent initial_dialog state timeout success failure notification
cseq branch retransmit_time fail_time |
SIPTransaction class >> stateInitial [ <category: 'states'> ^ #initial ]
@ -35,7 +35,7 @@ Object subclass: SIPTransaction [
^ self new
initialize;
userAgent: aUA;
dialog: aDialog;
initialDialog: aDialog;
setupTransaction;
yourself.
]
@ -45,9 +45,9 @@ Object subclass: SIPTransaction [
sem := RecursionLock new.
]
dialog: aDialog [
initialDialog: aDialog [
<category: 'creation'>
dialog := aDialog
initial_dialog := aDialog
]
userAgent: aUA [
@ -92,7 +92,7 @@ Object subclass: SIPTransaction [
branch := useragent class generateBranch.
]
queueData: aData [
queueData: aData dialog: aDialog [
| res datagram |
<category: 'private'>
@ -102,8 +102,8 @@ Object subclass: SIPTransaction [
datagram := Sockets.Datagram
data: aData
address: (Sockets.SocketAddress
byName: dialog destIp)
port: dialog destPort.
byName: aDialog destIp)
port: aDialog destPort.
useragent queueData: datagram.
]
@ -112,33 +112,33 @@ Object subclass: SIPTransaction [
^ branch
]
respNotification: aReq [
respNotification: aReq dialog: aDialog [
<category: 'private-dispatch'>
self changeState: self class stateProceeding.
notification ifNotNil: [
notification value: aReq]
notification value: aReq value: aDialog]
]
respSuccess: aReq [
respSuccess: aReq dialog: aDialog [
<category: 'private-dispatch'>
useragent removeTransaction: self.
success ifNotNil: [
success value: aReq]
success value: aReq value: aDialog]
]
respFailure: aReq [
respFailure: aReq dialog: aDialog [
<category: 'private-dispatch'>
useragent removeTransaction: self.
failure ifNotNil: [
failure value: aReq]
failure value: aReq value: aDialog]
]
newData: aReq [
| code |
| code dialog |
<category: 'private-dispatch'>
('Found response %1 %2' % {aReq code. aReq phrase}) printNl.
@ -147,19 +147,22 @@ Object subclass: SIPTransaction [
fail_time cancel.
].
dialog updateFromRequest: aReq.
"Verify the To/From tags here"
"Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aReq.
code := aReq code asInteger.
code < 200 ifTrue: [
^ self respNotification: aReq
^ self respNotification: aReq dialog: dialog
].
code = 200 ifTrue: [
^ self respSuccess: aReq
^ self respSuccess: aReq dialog: dialog
].
code > 200 ifTrue: [
^ self respFailure: aReq
^ self respFailure: aReq dialog: dialog
]
]
@ -197,25 +200,25 @@ Object subclass: SIPTransaction [
| invite |
<category: 'invite'>
invite := (SIPInviteRequest from: dialog)
invite := (SIPInviteRequest from: initial_dialog)
sdp: sdp;
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'INVITE'};
addParameter: 'Allow' value: 'ACK,BYE';
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'Call-ID' value: initial_dialog callId;
yourself.
useragent injectDefaults: invite.
^ invite
]
createAck: aBranch [
createAck: aBranch dialog: aDialog [
| ack |
<category: 'ack'>
ack := (SIPACKRequest from: dialog)
ack := (SIPACKRequest from: aDialog)
addParameter: 'Via' value: (useragent generateVia: aBranch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'ACK'};
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'Call-ID' value: aDialog callId;
yourself.
useragent injectDefaults: ack.
^ ack
@ -225,10 +228,10 @@ Object subclass: SIPTransaction [
| bye |
<category: 'invite'>
bye := (SIPByeRequest from: dialog)
bye := (SIPByeRequest from: initial_dialog)
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'BYE'};
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'Call-ID' value: initial_dialog callId;
yourself.
useragent injectDefaults: bye.
^ bye
@ -238,10 +241,10 @@ Object subclass: SIPTransaction [
| cancel |
<category: 'cancel'>
cancel := (SIPCancelRequest from: dialog)
cancel := (SIPCancelRequest from: initial_dialog)
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'CANCEL'};
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'Call-ID' value: initial_dialog callId;
yourself.
useragent injectDefaults: cancel.
^ cancel.
@ -255,6 +258,7 @@ SIPTransaction subclass: SIPInviteTransaction [
"200ms to get TRYING or OK"
SIPInviteTransaction class >> createWith: aDialog on: aUA with: aSDP [
<category: 'creation'>
^ (super createWith: aDialog on: aUA)
instVarNamed: #sdp put: aSDP;
yourself.
@ -262,23 +266,24 @@ SIPTransaction subclass: SIPInviteTransaction [
transmit [
| invite |
<category: 'transmit'>
invite := self createInvite: sdp.
self queueData: invite asDatagram.
self queueData: invite asDatagram dialog: initial_dialog.
]
respSuccess: aReq [
respSuccess: aReq dialog: aDialog [
| branch |
branch := useragent class generateBranch.
self changeState: self class stateTerminated.
dialog sdp: aReq sdp.
self queueData: (self createAck: branch) asDatagram.
^ super respSuccess: aReq.
aDialog sdp: aReq sdp.
self queueData: (self createAck: branch) asDatagram dialog: aDialog.
^ super respSuccess: aReq dialog: aDialog.
]
respFailure: aReq [
respFailure: aReq dialog: aDialog [
self changeState: self class stateCompleted.
self queueData: (self createAck: branch) asDatagram.
^ super respFailure: aReq.
self queueData: (self createAck: branch) asDatagram dialog: aDialog.
^ super respFailure: aReq dialog: aDialog.
]
]
@ -288,6 +293,6 @@ SIPTransaction subclass: SIPByeTransaction [
transmit [
| bye |
bye := self createBye.
self queueData: bye asDatagram.
self queueData: bye asDatagram dialog: initial_dialog.
]
]