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

117 lines
3.0 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: SIPTransaction [
| useragent dialog state timeout success failure cseq branch |
SIPTransaction class >> stateInitial [ ^ 0 ]
SIPTransaction class >> stateTrying [ ^ 1 ]
SIPTransaction class >> stateProceeding [ ^ 2 ]
SIPTransaction class >> stateCompleted [ ^ 3 ]
SIPTransaction class >> stateTerminated [ ^ 4 ]
dialog: aDialog [
dialog := aDialog
]
userAgent: aUA [
<category: 'accessing'>
useragent := aUA
]
state [
^ state ifNil: [^ self class stateInitial]
]
timeout: aTimeout [
timeout := aTimeout
]
success: aSuc [
success := aSuc
]
failure: aFail [
failure := aFail
]
setupTransaction [
"I setup the transaction"
useragent addTransaction: self.
cseq := useragent generateCSeq.
branch := useragent class generateBranch.
]
]
SIPTransaction subclass: SIPInviteTransaction [
| sdp t1 |
<category: 'RFC3161 17.2.1'>
"200ms to get TRYING or OK"
SIPInviteTransaction class >> createWith: aDialog on: aUA with: aSDP [
^ self new
instVarNamed: #sdp put: aSDP;
userAgent: aUA;
dialog: aDialog;
setupTransaction;
yourself.
]
start [
| invite |
state = self class stateInitial ifFalse: [
^ self error: 'Can not restart.'
].
"Enter the state, remember the timeout"
state := self class stateTrying.
t1 := DateTime now.
invite := self createInvite.
]
checkTimeout: now [
"Check if a timeout has happened"
self state = self class stateTrying ifTrue: [
t1 > now ifTrue: [
^ true
]
].
^ false
]
createInvite [
| invite |
<category: 'invite'>
invite := (SIPInviteRequest from: 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;
yourself.
useragent injectDefaults: invite.
^ invite
]
]