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

214 lines
5.1 KiB
Smalltalk

"
(C) 2010-2012 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/>.
"
"TODO: Compare with MGCPCommands and share code..."
Object subclass: SIPRequest [
| dest parameters sdp dialog |
<category: 'OsmoSIP-Callagent'>
<comment: 'I should share a parent with MGCPCommand'>
SIPRequest class >> requestForVerb: aVerb [
"Find a class that handles this verb"
SIPRequest allSubclassesDo: [:each |
each verb = aVerb ifTrue: [
^ each new
]
].
^ self error: ('Failed to find class for <1s>'
expandMacrosWith: aVerb).
]
SIPRequest class >> parseFrom: aParseDict [
| req |
req := self requestForVerb: aParseDict first first.
req sdp: aParseDict fourth.
req instVarNamed: #dest put: aParseDict first third.
aParseDict second do: [:each |
req addParameter: each first first value: each first third].
^ req
]
SIPRequest class >> from: aDialog [
^ self new
instVarNamed: #dialog put: aDialog;
yourself
]
isRequest [
^ true
]
dialog [
^ dialog
]
parameters [
<category: 'accessing'>
^ parameters ifNil: [parameters := OrderedCollection new]
]
sdp: aSDP [
<category: 'accessing'>
sdp := aSDP
]
addParameter: aPar value: aValue [
<category: 'accessing'>
self parameters add: (aPar -> aValue).
]
parameter: aPar ifAbsent: aBlock [
<category: 'accessing'>
self parameters do: [:each |
each key = aPar ifTrue: [^ each value]].
aBlock value.
]
asDatagram [
| out |
out := WriteStream on: (String new).
out
nextPutAll: self class verb;
nextPutAll: ' ';
nextPutAll: self dest;
nextPutAll: ' SIP/2.0';
cr; nl.
self parameters do: [:each |
out
nextPutAll: each key;
nextPutAll: ': ';
nextPutAll: each value;
cr; nl.
].
self addDefaults: out.
sdp isNil
ifTrue: [out cr; nl.]
ifFalse: [
out
nextPutAll: 'Content-Type: application/sdp'; cr; nl;
nextPutAll: 'Content-Length: '; nextPutAll: sdp size asString; cr; nl;
cr; nl;
nextPutAll: sdp.
].
^ out contents
]
addDefaults: out [
self parameter: 'To' ifAbsent: [
out
nextPutAll: 'To: ';
nextPutAll: dialog generateTo;
cr; nl].
self parameter: 'From' ifAbsent: [
out
nextPutAll: 'From: ';
nextPutAll: dialog generateFrom;
cr; nl].
]
dest [
^ dest ifNil: [dialog destinationAddress].
]
]
SIPRequest subclass: SIPInviteRequest [
<category: 'OsmoSIP-Callagent'>
SIPInviteRequest class >> verb [
<category: 'verb'>
^ 'INVITE'
]
addDefaults: out [
super addDefaults: out.
dialog isNil ifTrue:[^self].
self parameter: 'Contact' ifAbsent: [
out nextPutAll: 'Contact: <';
nextPutAll: dialog contact;
nextPutAll: '>';
cr; nl.
].
]
]
SIPRequest subclass: SIPACKRequest [
<category: 'OsmoSIP-Callagent'>
SIPACKRequest class >> verb [
<category: 'verb'>
^ 'ACK'
]
]
SIPRequest subclass: SIPCancelRequest [
<category: 'OsmoSIP-Callagent'>
SIPCancelRequest class >> verb [
<category: 'verb'>
^ 'CANCEL'
]
]
SIPRequest subclass: SIPByeRequest [
<category: 'OsmoSIP-Callagent'>
SIPByeRequest class >> verb [
<category: 'verb'>
^ 'BYE'
]
]
SIPRequest subclass: SIPOptionsRequest [
<category: 'OsmoSIP-Callagent'>
SIPOptionsRequest class >> verb [
<category: 'verb'>
^ 'OPTIONS'
]
addDefaults: out [
super addDefaults: out.
"Add a contact if we have a dialog"
dialog isNil ifFalse:[
self parameter: 'Contact' ifAbsent: [
out
nextPutAll: 'Contact: <';
nextPutAll: dialog contact;
nextPutAll: '>'; cr; nl]].
self parameter: 'Accept' ifAbsent: [
out nextPutAll: 'Accept: application/sdp'; cr; nl.
].
]
]