" (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 . " SIPCallBase subclass: SIPIncomingCall [ | branch wasTrying wasRinging localSDP remoteSDP | LegalStates := nil. SIPIncomingCall class >> stateAccepted [ ^#accepted] SIPIncomingCall class >> stateRejected [ ^#rejected] SIPIncomingCall class >> legalStates [ ^ LegalStates ifNil: [ LegalStates := { self stateInvite -> self stateInvite. self stateInvite -> self stateRejected. self stateInvite -> self stateFailed. self stateInvite -> self stateAccepted. self stateAccepted -> self stateAccepted. self stateAccepted -> self stateSession. self stateRejected -> self stateRejected. self stateSession -> self stateHangup. self stateSession -> self stateRemoteHangup. } ] ] SIPIncomingCall class >> initWith: anInvite dialog: dialog on: anAgent [ ^self new initialize; remoteSDP: anInvite sdp; useragent: anAgent; confirmDialog: dialog with: anInvite; yourself ] initialize [ state := self class stateInvite. wasTrying := false. wasRinging := false. ] confirmDialog: aDialog with: aRequest [ | via newDialog | "TODO: look at where the data was actually received!" via := (aRequest parameter: 'Via' ifAbsent: []). branch := via branch. newDialog := (SIPDialog localFromMessage: aRequest) destIp: via address; destPort: via port; confirm; yourself. initial_dialog := newDialog. dialog := newDialog. next_cseq := initial_dialog cseq + 1. self registerDialog. ] remoteSDP: aSDP [ remoteSDP := aSDP ] remoteSDP [ ^remoteSDP ] reject [ (self moveToState: self class stateRejected) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to reject.' expandMacrosWith: self callId) area: #sip. ^false]. self sendResponse: 603 text: 'Not Found' data: nil. self unregisterDialog. ] trying [ (self moveToState: self class stateInvite) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to send invite' expandMacrosWith: self callId) area: #sip. ^false]. wasTrying := true. self sendResponse: 100 text: 'Trying' data: nil. ] ringing [ (self moveToState: self class stateInvite) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to send ringing' expandMacrosWith: self callId) area: #sip. ^false]. wasRinging := true. self sendResponse: 180 text: 'Ringing' data: nil. ] pickUp: aSDPFile [ (self moveToState: self class stateAccepted) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to send ringing' expandMacrosWith: self callId) area: #sip. ^false]. localSDP := aSDPFile. self sendResponse: 200 text: 'OK' data: localSDP. ] respondTo: aDialog code: aCode text: aText data: aFile cseq: aCseq[ | resp | resp := (SIPResponse code: aCode with: aText) addParameter: 'Via' value: (ua generateVia: branch); addParameter: 'From' value: aDialog generateFrom; addParameter: 'To' value: aDialog generateTo; addParameter: 'Call-ID' value: aDialog callId; addParameter: 'CSeq' value: ('<1p> <2s>' expandMacrosWith: aDialog cseq with: aCseq); sdp: aFile; yourself. ua queueData: resp asDatagram dialog: aDialog. ] sendResponse: aCode text: aText data: aFile [ ^self respondTo: dialog code: aCode text: aText data: aFile cseq: 'INVITE' ] remoteReInvite: aRequest dialog: aDialog [ self state = self class stateRejected ifTrue: [^self reject]. self state = self class stateAccepted ifTrue: [^self pickUp: localSDP]. wasRinging ifTrue: [^self ringing]. wasTrying ifTrue: [^self trying]. ^self error: ('SIPIncomingCall(<1s>) unknown action for state <2s>' expandMacrosWith: self callId with: self state) area: #sip. ] sessionAcked: anAck dialog: aDialog [ "TODO: This could be an ACK for a reject as well! Deal with it!" (self moveToState: self class stateSession) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to send ringing' expandMacrosWith: self callId) area: #sip. ^false]. "We have a new session now" self sessionNew. ] sessionCanceled: aCancel dialog: aDialog [ (self moveToState: self class stateFailed) ifFalse: [ self logError: ('SIPIncomingCall(<1s>) failed to handle cancel' expandMacrosWith: self callId) area: #sip. self respondTo: aDialog code: '200' text: 'OK' data: nil. ^false]. "Tell the user the session has failed. Use the existing dialogue to say the request was terminated and to reply to the CANCEL transaction itself." self sessionFailed. self sendResponse: 487 text: 'Request Terminated' data: nil. self unregisterDialog. self respondTo: aDialog code: '200' text: 'OK' data: nil cseq: 'CANCEL'. ] ]