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

142 lines
3.1 KiB
Smalltalk

"
(C) 2010-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 <http://www.gnu.org/licenses/>.
"
Object subclass: SIPResponse [
| code phrase params sdp |
<category: 'OsmoSIP-Callagent'>
SIPResponse class >> parseFrom: aParseDict [
| res |
res := (self
code: (aParseDict first at: 3) with: (aParseDict first at: 5))
sdp: (aParseDict fourth);
yourself.
aParseDict second do: [:each |
res addParameter: each first first
value: each first third
].
^ res
]
SIPResponse class >> code: code with: phrase [
<category: 'factory'>
^ self basicNew
initialize;
code: code;
phrase: phrase;
yourself
]
initialize [
params := OrderedCollection new: 7.
]
code: aCode [
<category: 'accessing'>
code := aCode
]
pharse: aPhrase [
<category: 'accessing'>
phrase := aPhrase
]
code [
<category: 'accessing'>
^ code
]
phrase: aPhrase [
phrase := aPhrase
]
phrase [
<category: 'accessing'>
^ phrase
]
parameters [
<category: 'accessing'>
^params
]
addParameter: aPar value: aValue [
<category: 'accessing'>
params add: (Association key: aPar value: aValue).
]
parameter: aPar [
^ self parameter: aPar ifAbsent: []
]
parameter: aPar ifAbsent: absent [
params do: [:each |
(each key sameAs: aPar) ifTrue: [^ each value]].
^absent value.
]
sdp: aSdp [
sdp := aSdp
]
sdp [
^ sdp
]
asDatagram [
| out |
out := WriteStream on: (String new).
out
nextPutAll: 'SIP/2.0 ';
nextPutAll: code asString;
nextPutAll: ' ';
nextPutAll: phrase;
cr; nl.
params do: [:each |
out
nextPutAll: each key;
nextPutAll: ': ';
nextPutAll: each value asFoldedString;
cr; nl.
].
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
]
isRequest [
^ false
]
]