diff --git a/callagent/SIPCall.st b/callagent/SIPCall.st index fe9012e..f0b9a06 100644 --- a/callagent/SIPCall.st +++ b/callagent/SIPCall.st @@ -17,7 +17,7 @@ " Object subclass: SIPCall [ - | initial_dialog dialog sdp_offer invite state ua next_cseq | + | initial_dialog dialog sdp_offer sdp_result invite state ua next_cseq | SIPCall class >> stateCancel [ ^ #cancel ] SIPCall class >> stateHangup [ ^ #hangup ] SIPCall class >> stateRemoteHangup [ ^ #remoteHangup ] + SIPCall class >> stateFailed [ ^ #failed ] LegalStates := nil. @@ -91,6 +92,13 @@ will simply ignore everything but the first dialog.'> createCall: aSDPOffer [ + + (self moveToState: self class stateInvite) ifFalse: [ + self logError: 'Call failed to start.' area: #sip. + ^ false + ]. + + sdp_offer := aSDPOffer. next_cseq := initial_dialog cseq + 1. @@ -124,23 +132,69 @@ will simply ignore everything but the first dialog.'> ]. ] + check: aDialog [ + + "I check if this enters a new confirmed dialog or if this is the + confirmed dialog." + + "We have no confirmed dialog, accept it" + ^ dialog isNil + ifTrue: [ + aDialog isConfirmed ifTrue: [ + dialog := aDialog. + self logError: 'SIPCall dialog is confirmed now.' area: #sip. + ]. + true] + ifFalse: [ + "We could fork things here. For multi party call" + dialog to_tag = aDialog to_tag]. + ] + callTimedOut [ self logError: 'Call timed-out.' area: #sip. + + (self moveToState: self class stateTimeout) ifFalse: [ + ^ self logError: 'Call failed to move to timeout.' area: #sip. + ]. ] callSuccess: aResponse dialog: aDialog [ - self logError: 'Call session etsablished.' area: #sip. + (self check: aDialog) ifFalse: [ + self logError: 'Call can only have one session. Ignoring.' area: #sip. + ^ false + ]. + + (self moveToState: self class stateSession) ifTrue: [ + self logError: 'Call session etsablished.' area: #sip. + sdp_result := aResponse sdp. + self newSession. + ^ true + ]. + ^ false ] callFailure: aResponse dialog: aDialog [ - self logError: 'Call Failure.' area: #sip. + (self check: aDialog) ifFalse: [ + self logError: 'Call can only have one session. Ignoring failure.' area: #sip. + ^ false + ]. + + (self moveToState: self class stateFailed) ifTrue: [ + self logError: 'Call Failure.' area: #sip. + self newFailed. + ]. ] callNotification: aResponse dialog: aDialog [ + (self check: aDialog) ifFalse: [ + self logError: 'Call can only have one session. Ignoring notification.' area: #sip. + ^ false + ]. + self logError: 'Call Notification.' area: #sip. ] @@ -151,18 +205,37 @@ will simply ignore everything but the first dialog.'> hangupSuccess: aResponse dialog: aDialog [ + (self check: aDialog) ifFalse: [ + self logError: 'Call can only have one session. Ignoring failure.' area: #sip. + ^ false + ]. + self logError: 'Hang-Up success.' area: #sip. ] hangupFailure: aResponse dialog: aDialog [ + (self check: aDialog) ifFalse: [ + self logError: 'Call can only have one session. Ignoring failure.' area: #sip. + ^ false + ]. + self logError: 'Hang-Up failure.' area: #sip. ] + newSession [ + + ] + + newFailed [ + + ] + nextCSeq [ | res | res := next_cseq. - ^ (next_cseq := next_cseq + 1) + next_cseq := next_cseq + 1. + ^ res ] ] diff --git a/callagent/SIPTransactions.st b/callagent/SIPTransactions.st index 0f9ee5c..9916066 100644 --- a/callagent/SIPTransactions.st +++ b/callagent/SIPTransactions.st @@ -130,8 +130,9 @@ Object subclass: SIPTransaction [ useragent removeTransaction: self. - success ifNotNil: [ - success value: aReq value: aDialog] + ^ success isNil + ifTrue: [true] + ifFalse: [success value: aReq value: aDialog]. ] respFailure: aReq dialog: aDialog [ @@ -143,18 +144,31 @@ Object subclass: SIPTransaction [ ] newData: aReq [ - | code dialog | + | code dialog new_cseq | ('Found response %1 %2' % {aReq code. aReq phrase}) printNl. - sem critical: [ - retransmit_time cancel. - fail_time cancel. + "Compare the sequence number" + new_cseq := (aReq parameter: 'CSeq' ifAbsent: [ + self logError: '%1(%2) response lacks CSeq.' + % {self class. self branch} area: #sip. + ^ false + ]) number. + + cseq = new_cseq ifFalse: [ + self logError: '%1(%2) wrong cseq:. %1 %2.' + % {self class. self branch. cseq. new_cseq} area: #sip. + ^ false ]. "Store all dialogs.... and match them..." dialog := initial_dialog newFromRequest: aReq. + sem critical: [ + retransmit_time cancel. + fail_time cancel. + ]. + code := aReq code asInteger. code < 200 ifTrue: [ ^ self respNotification: aReq dialog: dialog @@ -285,9 +299,12 @@ SIPTransaction subclass: SIPInviteTransaction [ | branch | branch := useragent class generateBranch. self changeState: self class stateTerminated. - self queueData: (self createAck: branch dialog: aDialog) asDatagram - dialog: aDialog. - ^ super respSuccess: aReq dialog: aDialog. + + "TODO: We probably want to accept and then release/BYE it" + (super respSuccess: aReq dialog: aDialog) ifTrue: [ + self queueData: (self createAck: branch dialog: aDialog) asDatagram + dialog: aDialog. + ] ] respFailure: aReq dialog: aDialog [