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

callagent: Big performance improvement, cache the parser

Constructing a PetitParser is an expensive operation (Object>>becomeForward:)
we can keep the parser in the class. For the SIPTransactions we keep it as
a global, it is assumed that all SIPTransactions operate through the same
process and will not run into concurrency issues.
This commit is contained in:
Holger Hans Peter Freyther 2011-07-06 19:21:20 +02:00
parent 29fdd40b85
commit 44efac4f5b
2 changed files with 24 additions and 3 deletions

View File

@ -208,7 +208,7 @@ Object subclass: SIPUserAgentBase [
]
SIPUserAgentBase subclass: SIPUserAgent [
| transactions retransmit sem |
| dialogs transactions retransmit sem parser |
<category: 'SIP-Callagent'>
<comment: 'I am a user agent base'>
@ -274,13 +274,18 @@ SIPUserAgentBase subclass: SIPUserAgent [
OsmoDispatcher dispatchBlock: [self transportDataInternal: aData].
]
parser [
<category: 'parser'>
^ parser ifNil: [parser := SIPParser new]
]
transportDataInternal: aData [
| req data |
<category: 'private'>
[
data := aData data copyFrom: 1 to: aData size.
req := SIPParser parse: data asString onError: [:e |
req := self parser parse: data asString onError: [:e |
data printNl.
self logError: 'Failed to parse: "%1" with %2'
% {data asString. e} area: #sip.

View File

@ -31,6 +31,8 @@ Object subclass: SIPTransaction [
SIPTransaction class >> stateTerminated [ <category: 'states'> ^ #terminated ]
SIPTransaction class >> stateCanceled [ <category: 'states'> ^ #canceled ]
Grammar := nil.
SIPTransaction class >> createWith: aDialog on: aUA cseq: aCseq [
<category: 'creation'>
^ self new
@ -41,6 +43,20 @@ Object subclass: SIPTransaction [
yourself.
]
SIPTransaction class >> grammar [
<category: 'private'>
^ Grammar ifNil: [Grammar := SIPGrammar new]
]
SIPTransaction class >> verifyGrammar: aData [
<category: 'private'>
self grammar parse: aData onError: [:e |
e logException: 'Outgoing data has parsing error' area: #sip.
e signal
]
]
initialize [
<category: 'creation'>
sem := RecursionLock new.
@ -103,7 +119,7 @@ Object subclass: SIPTransaction [
<category: 'private'>
"validate the output"
res := SIPGrammar parse: aData.
self class verifyGrammar: aData.
datagram := Sockets.Datagram
data: aData