The Trunk: ToolBuilder-Kernel-ul.128.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
3 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: ToolBuilder-Kernel-ul.128.mcz

commits-2
Marcel Taeumel uploaded a new version of ToolBuilder-Kernel to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Kernel-ul.128.mcz

==================== Summary ====================

Name: ToolBuilder-Kernel-ul.128
Author: ul
Time: 16 July 2019, 11:36:38.782463 pm
UUID: 7153b8e4-a085-4af2-b2a8-3f14585475b0
Ancestors: ToolBuilder-Kernel-mt.127

Further improvements:
- do not convert potentialNames from Array to OrderedCollection
- removed unnecessary ifEmpty: check
- use #indexOf:startingAt: to search for a single character in a string
- applied JIT tricks
- simplified/restructured wildcard/feature-based searches

Ideas not implemented:
- suggestedTypeNames could become suggestedTypeNamesDo:

=============== Diff against ToolBuilder-Kernel-mt.127 ===============

Item was changed:
  ----- Method: UIManager>>classOrTraitFrom:pattern:label: (in category 'system introspecting') -----
  classOrTraitFrom: environment pattern: pattern label: label
  "Given a pattern and an environment, try to find a class or trait using several strategies:
  - EXACT: If there is a class or trait whose name exactly given by pattern, return it.
  - UPPER: If the pattern is upper-case only, find camel-case letters with that sequence.
  - WILD: Try the pattern as-is for regular wild-card search.
  - FEATURE: Split patterns at feature boundaries and insert wild cards between.
  - FUZZY: Split patterns at feature boundaries BUT treat each feature as a full class name.
  If there is only one class or trait in the given environment whose name matches pattern, return it. Otherwise, put up a menu offering the names of all classes that match pattern, and return the class chosen, else nil if nothing chosen.
 
  !!!! In any case, separator characters in the pattern are ignored."
 
  | toMatch potentialNames names selectedIndex |
 
  "If there's a class or trait named as pattern, then return it."
  (environment classOrTraitNamed: pattern) ifNotNil: [:classOrTrait | ^ classOrTrait].
 
  "Validate pattern."
  toMatch := pattern copyWithoutAll: Character separators.
  toMatch := toMatch asLowercase copyWithout: $..
  toMatch ifEmpty: [ ^nil ].
 
  "Fetch search space."
  names := OrderedCollection new.
+ potentialNames := environment classAndTraitNames.
- potentialNames := environment classAndTraitNames asOrderedCollection.
 
  "Try uppercase-only patterns for patterns such as 'WKD' to find 'WeakIdentityKeyDictionary' etc."
+ (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [
+ | patternSize |
+ patternSize := pattern size.
+ potentialNames do: [ :eachName |
+ | lookupIndex characterIndex |
+ lookupIndex := 0.
+ characterIndex := 1.
+ [ (lookupIndex := eachName
+ indexOf: (pattern at: characterIndex)
+ startingAt: lookupIndex + 1) > 0
+ and: [ (characterIndex := characterIndex + 1) <= patternSize ] ] whileTrue.
+ lookupIndex > 0 ifTrue: [ names add: eachName ] ] ].
- names ifEmpty: [
- (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [
- (potentialNames do: [:eachName |
- | isMatch lookupIndex |
- isMatch := true.
- lookupIndex := 0.
- 1 to: pattern size do: [:charIndex | | char |
- char := pattern at: charIndex.
- isMatch ifTrue: [
- lookupIndex := (eachName findString: char asString startingAt: lookupIndex+1 caseSensitive: true).
- isMatch := lookupIndex > 0]].
- isMatch ifTrue: [names add: eachName] ])]].
 
  "Try wildcard search for patterns such as 'Weak*Dict*' to find 'WeakIdentityKeyDictionary' etc."
  names ifEmpty: [
+ potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
+ "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
+ names ifEmpty: [
- potentialNames do: [ :each | (toMatch match: each) ifTrue: [names add: each] ]].
-
- "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
- names ifEmpty: [
- toMatch := pattern copyWithoutAll: '.*#'.
- toMatch findFeatures in: [:features |
  "1) Insert wildcards between features and at the end."
+ toMatch := ((pattern copyWithoutAll: '.*#') findFeatures joinSeparatedBy: '*'), '*'.
+ potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
- toMatch := (features joinSeparatedBy: '*'), '*'.
- names := potentialNames select: [ :each | toMatch match: each ].
  names ifEmpty: [
  "2) Insert wildcards before, between, and after features."
+ toMatch := '*', toMatch.
+ potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ] ] ] ].
- toMatch := '*', (features joinSeparatedBy: '*'), '*'.
- names := potentialNames select: [ :each | toMatch match: each ] ]] ].
 
  "Try some fuzzy matching."
