" (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 . " Object subclass: SIPDialog [ | from from_tag to to_tag dest_ip dest_port is_client call_id state contact cseq identity | SIPDialog class >> stateUnconfirmed [ ^ #unconfirmed ] SIPDialog class >> stateConfirmed [ ^ #confirmed ] SIPDialog class >> generateTag [ ^ SIPRandomHelper generateTag ] SIPDialog class >> generateCallId [ ^ SIPRandomHelper generateCallId ] SIPDialog class >> fromUser: aFrom host: aHost port: aPort [ ^ 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 [ ^ 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. ] SIPDialog class >> localFromMessage: aMsg [ "For incoming requests like a SIP INVITE create a new dialog that looks like a local dialog. So From/To are switched and from gets a new tag" ^ self new instVarNamed: #from put: (aMsg parameter: 'To' ifAbsent: []) address; instVarNamed: #from_tag put: self generateTag; instVarNamed: #to put: (aMsg parameter: 'From' ifAbsent: []) address; instVarNamed: #to_tag put: (aMsg parameter: 'From' ifAbsent: []) tag; instVarNamed: #call_id put: (aMsg parameter: 'Call-ID' ifAbsent: []); instVarNamed: #cseq put: (aMsg parameter: 'CSeq' ifAbsent: []) number; instVarNamed: #is_client put: true; yourself. ] SIPDialog class >> format: to withTag: to_tag [ | stream | stream := (WriteStream on: String new) nextPut: $<; nextPutAll: to; nextPut: $>; yourself. to_tag ifNotNil: [ stream nextPutAll: ';tag='; nextPutAll: to_tag. ]. ^ stream contents. ] identity: anIdentity [ identity := anIdentity ] identity [ ^identity ] isClient [ ^ is_client ] from: aFrom [ from := aFrom ] fromTag: aTag [ from_tag := aTag ] to: aTo [ to := aTo ] toTag: aTag [ to_tag := aTag ] callId: aCallId [ call_id := aCallId ] callId [ ^ call_id ] cseq [ ^ cseq ] generateTo [ ^ self class format: to withTag: to_tag. ] generateFrom [ ^ self class format: from withTag: from_tag. ] destinationAddress [ ^ is_client ifTrue: [to] ifFalse: [from] ] from [ ^ from ] from_tag [ ^ from_tag ] to [ ^ to ] to_tag [ ^ to_tag ] contact: aContact [ contact := aContact. ] contact [ ^ contact ifNil: [self from] ] confirm [ state := self class stateConfirmed. ] destIp [ ^ dest_ip ] destPort [ ^ dest_port ] destIp: aIP [ dest_ip := aIP ] destPort: aPort [ dest_port := aPort ] isCompatible: aDialog [ "I check if the remote and the local dialog match. I do this by cross checking the to/from, from/to." self callId = aDialog callId ifFalse: [^false]. self from_tag = aDialog to_tag ifFalse: [ "In case of a re-transmission of a SIP request the remote does not have our local tag yet. Deal with it by checking if we have the remote tag. TODO: maybe look at the kind of request being made." (self isClient and: [self to_tag isNil]) ifTrue: [^false]]. self to_tag = aDialog from_tag ifFalse: [^false]. ^true ] checkCompatible: other [ "I am checking if the dialog is compatible." self callId = other callId ifFalse: [ ^ self error: ('SIPDialog is not compatible due wrong CallID <1p> <2p>.' expandMacrosWithArguments: {self callId. other callId}). ]. self from_tag = other from_tag ifFalse: [ ^ self error: ('SIPDialog is not compatible due wrong from tag <1p> <2p>.' expandMacrosWithArguments: {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 <1p> <2p>.' expandMacrosWithArguments: {self to_tag. other to_tag}) ]. ]. ] newFromRequest: aReq [ | to other | "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 [ ^ self state = self class stateConfirmed ] isUnconfirmed [ ^ self state = self class stateUnconfirmed ] state [ ^ state ifNil: [self class stateUnconfirmed] ] ]