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

callagent: Parse the CSeq into a special data holder

This commit is contained in:
Holger Hans Peter Freyther 2011-06-14 19:34:54 +02:00
parent 81aa0a0f27
commit 08038a93a4
5 changed files with 55 additions and 13 deletions

View File

@ -76,4 +76,12 @@ SIPGrammar subclass: SIPParser [
with: nodes fourth
]
]
CSeq [
^ super CSeq => [:nodes |
Array
with: nodes first
with: nodes second
with: (SIPCSeq parseFrom: nodes third)]
]
]

View File

@ -47,5 +47,7 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
res := self parse: data.
self assert: res asDatagram = data.
self assert: (res parameter: 'Via') branch = 'z9hG4bKMzQ4NTQzNDgxNCwyNDE1Nw__'.
self assert: (res parameter: 'CSeq') number = 1.
self assert: (res parameter: 'CSeq') method = 'INVITE'.
]
]

View File

@ -16,8 +16,21 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPVia [
| data branch |
Object subclass: SIPParam [
| data |
asFoldedString [
<category: 'compat'>
^ data
]
nextPutAllOn: astream [
^ data nextPutAllOn: astream
]
]
SIPParam subclass: SIPVia [
| branch |
SIPVia class >> findBranch: aData [
<category: 'creation'>
@ -35,16 +48,30 @@ Object subclass: SIPVia [
yourself
]
asFoldedString [
<category: 'compat'>
^ data
]
nextPutAllOn: astream [
^ data nextPutAllOn: astream
]
branch [
^ branch
]
]
SIPParam subclass: SIPCSeq [
| number method |
SIPCSeq class >> parseFrom: aParseDict [
<category: 'creation'>
^ self new
instVarNamed: #data put: aParseDict asFoldedString;
instVarNamed: #number put: aParseDict first asInteger;
instVarNamed: #method put: aParseDict third;
yourself
]
number [
<category: 'accessing'>
^ number
]
method [
<category: 'accessing'>
^ method
]
]

View File

@ -302,7 +302,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
"Simplified..."
<category: 'generic'>
^ (self Via / extension_header), CRLF
^ (self Via / self CSeq / extension_header), CRLF
]
message_body [
@ -364,6 +364,11 @@ PP.PPCompositeParser subclass: SIPGrammar [
(#digit asParser min: 1 max: 3).
]
CSeq [
<category: 'cseq'>
^ 'CSeq' asParser, HCOLON, (#digit asParser plus flatten, LWS, self Method)
]
generic_param [
<category: 'generic'>
^ self token, (EQUAL, self gen_value) optional

View File

@ -96,7 +96,7 @@ PP.PPCompositeParserTest subclass: SIPGrammarTest [
self assert: (hdr at: 4) first third = 'ofcwnpmulmceasg@xiaoyu'.
self assert: (hdr at: 5) first first = 'CSeq'.
self assert: (hdr at: 5) first third = '983 INVITE'.
self assert: (hdr at: 5) first third asFoldedString = '983 INVITE'.
self assert: (hdr at: 6) first first = 'User-Agent'.
self assert: (hdr at: 6) first third = 'FreeSWITCH-mod_sofia/1.0.head-git-dff41af 2011-04-20 14-11-24 +0200'.