+ pattern suggestedTypeNames do: [ :each |
+ (potentialNames includes: each) ifTrue: [ names add: each ] ].
- names addAll: (pattern suggestedTypeNames select: [ :each | potentialNames includes: each ]).
 
  "Still no match?"
+ names ifEmpty: [ ^nil ].
- names ifEmpty: [ ^ nil ].
 
  "Let the user select if there's more than one possible match. This may give surprising results."
  selectedIndex := names size = 1
  ifTrue: [ 1 ]
  ifFalse: [ self chooseFrom: names title: label ].
  selectedIndex = 0 ifTrue: [ ^nil ].
  ^environment at: (names at: selectedIndex) asSymbol!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: ToolBuilder-Kernel-ul.128.mcz

Nicolas Cellier


Le mer. 17 juil. 2019 à 08:18, <[hidden email]> a écrit :
Marcel Taeumel uploaded a new version of ToolBuilder-Kernel to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Kernel-ul.128.mcz

==================== Summary ====================

Name: ToolBuilder-Kernel-ul.128
Author: ul
Time: 16 July 2019, 11:36:38.782463 pm
UUID: 7153b8e4-a085-4af2-b2a8-3f14585475b0
Ancestors: ToolBuilder-Kernel-mt.127

Further improvements:
- do not convert potentialNames from Array to OrderedCollection
- removed unnecessary ifEmpty: check
- use #indexOf:startingAt: to search for a single character in a string
- applied JIT tricks
- simplified/restructured wildcard/feature-based searches

Ideas not implemented:
- suggestedTypeNames could become suggestedTypeNamesDo:

=============== Diff against ToolBuilder-Kernel-mt.127 ===============

Item was changed:
  ----- Method: UIManager>>classOrTraitFrom:pattern:label: (in category 'system introspecting') -----
  classOrTraitFrom: environment pattern: pattern label: label
        "Given a pattern and an environment, try to find a class or trait using several strategies:
                - EXACT: If there is a class or trait whose name exactly given by pattern, return it.
                - UPPER: If the pattern is upper-case only, find camel-case letters with that sequence.
                - WILD: Try the pattern as-is for regular wild-card search.
                - FEATURE: Split patterns at feature boundaries and insert wild cards between.
                - FUZZY: Split patterns at feature boundaries BUT treat each feature as a full class name.
        If there is only one class or trait in the given environment whose name matches pattern, return it. Otherwise, put up a menu offering the names of all classes that match pattern, and return the class chosen, else nil if nothing chosen.

        !!!! In any case, separator characters in the pattern are ignored."

        | toMatch potentialNames names selectedIndex |

        "If there's a class or trait named as pattern, then return it."
        (environment classOrTraitNamed: pattern) ifNotNil: [:classOrTrait | ^ classOrTrait].

        "Validate pattern."     
        toMatch := pattern copyWithoutAll: Character separators.
Note that pattern copyWithoutAll: CharacterSet separators is a tiny bit faster than Character separators.

        toMatch := toMatch asLowercase copyWithout: $..
        toMatch ifEmpty: [ ^nil ].

        "Fetch search space."
        names := OrderedCollection new.
+       potentialNames := environment classAndTraitNames.
-       potentialNames := environment classAndTraitNames asOrderedCollection.

        "Try uppercase-only patterns for patterns such as 'WKD' to find 'WeakIdentityKeyDictionary' etc."
