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

perf: Various changes to speed up various operations

* Do not use >>#instVarNamed:put: but add selectors
* Pre-allocate some arrays with a default string to avoid
  re-allocations at the start
* Share same parser trees to avoid construction costs
* Remove some lazy allocation and always allocate it
This commit is contained in:
Holger Hans Peter Freyther 2014-08-11 20:41:52 +02:00
parent a536a7a788
commit 9161371a32
8 changed files with 100 additions and 54 deletions

View File

@ -38,12 +38,17 @@ Object subclass: SIPResponse [
SIPResponse class >> code: code with: phrase [
<category: 'factory'>
^ self new
instVarNamed: #code put: code;
instVarNamed: #phrase put: phrase;
^ self basicNew
initialize;
code: code;
phrase: phrase;
yourself
]
initialize [
params := OrderedCollection new: 7.
]
code: aCode [
<category: 'accessing'>
code := aCode
@ -59,6 +64,10 @@ Object subclass: SIPResponse [
^ code
]
phrase: aPhrase [
phrase := aPhrase
]
phrase [
<category: 'accessing'>
^ phrase
@ -66,12 +75,12 @@ Object subclass: SIPResponse [
parameters [
<category: 'accessing'>
^ params ifNil: [params := OrderedCollection new]
^params
]
addParameter: aPar value: aValue [
<category: 'accessing'>
self parameters add: (aPar -> aValue).
params add: (Association key: aPar value: aValue).
]
parameter: aPar [
@ -79,7 +88,7 @@ Object subclass: SIPResponse [
]
parameter: aPar ifAbsent: absent [
self parameters do: [:each |
params do: [:each |
(each key sameAs: aPar) ifTrue: [^ each value]].
^absent value.
@ -105,7 +114,7 @@ Object subclass: SIPResponse [
nextPutAll: phrase;
cr; nl.
self parameters do: [:each |
params do: [:each |
out
nextPutAll: each key;
nextPutAll: ': ';

View File

@ -23,13 +23,25 @@ SIPParam subclass: SIPCSeq [
SIPCSeq class >> parseFrom: aParseDict [
<category: 'creation'>
^ self new
instVarNamed: #data put: aParseDict asFoldedString;
instVarNamed: #number put: aParseDict first asInteger;
instVarNamed: #method put: aParseDict third;
^ self basicNew
data: aParseDict asFoldedString;
number: aParseDict first asInteger;
method: aParseDict third;
yourself
]
data: aData [
data := aData
]
number: aNumber [
number := aNumber
]
method: aMethod [
method := aMethod
]
number [
<category: 'accessing'>
^ number

View File

@ -63,17 +63,14 @@ Object subclass: SIPGenericParam [
asFoldedString [
| str |
<category: 'helper'>
str := (WriteStream on: (String new))
nextPutAll: key;
yourself.
value isNil ifFalse: [
str
nextPut: $=;
nextPutAll: value.
].
^ str contents
^value isNil
ifTrue: [key]
ifFalse: [
(WriteStream on: (String new: key size + value size + 1))
nextPutAll: key;
nextPut: $=;
nextPutAll: value;
contents].
]
isGenericSIPParam [

View File

@ -31,13 +31,25 @@ SIPParam subclass: SIPToFromParam [
SIPToFromParam class >> parseFrom: anArray [
<category: 'creation'>
^ self new
instVarNamed: #addr put: anArray first third;
instVarNamed: #data put: anArray asFoldedString;
instVarNamed: #params put: (self buildParams: anArray second);
^ self basicNew
address: anArray first third;
data: anArray asFoldedString;
params: (self buildParams: anArray second);
yourself
]
address: anAddress [
addr := anAddress
]
data: aData [
data := aData
]
params: aParam [
params := aParam
]
address [
<category: 'accessing'>
^ addr

View File

@ -35,14 +35,30 @@ SIPParam subclass: SIPVia [
<category: 'creation'>
(aParseDict at: 7) second
ifNotNil: [:val | port := val second asInteger].
^ self new
instVarNamed: #data put: aParseDict asFoldedString;
instVarNamed: #address put: (aParseDict at: 7) first;
instVarNamed: #port put: port;
instVarNamed: #branch put: (self findBranch: (aParseDict at: 8));
^self basicNew
data: aParseDict asFoldedString;
address: (aParseDict at: 7) first;
port: port;
branch: (self findBranch: (aParseDict at: 8));
yourself
]
data: aData [
data := aData
]
address: anAddress [
address := anAddress
]
port: aPort [
port := aPort
]
branch: aBranch [
branch := aBranch
]
branch [
^ branch
]

View File

@ -19,7 +19,7 @@
Array extend [
asFoldedString [
<category: '*OsmoSIP-parser'>
^ (Osmo at: #SIPParser) combineUri: self.
^ Osmo.SIPParser combineUri: self.
]
]

View File

@ -36,7 +36,7 @@ SIPGrammar subclass: SIPParser [
SIPParser class >> combineUri: anArray [
| str |
str := WriteStream on: (String new).
str := WriteStream on: (String new: 20).
self addArrayRec: anArray on: str.
^ str contents
]

View File

@ -23,7 +23,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
message_body SIPVersion StatusCode ReasonPhrase
extension_header header_name header_value
Request RequestLine Method extension_method
RequestURI
RequestURI quoted_string token
|
"http://sofia-sip.org/repos/sofia-sip/libsofia-sip-ua/sip/GRAMMAR"
<category: 'OsmoSIP-Grammar'>
@ -226,7 +226,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
]
extension_method [
^ self token
^token
]
Response [
@ -326,7 +326,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
Via [
<category: 'via'>
^ ( 'Via' asParser / 'v' asParser), self HCOLON,
^ ( 'Via' asParser / 'v' asParser), HCOLON,
self via_parm, (COMMA, self via_parm) star
]
@ -359,7 +359,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
via_branch [
<category: 'via'>
^ 'branch' asParser, EQUAL, self token
^ 'branch' asParser, EQUAL, token
]
via_extension [
@ -391,12 +391,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
generic_param [
<category: 'generic'>
^ self token, (EQUAL, self gen_value) optional
^ token, (EQUAL, self gen_value) optional
]
gen_value [
<category: 'generic'>
^ self token / self host / self quoted_string
^token / self host / quoted_string
]
quoted_string [
@ -438,12 +438,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
protocol_name [
<category: 'via'>
^ 'SIP' asParser / self token.
^ 'SIP' asParser / token.
]
protocol_version [
<category: 'via'>
^ self token
^token
]
transport [
@ -454,7 +454,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
other_transport [
<category: 'via'>
^ self token
^token
]
From [
@ -491,7 +491,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
tag_param [
<category: 'to'>
^ 'tag' asParser, EQUAL, self token
^ 'tag' asParser, EQUAL, token
]
name_addr [
@ -501,7 +501,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
display_name [
<category: 'to-from'>
^ (self quoted_string / (self token, LWS) star) flatten
^ (quoted_string / (token, LWS) star) flatten
]
addr_spec [
@ -540,7 +540,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
username [
<category: 'WWW-Authenticate'>
^'username' asParser, EQUAL, self quoted_string
^'username' asParser, EQUAL, quoted_string
]
digest_uri [
@ -607,7 +607,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
realm_value [
<category: 'WWW-Authenticate'>
^self quoted_string
^quoted_string
]
domain [
@ -622,12 +622,12 @@ PP.PPCompositeParser subclass: SIPGrammar [
nonce_value [
<category: 'WWW-Authenticate'>
^self quoted_string
^quoted_string
]
opaque [
<category: 'WWW-Authenticate'>
^'opaque' asParser, EQUAL, self quoted_string
^'opaque' asParser, EQUAL, quoted_string
]
stale [
@ -637,7 +637,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
algorithm [
<category: 'WWW-Authenticate'>
^'algorithm' asParser, EQUAL, ('MD5' asParser / 'MD5-sess' asParser / self token)
^'algorithm' asParser, EQUAL, ('MD5' asParser / 'MD5-sess' asParser / token)
]
qop_options [
@ -649,17 +649,17 @@ PP.PPCompositeParser subclass: SIPGrammar [
qop_value [
<category: 'WWW-Authenticate'>
^'auth' asParser / 'auth-init' asParser / self token
^'auth' asParser / 'auth-init' asParser / token
]
auth_param [
<category: 'WWW-Authenticate'>
^self auth_param_name, EQUAL, (self token / self quoted_string)
^self auth_param_name, EQUAL, (token / quoted_string)
]
auth_param_name [
<category: 'WWW-Authenticate'>
^self token
^token
]
other_response [
@ -669,7 +669,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
auth_scheme [
<category: 'WWW-Authenticate'>
^self token
^token
]
ProxyAuthenticate [
@ -737,7 +737,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
header_name [
<category: 'generic'>
"hmm 1*() should be optional but it must be star here"
^ self token
^token
]
header_value [