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/SIPDialog.st

222 lines
5.6 KiB
Smalltalk

"
(C) 2011 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/>.
"
Object subclass: SIPDialog [
| from from_tag to to_tag dest_ip dest_port is_client call_id
state contact cseq |
<comment: 'I represent a dialog between two parties'>
<category: 'SIP-Callagent'>
SIPDialog class >> stateUnconfirmed [ <category: 'state'> ^ #unconfirmed ]
SIPDialog class >> stateConfirmed [ <category: 'state'> ^ #confirmed ]
SIPDialog class >> generateTag [
^ SIPRandomHelper generateTag
]
SIPDialog class >> generateCallId [
^ SIPRandomHelper generateCallId
]
SIPDialog class >> fromUser: aFrom host: aHost port: aPort [
<category: 'factory'>
^ self new
instVarNamed: #from put: aFrom;
instVarNamed: #from_tag put: self generateTag;
instVarNamed: #dest_ip put: aHost;
instVarNamed: #dest_port put: aPort;
instVarNamed: #is_client put: true;
instVarNamed: #call_id put: self generateCallId;
instVarNamed: #cseq put: SIPUserAgent generateCSeq;
yourself
]
SIPDialog class >> fromMessage: aMsg [
<category: 'creation'>
^ self new
instVarNamed: #from put: (aMsg parameter: 'From' ifAbsent: []) address;
instVarNamed: #from_tag put: (aMsg parameter: 'From' ifAbsent: []) tag;
instVarNamed: #to put: (aMsg parameter: 'To' ifAbsent: []) address;
instVarNamed: #to_tag put: (aMsg parameter: 'To' ifAbsent: []) tag;
instVarNamed: #call_id put: (aMsg parameter: 'Call-ID' ifAbsent: []);
instVarNamed: #cseq put: (aMsg parameter: 'CSeq' ifAbsent: []) number;
yourself.
]
isClient [
<category: 'direction'>
^ is_client
]
from: aFrom [
<category: 'accessing'>
from := aFrom
]
fromTag: aTag [
<category: 'accessing'>
from_tag := aTag
]
to: aTo [
<category: 'accessing'>
to := aTo
]
toTag: aTag [
<category: 'accessing'>
to_tag := aTag
]
callId: aCallId [
<category: 'private'>
call_id := aCallId
]
callId [
<category: 'accessing'>
^ call_id
]
cseq [
<category: 'accessing'>
^ cseq
]
generateTo [
<category: 'message'>
^ to_tag isNil
ifTrue: ['<%1>' % {to}]
ifFalse: ['<%1>;tag=%2' % {to. to_tag}]
]
generateFrom [
<category: 'message'>
^ from_tag isNil
ifTrue: ['<%1>' % {from}]
ifFalse: ['<%1>;tag=%2' % {from. from_tag}]
]
destinationAddress [
^ is_client
ifTrue: [to]
ifFalse: [from]
]
from [
<category: 'accessing'>
^ from
]
from_tag [
<category: 'accessing'>
^ from_tag
]
to [
<category: 'accessing'>
^ to
]
to_tag [
<category: 'accessing'>
^ to_tag
]
contact: aContact [
<category: 'accessing'>
contact := aContact.
]
contact [
<category: 'accessing'>
^ contact ifNil: [self from]
]
confirm [
<category: 'accessing'>
state := self class stateConfirmed.
]
destIp [
^ dest_ip
]
destPort [
^ dest_port
]
checkCompatible: other [
<category: 'private'>
"I am checking if the dialog is compatible."
self callId = other callId ifFalse: [
^ self error: 'SIPDialog is not compatible due wrong CallID %1 %2.'
% {self callId. other callId}.
].
self from_tag = other from_tag ifFalse: [
^ self error: 'SIPDialog is not compatible due wrong from tag %1 %2.'
% {self from_tag. other from_tag}
].
self to_tag isNil ifFalse: [
self to_tag = other to_tag ifFalse: [
^ self error: 'SIPDialog is not compatible due to tag %1 %2.'
% {self to_tag. other to_tag}
].
].
]
newFromRequest: aReq [
| to other |
<category: 'handling'>
"I try to confirm a dialog, i also verify that it is somehow compatible."
other := SIPDialog fromMessage: aReq.
self checkCompatible: other.
"I am already confirmed."
self isConfirmed ifTrue: [^self].
"There is no To... hmm return us"
to := aReq parameter: 'To' ifAbsent: [^self].
to tag isNil ifTrue: [^self].
^ self copy
toTag: to tag;
confirm;
yourself.
]
isConfirmed [
<category: 'accessing'>
^ self state = self class stateConfirmed
]
isUnconfirmed [
<category: 'accessing'>
^ self state = self class stateUnconfirmed
]
state [
<category: 'accessing'>
^ state ifNil: [self class stateUnconfirmed]
]
]