+       (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [
+               | patternSize |
+               patternSize := pattern size.
+               potentialNames do: [ :eachName |
+                       | lookupIndex characterIndex |
+                       lookupIndex := 0.
+                       characterIndex := 1.
+                       [ (lookupIndex := eachName
+                                       indexOf: (pattern at: characterIndex)
+                                       startingAt: lookupIndex + 1) > 0
+                               and: [ (characterIndex := characterIndex + 1) <= patternSize ] ] whileTrue.
+                       lookupIndex > 0 ifTrue: [ names add: eachName ] ] ].
-       names ifEmpty: [
-               (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [             
-                       (potentialNames do: [:eachName |
-                               | isMatch lookupIndex |
-                               isMatch := true.
-                               lookupIndex := 0.
-                               1 to: pattern size do: [:charIndex | | char |
-                                       char := pattern at: charIndex.
-                                       isMatch ifTrue: [
-                                               lookupIndex := (eachName findString: char asString startingAt: lookupIndex+1 caseSensitive: true).
-                                               isMatch := lookupIndex > 0]].
-                               isMatch ifTrue: [names add: eachName] ])]].

        "Try wildcard search for patterns such as 'Weak*Dict*' to find 'WeakIdentityKeyDictionary' etc."
        names ifEmpty: [
+               potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
+               "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
+               names ifEmpty: [
-               potentialNames do: [ :each | (toMatch match: each) ifTrue: [names add: each] ]].
-       
-       "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
-       names ifEmpty: [
-               toMatch := pattern copyWithoutAll: '.*#'.
-               toMatch findFeatures in: [:features |
                        "1) Insert wildcards between features and at the end."
+                       toMatch := ((pattern copyWithoutAll: '.*#') findFeatures joinSeparatedBy: '*'), '*'.
+                       potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
-                       toMatch := (features joinSeparatedBy: '*'), '*'.
-                       names := potentialNames select: [ :each | toMatch match: each ].
                        names ifEmpty: [       
                                "2) Insert wildcards before, between, and after features."
+                               toMatch := '*', toMatch.
+                               potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ] ] ] ].
-                               toMatch := '*', (features joinSeparatedBy: '*'), '*'.
-                               names := potentialNames select: [ :each | toMatch match: each ] ]] ].

        "Try some fuzzy matching."
+       pattern suggestedTypeNames do: [ :each |
+               (potentialNames includes: each) ifTrue: [ names add: each ] ].
-       names addAll: (pattern suggestedTypeNames select: [ :each | potentialNames includes: each ]).

        "Still no match?"
+       names ifEmpty: [ ^nil ].
-       names ifEmpty: [ ^ nil ].

        "Let the user select if there's more than one possible match. This may give surprising results."       
        selectedIndex := names size = 1
                ifTrue: [ 1 ]
                ifFalse: [ self chooseFrom: names title: label ].
        selectedIndex = 0 ifTrue: [ ^nil ].
        ^environment at: (names at: selectedIndex) asSymbol!




Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: ToolBuilder-Kernel-ul.128.mcz

marcel.taeumel
I think we should extract and move those search algorithms to SystemNavigation so that we can use them without having to open a dialog box.

Best,
Marcel

Am 21.07.2019 09:29:14 schrieb Nicolas Cellier <[hidden email]>:



Le mer. 17 juil. 2019 à 08:18, <[hidden email]> a écrit :
Marcel Taeumel uploaded a new version of ToolBuilder-Kernel to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Kernel-ul.128.mcz

==================== Summary ====================

Name: ToolBuilder-Kernel-ul.128
Author: ul
Time: 16 July 2019, 11:36:38.782463 pm
UUID: 7153b8e4-a085-4af2-b2a8-3f14585475b0
Ancestors: ToolBuilder-Kernel-mt.127

Further improvements:
- do not convert potentialNames from Array to OrderedCollection
- removed unnecessary ifEmpty: check
- use #indexOf:startingAt: to search for a single character in a string
- applied JIT tricks
- simplified/restructured wildcard/feature-based searches

Ideas not implemented:
- suggestedTypeNames could become suggestedTypeNamesDo:

=============== Diff against ToolBuilder-Kernel-mt.127 ===============

Item was changed:
  ----- Method: UIManager>>classOrTraitFrom:pattern:label: (in category 'system introspecting') -----
  classOrTraitFrom: environment pattern: pattern label: label
        "Given a pattern and an environment, try to find a class or trait using several strategies:
                - EXACT: If there is a class or trait whose name exactly given by pattern, return it.
                - UPPER: If the pattern is upper-case only, find camel-case letters with that sequence.
                - WILD: Try the pattern as-is for regular wild-card search.
                - FEATURE: Split patterns at feature boundaries and insert wild cards between.
                - FUZZY: Split patterns at feature boundaries BUT treat each feature as a full class name.
        If there is only one class or trait in the given environment whose name matches pattern, return it. Otherwise, put up a menu offering the names of all classes that match pattern, and return the class chosen, else nil if nothing chosen.

        !!!! In any case, separator characters in the pattern are ignored."

        | toMatch potentialNames names selectedIndex |

        "If there's a class or trait named as pattern, then return it."
        (environment classOrTraitNamed: pattern) ifNotNil: [:classOrTrait | ^ classOrTrait].

        "Validate pattern."     
        toMatch := pattern copyWithoutAll: Character separators.
