I accidentally sent this to the pharo-users list...
---------- Forwarded message ----------
Date: Fri, 8 Oct 2010 23:14:02 +0200 (CEST)
From: Levente Uzonyi <[email protected]>
To: [email protected], [email protected]
Subject: #hasBindingThatBeginsWith:, Shout, E/OCompletion
Hi folks,
there's a method called #hasBindingThatBeginsWith: which seems to be used
only by Shout. If that's true, then it would be better to add it to the
Shout/ShoutCore package if possible.
Also this method is responsible for the slowdown of Shout's parser when there
are undefined variables in the code. Actually only SystemDictionary
#hasBindingsThatBeginsWith: is responsible for the slowdown which uses
Dictionary's implementation which checks all keys.
There's already an issue on Pharo's tracker (with some useful, but with
some wrong info too): http://code.google.com/p/pharo/issues/detail?id=1452 .
The slowdown affects E/OCompletion more, because those invoke Shout's parser
after every keystroke, while Shout uses a background process for parsing.
I propose two possible solutions here:
1) Add the following method (+2-3 other, see below):
SystemDictionary >> hasBindingThatBeginsWith: aString
| className |
aString isEmpty ifTrue: [ ^false ].
(self class fastBindingPrefixSearch and: [
aString first isLowercase ])
ifTrue: [ ^false ].
className := self classNames
findBinary: [ :element |
(element beginsWith: aString)
ifTrue: [ 0 ]
ifFalse: [
aString < element
ifTrue: [ -1 ]
ifFalse: [ 1 ] ] ]
ifNone: nil.
className ifNotNil: [ ^true ].
^super hasBindingThatBeginsWith: aString
How does it work?
There are two optimizations. The first checks if the argument's first letter is
lowercase. If it's a lowercase letter, then it returns false instead of
checking the dictionary. This is the most common case when you're typing
methods with undefined local/instance variables. Since this optimization breaks
Shout's highlighting when the argument is a prefix of a global that begins with
a lowercase letter, there's a boolean preference/setting that enables/disables
this optimization (SystemDictionary class >> #fastBindingPrefixSearch).
The other optimization uses binary search on SystemDictionary's cached class
names, which is a SortedCollection with all the classnames in the system. This
helps when you're typing the name of an existing class. Since Shout uses a
background process, this is mostly useful for E/OCompletion. When none of these
optimizations are usable, the method simply falls back to scanning all keys.
Pros:
- very simple addition
- covers the most common cases
Cons:
- it doesn't work for all cases
- it breaks Shout highlighting a bit
2) Add a new instance variable to SystemDictionary to hold the name of
non-class globals, use binary search on both sorted collections:
SystemDictionary >> hasBindingThatBeginsWith: aString
| name searchBlock |
searchBlock := [ :element |
(element beginsWith: aString)
ifTrue: [ 0 ]
ifFalse: [
aString < element
ifTrue: [ -1 ]
ifFalse: [ 1 ] ] ].
name := self classNames
findBinary: searchBlock
ifNone: nil.
name ifNotNil: [ ^true ].
name := self nonClassNames
findBinary: searchBlock
ifNone: nil.
^name notNil
(for the rest see System-ul.384 in the Inbox for Squeak and
http://leves.web.elte.hu/squeak/SystemDictionary.ul.1.cs for Pharo)
How does it work?
It's just two binary search, one on the class names and one on the non-clas
names. This covers all globals (except those which are not in memory (Squeak
only)).
Pros:
- covers all cases with good performance
- the new cache can be used to speed up other methods (like #allTraits)
Cons:
- modifies SystemDictionary
I'd go with the second solution. What do you think?
Cheers,
Levente
_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project