smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0

parser: Extract the generic_param/to_param provide access to the tag

Parse every generic_param (or specialized) into a SIPGenericParam,
provide a asFoldedString implementation, tell the folding code about
it, create a SIPToFromParam that holds the list of params.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-30 11:35:38 +02:00
parent 59d476b5cd
commit b41d170320
3 changed files with 128 additions and 0 deletions

View File

@ -75,3 +75,107 @@ SIPParam subclass: SIPCSeq [
^ method
]
]
Object extend [
isGenericSIPParam [
<category: '*osmo-sip-extension'>
^ false
]
]
Object subclass: SIPGenericParam [
| key value |
<category: 'SIP-Param'>
<comment: 'I am a simple key value pair with the value being optional'>
SIPGenericParam class >> fromOptional: anArray [
"The =value is optional here"
<category: 'creation'>
^ self new
key: anArray first;
value: (anArray second isNil
ifTrue: [nil]
ifFalse: [anArray second second])
]
SIPGenericParam class >> fromMandantory: anArray [
"There must be a key and value"
<category: 'creation'>
^ self new
key: anArray first;
value: anArray third.
]
key: aKey [
<category: 'accessing'>
key := aKey.
]
value: aValue [
<category: 'accessing'>
value := aValue.
]
key [
<category: 'accessing'>
^ key
]
value [
<category: 'accessing'>
^ value
]
asFoldedString [
| str |
<category: 'helper'>
str := (WriteStream on: (String new))
nextPutAll: key;
yourself.
value isNil ifFalse: [
str
nextPut: $=;
nextPutAll: value.
].
^ str contents
]
isGenericSIPParam [
<category: '*osmo-sip-extension'>
^ true
]
]
SIPParam subclass: SIPToFromParam [
| params |
<category: 'SIP-Param'>
<comment: 'I represent a To/From parameter'>
SIPToFromParam class >> buildParams: aParam [
<category: 'creation'>
^ aParam inject: Dictionary new into: [:dict :each |
dict at: (each second key) put: (each second);
yourself].
]
SIPToFromParam class >> parseFrom: anArray [
<category: 'creation'>
^ self new
instVarNamed: #data put: anArray asFoldedString;
instVarNamed: #params put: (self buildParams: anArray second);
yourself
]
tag [
| res |
<category: 'accessing'>
res := params at: 'tag' ifAbsent: [^nil].
^ res value.
]
valueAt: aKey [
^ (params at: aKey) value.
]
]

View File

@ -40,6 +40,7 @@ SIPGrammar subclass: SIPParser [
ifFalse: [
each isString ifTrue: [aStream nextPutAll: each].
each isCharacter ifTrue: [aStream nextPut: each].
each isGenericSIPParam ifTrue: [aStream nextPutAll: each asFoldedString]
].
]
]
@ -67,6 +68,24 @@ SIPGrammar subclass: SIPParser [
^ super SIPSURI => [:nodes | self class combineUri: nodes]
]
generic_param [
^ super generic_param => [:nodes |
SIPGenericParam fromOptional: nodes].
]
tag_param [
^ super tag_param => [:nodes |
SIPGenericParam fromMandantory: nodes].
]
To [
^ super To => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPToFromParam parseFrom: nodes third)]
]
Via [
^ super Via => [:nodes |
Array

View File

@ -49,5 +49,10 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
self assert: (res parameter: 'Via') branch = 'z9hG4bKMzQ4NTQzNDgxNCwyNDE1Nw__'.
self assert: (res parameter: 'CSeq') number = 1.
self assert: (res parameter: 'CSeq') method = 'INVITE'.
self assert: (res parameter: 'To') tag = '42eBv22Fj314N'.
self assert: ((res parameter: 'To') valueAt: 'abc') = 'def'.
self assert: ((res parameter: 'To') valueAt: 'kbc') = nil.
self assert: ((res parameter: 'To') valueAt: 'ajk') = nil.
self should: [((res parameter: 'To') valueAt: 'foo')] raise: SystemExceptions.NotFound.
]
]