Note that pattern copyWithoutAll: CharacterSet separators is a tiny bit faster than Character separators.

        toMatch := toMatch asLowercase copyWithout: $..
        toMatch ifEmpty: [ ^nil ].

        "Fetch search space."
        names := OrderedCollection new.
+       potentialNames := environment classAndTraitNames.
-       potentialNames := environment classAndTraitNames asOrderedCollection.

        "Try uppercase-only patterns for patterns such as 'WKD' to find 'WeakIdentityKeyDictionary' etc."
+       (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [
+               | patternSize |
+               patternSize := pattern size.
+               potentialNames do: [ :eachName |
+                       | lookupIndex characterIndex |
+                       lookupIndex := 0.
+                       characterIndex := 1.
+                       [ (lookupIndex := eachName
+                                       indexOf: (pattern at: characterIndex)
+                                       startingAt: lookupIndex + 1) > 0
+                               and: [ (characterIndex := characterIndex + 1) <= patternSize ] ] whileTrue.
+                       lookupIndex > 0 ifTrue: [ names add: eachName ] ] ].
-       names ifEmpty: [
-               (pattern allSatisfy: [:char | char isUppercase]) ifTrue: [             
-                       (potentialNames do: [:eachName |
-                               | isMatch lookupIndex |
-                               isMatch := true.
-                               lookupIndex := 0.
-                               1 to: pattern size do: [:charIndex | | char |
-                                       char := pattern at: charIndex.
-                                       isMatch ifTrue: [
-                                               lookupIndex := (eachName findString: char asString startingAt: lookupIndex+1 caseSensitive: true).
-                                               isMatch := lookupIndex > 0]].
-                               isMatch ifTrue: [names add: eachName] ])]].

        "Try wildcard search for patterns such as 'Weak*Dict*' to find 'WeakIdentityKeyDictionary' etc."
        names ifEmpty: [
+               potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
+               "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
+               names ifEmpty: [
-               potentialNames do: [ :each | (toMatch match: each) ifTrue: [names add: each] ]].
-       
-       "Try feature-based search for patterns such as 'WeakDict' to find 'WeakIdentityKeyDictionary' etc."
-       names ifEmpty: [
-               toMatch := pattern copyWithoutAll: '.*#'.
-               toMatch findFeatures in: [:features |
                        "1) Insert wildcards between features and at the end."
+                       toMatch := ((pattern copyWithoutAll: '.*#') findFeatures joinSeparatedBy: '*'), '*'.
+                       potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ].
-                       toMatch := (features joinSeparatedBy: '*'), '*'.
-                       names := potentialNames select: [ :each | toMatch match: each ].
                        names ifEmpty: [       
                                "2) Insert wildcards before, between, and after features."
+                               toMatch := '*', toMatch.
+                               potentialNames do: [ :each | (toMatch match: each) ifTrue: [ names add: each ] ] ] ] ].
-                               toMatch := '*', (features joinSeparatedBy: '*'), '*'.
-                               names := potentialNames select: [ :each | toMatch match: each ] ]] ].

        "Try some fuzzy matching."
+       pattern suggestedTypeNames do: [ :each |
+               (potentialNames includes: each) ifTrue: [ names add: each ] ].
-       names addAll: (pattern suggestedTypeNames select: [ :each | potentialNames includes: each ]).

        "Still no match?"
+       names ifEmpty: [ ^nil ].
-       names ifEmpty: [ ^ nil ].

        "Let the user select if there's more than one possible match. This may give surprising results."       
        selectedIndex := names size = 1
                ifTrue: [ 1 ]
                ifFalse: [ self chooseFrom: names title: label ].
        selectedIndex = 0 ifTrue: [ ^nil ].
        ^environment at: (names at: selectedIndex) asSymbol!