smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/callagent/transactions/SIPInviteTransaction.st

165 lines
5.8 KiB
Smalltalk

"
(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/>.
"
SIPTransaction subclass: SIPInviteTransaction [
| sdp ack_branch canceled cancelSent |
<category: 'OsmoSIP-Callagent'>
<comment: 'RFC3161 17.2.1'>
SIPInviteTransaction class >> operationName [
^SIPInviteRequest verb
]
SIPInviteTransaction class >> createWith: aDialog on: aUA with: aSDP cseq: aCseq[
<category: 'creation'>
^ (super createWith: aDialog on: aUA cseq: aCseq)
instVarNamed: #sdp put: aSDP;
yourself.
]
initialize [
<category: 'creation'>
super initialize.
canceled := false.
cancelSent := false.
]
transmit [
| invite |
<category: 'transmit'>
invite := self createInvite: sdp.
self queueData: invite asDatagram dialog: initial_dialog.
]
dispatchDialog: aDialog response: aResponse [
| cseq |
<category: 'private-dispatch'>
"The INVITE transaction is a bit more complicated. It is the only
transaction that can be canceled and we will need to do some things
to check if this is canceled. We have some indirections here
1.) we get a 200 for a BYE/CANCEL in the CSeq
2.) we get a reply but we should cancel, e.g. we were waiting for
a proceeding/notification or the call is too far in the setup
and we will just bye it.
3.) the normal dispatch..."
cseq := aResponse parameter: 'CSeq' ifAbsent: [].
cseq method = 'INVITE'
ifTrue: [self dispatchInvite: aDialog response: aResponse]
ifFalse: [self dispatchOther: aDialog response: aResponse].
]
dispatchOther: aDialog response: aResponse [
| cseq code |
<category: 'private-dispatch'>
code := aResponse code asInteger.
cseq := aResponse parameter: 'CSeq' ifAbsent: [].
code = 200 ifTrue: [
self removeTransaction.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
].
]
handleCancel: aDialog response: aResponse [
| code |
<category: 'private-dispatch'>
code := aResponse code asInteger.
"We will send a CANCEL, maybe it is already the second."
code < 200 ifTrue: [
"Some equipment sent us 100 TRYING. We sent CANCEL, we got a 200 for
and then we 'ACK' the cancel. Just for the equipment to send us trying
again. TODO: Link a cancel transaction here? And verify that it succeeded?
"
cancelSent ifFalse: [
self queueData: (self createCancel asDatagram) dialog: initial_dialog].
cancelSent := true.
].
"We are connected but we didn't want to, let us BYE it"
(code = 200 or: [(code > 200 and: [code ~= 487])]) ifTrue: [
| bye branch |
branch := useragent class generateBranch.
self removeTransaction.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
bye := SIPByeTransaction
createWith: aDialog on: useragent cseq: cseq + 1.
bye start.
].
]
dispatchInvite: aDialog response: aResponse [
<category: 'private-dispatch'>
"Send a cancel if this is a non final response"
canceled
ifTrue: [self handleCancel: aDialog response: aResponse]
ifFalse: [super dispatchDialog: aDialog response: aResponse].
]
respSuccess: aReq dialog: aDialog [
| branch |
<category: 'private-dispatch'>
branch := useragent class generateBranch.
self changeState: self class stateTerminated.
"We send the ACK, if our callbacks don't like the result we
will need to send a BYE to stop that session."
self queueData: (self createAck: branch dialog: aDialog) asDatagram dialog: aDialog.
(super respSuccess: aReq dialog: aDialog) ifFalse: [| bye |
bye := SIPByeTransaction
createWith: aDialog on: useragent cseq: cseq + 1.
bye start.
]
]
respFailure: aReq dialog: aDialog [
<category: 'private-dispatch'>
self logNotice: ('<1p>(<2p>) failure code(<3p>)'
expandMacrosWith: self class with: self branch with: aReq code)
area: #sip.
self changeState: self class stateCompleted.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
^ super respFailure: aReq dialog: aDialog.
]
cancel [
| old_state |
<category: 'cancel'>
canceled := true.
self stopRetransmitTimer.
old_state := self state.
self changeState: self class stateCanceled.
old_state = self class stateProceeding ifTrue: [
self queueData: self createCancel asDatagram dialog: initial_dialog.
cancelSent := true.
].
old_state = self class stateCompleted ifTrue: [
self logError: 'SIPTransaction already completed.' area: #sip.
].
]
]