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

callagent: Simplify the transaction code a small bit

This commit is contained in:
Holger Hans Peter Freyther 2011-06-14 02:43:12 +02:00
parent 4d6b967b21
commit 026e0bd87b
1 changed files with 25 additions and 33 deletions

View File

@ -19,7 +19,8 @@
PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPTransaction [
| useragent dialog state timeout success failure notification cseq branch terminated t1|
| useragent dialog state timeout success failure notification
cseq branch terminated start_time |
SIPTransaction class >> stateInitial [ ^ 0 ]
SIPTransaction class >> stateTrying [ ^ 1 ]
@ -27,6 +28,14 @@ Object subclass: SIPTransaction [
SIPTransaction class >> stateCompleted [ ^ 3 ]
SIPTransaction class >> stateTerminated [ ^ 4 ]
SIPTransaction class >> createWith: aDialog on: aUA [
^ self new
userAgent: aUA;
dialog: aDialog;
setupTransaction;
yourself.
]
dialog: aDialog [
dialog := aDialog
]
@ -126,6 +135,18 @@ Object subclass: SIPTransaction [
^ self respFailure: aReq
]
]
start [
self state = self class stateInitial ifFalse: [
^ self error: 'Can not restart.'
].
"Enter the state, remember the timeout"
state := self class stateTrying.
start_time := DateTime now.
self transmit.
]
]
SIPTransaction subclass: SIPInviteTransaction [
@ -135,25 +156,13 @@ SIPTransaction subclass: SIPInviteTransaction [
"200ms to get TRYING or OK"
SIPInviteTransaction class >> createWith: aDialog on: aUA with: aSDP [
^ self new
^ (super createWith: aDialog on: aUA)
instVarNamed: #sdp put: aSDP;
userAgent: aUA;
dialog: aDialog;
setupTransaction;
yourself.
]
start [
transmit [
| invite |
self 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.
self queueData: invite asDatagram.
]
@ -205,25 +214,8 @@ SIPTransaction subclass: SIPInviteTransaction [
SIPTransaction subclass: SIPByeTransaction [
<category: 'a bye...'>
SIPByeTransaction class >> createWith: aDialog on: aUA [
^ self new
userAgent: aUA;
dialog: aDialog;
setupTransaction;
yourself.
]
start [
transmit [
| bye |
self state = self class stateInitial ifFalse: [
^ self error: 'Can not restart.'
].
"Enter the state, remember the timeout"
state := self class stateTrying.
t1 := DateTime now.
bye := self createBye.
self queueData: bye asDatagram.
]