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/parser/SIPParser.st

198 lines
5.2 KiB
Smalltalk

"
(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 <http://www.gnu.org/licenses/>.
"
SIPGrammar subclass: SIPParser [
<category: 'OsmoSIP-Parser'>
<comment: 'I create either a SIPRequest or a SIPResponse'>
SIPParser class >> addArrayRec: anArray on: aStream [
anArray isNil ifTrue: [^false].
anArray do: [:each |
each isArray
ifTrue: [self addArrayRec: each on: aStream]
ifFalse: [
each isString ifTrue: [aStream nextPutAll: each].
each isCharacter ifTrue: [aStream nextPut: each].
each isGenericSIPParam ifTrue: [aStream nextPutAll: each asFoldedString]
].
]
]
SIPParser class >> combineUri: anArray [
| str |
str := WriteStream on: (String new).
self addArrayRec: anArray on: str.
^ str contents
]
Request [
^ super Request => [:nodes | SIPRequest parseFrom: nodes ]
]
Response [
^ super Response => [:nodes | SIPResponse parseFrom: nodes ]
]
SIPURI [
^ super SIPURI => [:nodes | self class combineUri: nodes]
]
SIPSURI [
^ super SIPSURI => [:nodes | self class combineUri: nodes]
]
via_ttl [
<category: 'via'>
^ super via_ttl => [:nodes | SIPGenericParam fromMandatory: nodes]
]
via_maddr [
<category: 'via'>
^ super via_maddr => [:nodes | SIPGenericParam fromMandatory: nodes]
]
via_received [
<category: 'via'>
^ super via_received => [:nodes | SIPGenericParam fromMandatory: nodes]
]
via_branch [
<category: 'via'>
^ super via_branch => [:nodes | SIPGenericParam fromMandatory: nodes]
]
response_port [
<category: 'via'>
^ super response_port => [:nodes | SIPGenericParam fromOptional: nodes]
]
generic_param [
^ super generic_param => [:nodes |
SIPGenericParam fromOptional: nodes].
]
tag_param [
^ super tag_param => [:nodes |
SIPGenericParam fromMandatory: nodes].
]
From [
^ super From => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPToFromParam parseFrom: nodes third)]
]
To [
^ super To => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPToFromParam parseFrom: nodes third)]
]
Via [
^ super Via => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPVia parseFrom: nodes third)
with: nodes fourth
]
]
CSeq [
^ super CSeq => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPCSeq parseFrom: nodes third)]
]
IPv4address [
^ super IPv4address flatten
]
EQUAL [
^super EQUAL flatten
]
realm_value [
^super realm_value => [:nodes | nodes third]
]
nonce_value [
^super nonce_value => [:nodes | nodes third]
]
stale [
^super stale => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes third asLowercase = 'true']
]
challenge [
^super challenge => [:nodes |
| d |
d := Dictionary new.
(nodes at: 4) do:
[:each | d at: each second first put: each second third ].
d at: (nodes at: 3) first put: (nodes at: 3) third.
d]
]
request_digest [
^super request_digest => [:nodes | nodes second]
]
digest_uri [
^super digest_uri => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes fourth]
]
username [
^super username => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes third third]
]
Authorization [
^super Authorization => [:nodes |
| params |
params := OrderedCollection new.
params add: nodes third third first.
nodes third third second do: [:each |
params add: each second].
Array
with: nodes first
with: nodes second
with: (SIPAuthorization from: params)]
]
]