class: DoWhatIMeanSupport
authorClaus Gittinger <cg@exept.de>
Sat, 31 Aug 2013 00:54:03 +0200
changeset 4352 8e3e22043a75
parent 4351 858c0249bb5a
child 4353 b04d3b1d44ac
class: DoWhatIMeanSupport class definition added: #codeCompletionForMethodSpec: #codeCompletionForMethodSpec:into: #findNodeForInterval:in:allowErrors:mustBeMethod:mustBeExpression: #tryCodeCompletionWithSource:nodeInterval:into: removed:5 methods comment/format in: #documentation #lookupClassForMessage:inClass:instance: changed:8 methods category of: #codeCompletionForMethod:orClass:context:codeView:into: #tryCodeCompletionWithSource:context:nodeInterval:into:
DoWhatIMeanSupport.st
--- a/DoWhatIMeanSupport.st	Thu Aug 29 22:41:59 2013 +0200
+++ b/DoWhatIMeanSupport.st	Sat Aug 31 00:54:03 2013 +0200
@@ -12,7 +12,8 @@
 "{ Package: 'stx:libwidg2' }"
 
 Object subclass:#DoWhatIMeanSupport
-	instanceVariableNames:'tree tokens classOrNil methodOrNil codeView'
+	instanceVariableNames:'tree tokens classOrNil methodOrNil contextOrNil instanceOrNil
+		codeView'
 	classVariableNames:'LastSource LastParseTree LastScanTokens LastChoices'
 	poolDictionaries:''
 	category:'System-Support'
@@ -43,6 +44,10 @@
 
 documentation
 "
+    Attention: this is currently being rewritten and refactored.
+    Don't get mad at the ugly (and duplicate) code.
+    Will cleanup when finished.
+
     misc collected UI support (functional)
     These used to be in the Smalltalk and SystemBrowser class; 
     however, they are only needed for programmers, and some of the stuff is useful in multiple
@@ -51,9 +56,6 @@
         1) not needed for standalone executables
         2) published here to avoid multiple implementations
 
-    Attention: this is currently being rewritten and refactored.
-    Don't get mad at the ugla (and duplicate) code.
-
     [author:]
         Claus Gittinger (cg@exept.de)
 
@@ -78,12 +80,6 @@
         codeCompletionForClass:classOrNil context:contextOrNil codeView:codeView
 !
 
-codeCompletionForMethod:methodOrNil orClass:classOrNil codeView:codeView into:actionBlock
-    self codeCompletionForMethod:methodOrNil orClass:classOrNil context:nil codeView:codeView into:actionBlock
-
-    "Modified (format): / 03-07-2011 / 15:49:49 / cg"
-!
-
 codeCompletionForMethod:methodOrNil orClass:classOrNil context:contextOrNil codeView:codeView into:actionBlock
     "contextOrNil is the current context, if this is called from the debugger;
      nil, if called from the browser.
@@ -1102,7 +1098,8 @@
 !DoWhatIMeanSupport methodsFor:'code completion'!
 
 codeCompletionForClass:classOrNilArg context:contextOrNil codeView:codeViewArg
-    "contextOrNil is the current context, if this is called from the debugger;
+    "OBSOLETE; migrating to use the into protocol.
+     contextOrNil is the current context, if this is called from the debugger;
      nil, if called from the browser.
      If nonNil, we can make better guesses, because we actually know what a variable's type is.
      This is not yet done, sigh"
@@ -1289,7 +1286,7 @@
         ].
         checkedNode isMethod ifTrue:[
             "/ completion in a method's selector pattern
-            self codeCompletionForMethod:checkedNode inClass:classOrNil codeView:codeView.
+            self codeCompletionForMethodSpec:checkedNode.
             ^ self.
         ].
         checkedNode := checkedNode parent.
@@ -1299,6 +1296,61 @@
 
     "Modified: / 04-07-2006 / 18:48:26 / fm"
     "Modified: / 28-08-2013 / 17:15:25 / cg"
+!
+
+codeCompletionForMethod:methodOrNilArg orClass:classOrNilArg context:contextOrNilArg codeView:codeViewArg into:actionBlock
+    "contextOrNil is the current context, if this is called from the debugger;
+     or nil, if called from the browser.
+     If nonNil, we can make better guesses, because we actually know what a variable's type is"
+
+    |crsrPos char interval source partialSource suggestions1 suggestions2 actions1 actions2 title1 title2|
+
+    methodOrNil := methodOrNilArg.
+    classOrNil := classOrNilArg.
+    codeView := codeViewArg.
+    contextOrNil := contextOrNilArg.
+
+"/    classOrNil isNil ifTrue:[
+"/        self information:'No class'.
+"/        ^ self.
+"/    ].
+
+    crsrPos := codeView characterPositionOfCursor"-1".
+    char := codeView characterAtCharacterPosition:crsrPos.
+
+    [crsrPos > 1 and:[char isSeparator or:['.' includes:char]]] whileTrue:[
+        crsrPos := crsrPos - 1.
+        char := codeView characterAtCharacterPosition:crsrPos.
+    ].
+
+    interval := crsrPos-1 to:crsrPos.
+
+    source := codeView contentsAsString string.
+    partialSource := source copyTo:crsrPos.
+
+    self 
+        tryCodeCompletionWithSource:partialSource nodeInterval:interval 
+        into:[:listOfSuggestions :listOfActions :titleWhenAsking |
+            suggestions1 := listOfSuggestions.
+            actions1 := listOfActions.
+            title1 := titleWhenAsking.
+        ].
+
+    self 
+        tryCodeCompletionWithSource:source nodeInterval:interval 
+        into:[:listOfSuggestions :listOfActions :titleWhenAsking |  
+            suggestions2 := listOfSuggestions.
+            actions2 := listOfActions.
+            title2 := titleWhenAsking.
+        ].
+
+    suggestions1 notEmptyOrNil ifTrue:[
+        actionBlock value:suggestions1 value:actions1 value:title1.
+    ] ifFalse:[
+        suggestions2 notEmptyOrNil ifTrue:[
+            actionBlock value:suggestions2 value:actions2 value:title2.
+        ]
+    ].
 ! !
 
 !DoWhatIMeanSupport methodsFor:'code completion-helpers'!
@@ -1392,6 +1444,9 @@
 !
 
 classOfReceiver:receiver inClass:classProvidingNamespaceOrNil instance:instanceOrNil context:contextOrNil
+    "when showing possible completions for a message, it is a good idea to know what the reveiver
+     is."
+
     | nm nodeVal receiverClass|
 
     receiver isLiteral ifTrue:[
@@ -1444,8 +1499,9 @@
     ].
 
     receiver isMessage ifTrue:[
-        (receiver selector = 'new'
-        or:[ receiver selector = 'new:' ]) ifTrue:[
+        "/ some hardwired knowlegde here
+        (receiver selector = #'new'
+        or:[ receiver selector = #'new:' ]) ifTrue:[
             receiverClass := self lookupClassForMessage:receiver inClass:classProvidingNamespaceOrNil.
             receiverClass notNil ifTrue:[
                 receiverClass isBehavior ifTrue:[
@@ -1456,10 +1512,18 @@
             ].
         ].
         classProvidingNamespaceOrNil notNil ifTrue:[
-            (receiver receiver isSelf and:[receiver selector = 'class']) ifTrue:[
+            (receiver receiver isSelf and:[receiver selector = #'class']) ifTrue:[
                 ^ classProvidingNamespaceOrNil class
             ].
         ].
+        (receiver selector = #'size') ifTrue:[
+            ^ SmallInteger
+        ].
+        (#( isNil notNil not emptyOrNil notEmptyOrNil notEmpty isEmpty 
+            = ~= == ~~ 
+            includes: contains: ) includes:receiver selector ) ifTrue:[
+            ^ Boolean
+        ].
     ].
     ^ nil
 
@@ -1467,54 +1531,78 @@
 !
 
 codeCompletionForLiteralSymbol:node into:actionBlock
-    |sym possibleCompletions best start stop oldLen newLen oldVar|
+    "looking for all symbols is way too much and inprecise;
+     experiment: only present symbols which are used by the class,
+     and classes in that class category. We'll see..."
+
+    |sym possibleCompletions longest editAction start stop addSymbol|
 
     "/ Transcript show:'lit in '; show:methodOrNil; show:' / '; showCR:classOrNil.
 
+    start := node start.
+    stop := node stop.
+    (codeView characterAtCharacterPosition:stop) == $' ifTrue:[
+        ^ self.
+    ].
+
     sym := node value.
     possibleCompletions := OrderedCollection new.
 
-    Symbol allInstancesDo:[:existingSym |
-        (existingSym startsWith:sym) ifTrue:[
-            (existingSym = sym) ifFalse:[
-                possibleCompletions add:existingSym
+    addSymbol :=
+        [:aSymbol |
+            (aSymbol startsWith:sym) ifTrue:[
+                (aSymbol = sym) ifFalse:[
+                    possibleCompletions add:aSymbol
+                ].
             ].
         ].
-    ].
-    possibleCompletions sort.
-
-    best := possibleCompletions longestCommonPrefix.
-    (best = sym or:[(possibleCompletions includes:best) not]) ifTrue:[
-        actionBlock value:possibleCompletions value:nil.
-        ^ self.
-    ].
-
-    actionBlock value:(Array with:best) value:nil.
-^ self.
-"/ self showInfo:best.
-
-    start := node start.
-    stop := node stop.
-    (codeView characterAtCharacterPosition:start) == $# ifTrue:[
-        start := start + 1.
+
+    classOrNil notNil ifTrue:[
+        Smalltalk allClassesInCategory:classOrNil do:[:cls |
+            cls theNonMetaclass instAndClassMethodsDo:[:mthd |
+                mthd usedSymbols do:addSymbol
+            ]
+        ].
+    ] ifFalse:[
+        Symbol allInstancesDo:addSymbol.
     ].
-    (codeView characterAtCharacterPosition:start) == $' ifTrue:[
-        start := start + 1.
-        stop := stop - 1.
-    ].
-
-    oldVar := (codeView textFromCharacterPosition:start to:stop) asString string withoutSeparators.
-
-    codeView
-        undoableDo:[ codeView replaceFromCharacterPosition:start to:stop with:best ]
-        info:'Completion'.
-
-    (best startsWith:oldVar) ifTrue:[
-        oldLen := stop - start + 1.
-        newLen := best size.
-        codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
-        codeView dontReplaceSelectionOnInput
-    ].
+
+    possibleCompletions sort.
+
+    longest := possibleCompletions longestCommonPrefix.
+    possibleCompletions remove:longest ifAbsent:[].
+    possibleCompletions addFirst: longest.
+
+    editAction :=
+        [:chosenIndex |
+            |chosen oldSym oldLen newLen|
+
+            chosen := possibleCompletions at:chosenIndex.
+
+            (codeView characterAtCharacterPosition:start) == $# ifTrue:[
+                start := start + 1.
+            ].
+            (codeView characterAtCharacterPosition:start) == $' ifTrue:[
+                start := start + 1.
+            ].
+
+            oldSym := (codeView textFromCharacterPosition:start to:stop) asString string withoutSeparators.
+
+            codeView
+                undoableDo:[ 
+                    codeView replaceFromCharacterPosition:start to:stop with:chosen 
+                ]
+                info:'Completion'.
+
+            (chosen startsWith:oldSym) ifTrue:[
+                oldLen := stop - start + 1.
+                newLen := chosen size.
+                codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
+                codeView dontReplaceSelectionOnInput
+            ].
+        ].
+
+    actionBlock value:possibleCompletions value:editAction value:'symbol'.
 
     "Modified: / 16-02-2010 / 10:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (format): / 03-07-2011 / 15:58:45 / cg"
@@ -1539,11 +1627,7 @@
 
         codeView topView withCursor:(Cursor questionMark) do:[
             srchClass := self lookupClassForMessage:node inClass:classOrNil.
-            srchClass notNil ifTrue:[
-                bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.
-            ] ifFalse:[
-                bestSelectors := Parser findBest:30 selectorsFor:selector in:nil forCompletion:true.
-            ].
+            bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.
         ].
 
         (bestSelectors includes:selector) ifTrue:[
@@ -1553,9 +1637,56 @@
     ].
 
     selector := node selector.
+    parentNode := node parent.
+
+    "/ if there is already space before the cursor, do not attempty to complete the
+    "/ current message. Instead, look for a parent keyword message.
+    "/ is this a good idea? (could be that we want to see possible arguments for the kw message)
+    (codeView characterBeforeCursor ? $ ) isSeparator ifTrue:[
+        (parentNode notNil and:[ parentNode isMessage ]) ifFalse:[
+            ^ self.
+        ].
+    ].
+
     bestSelectors := findBest value:node value:selector.
 
-    parentNode := node parent.
+    "/ if we are behind a keyword messages colon,
+    "/ only look for matching prefix selectors;
+    "/ also, a good completion is to insert an argument;
+    "/ the name of the variable from the implementation, as comment, and selected might be a good one!!
+    selector isKeyword ifTrue:[
+        codeView characterBeforeCursor == $: ifTrue:[
+            bestSelectors := bestSelectors select:[:sel | sel startsWith:selector].
+            bestSelectors isEmpty ifTrue:[
+                "/ nothing better around
+                |argIndex argNames impls|
+
+                argIndex := node selectorParts size.
+                argNames := Set new.
+                impls := Smalltalk allImplementorsOf:selector.
+                impls size < 10 ifTrue:[
+                    impls do:[:eachImplClass |
+                        |mthd argName|
+
+                        mthd := (eachImplClass compiledMethodAt:selector).
+                        argName := mthd methodArgNames at:argIndex.
+                        argNames add:(argName,' in (' ,mthd mclass name allBold,' ',mthd methodDefinitionTemplate).    
+                    ].
+                    argNames notEmptyOrNil ifTrue: [
+                        argNames := argNames asOrderedCollection sort.
+                        actionBlock 
+                            value:argNames
+                            value:[:selIndex |
+                                  ]
+                            value: 'argument name hint'.
+                        ^ self.
+                    ]
+                ]
+            ]
+        ].
+    ].
+
+
 
     "/ if its a unary message AND the parent is a keyword node, look for parent completion too.
     (node selector isUnarySelector 
@@ -1724,121 +1855,132 @@
             ].
         ].
 
-    actionBlock value:allBest value:editAction.
+    actionBlock value:allBest value:editAction value:nil.
 
     "Created: / 10-11-2006 / 13:18:27 / cg"
     "Modified: / 16-02-2010 / 10:33:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 27-07-2013 / 16:34:10 / cg"
 !
 
-codeCompletionForMethod:node 
+codeCompletionForMethodSpec:node 
     "completion in a method's selector pattern"
 
-    |crsrPos
-     selectorSoFar matchingSelectors
-     selectors distances best rest 
-     allExistingMethods nameBag namesByCount selectors1 selectors2|  
-
-    crsrPos := codeView characterPositionOfCursor - 1.
-
-    selectorSoFar := ''.
-    node selectorParts doWithIndex:[:partToken :argNr|
-        |part|
-
-        part := partToken value.
-        selectorSoFar := selectorSoFar , part.
-
-        (crsrPos >= partToken start
-        and:[crsrPos <= partToken stop]) ifTrue:[
-            (classOrNil notNil and:[classOrNil isMeta]) ifTrue:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-                "/ dont forget the stuff in the class-line
-                Metaclass withAllSuperclassesDo:[:cls |
-                    matchingSelectors addAll:(cls methodDictionary keys select:[:sel |sel startsWith:selectorSoFar]).
-                ].
-            ] ifFalse:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theNonMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-            ].
-            selectors := matchingSelectors asOrderedCollection.
-
-            "/ if there is only one, and user has already entered it, he might want to complete the argument-name    
-            (selectors size == 1 
-            and:[selectors first = selectorSoFar]) ifTrue:[
-                selectorSoFar numArgs == 0 ifTrue:[ ^ self ].
-
-                allExistingMethods := (Smalltalk allImplementorsOf:selectorSoFar asSymbol)
-                                        collect:[:cls | cls compiledMethodAt:selectorSoFar asSymbol].
-                nameBag := Bag new.
-                allExistingMethods do:[:eachMethod | nameBag addAll:(eachMethod methodArgNames ? #())].
-                namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
-                "/ take the one which occurs most often     
-                best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
-
-                codeView
-                    undoableDo:[
-                        (crsrPos+1) >= codeView contents size ifTrue:[
-                            codeView paste:best.
-                        ] ifFalse:[
-                            codeView insertString:best atCharacterPosition:crsrPos+1.
-                        ]
-                    ]
-                    info:'completion'.
-                codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
-            ] ifFalse:[
-                "the ones implemented in superclasses are shown first"
-                classOrNil notNil ifTrue:[
-                    selectors1 := selectors select:[:sel | classOrNil respondsTo:sel].  "/ in super
-                    selectors2 := selectors reject:[:sel | selectors1 includes:sel ].   "/ not in super
-                ] ifFalse:[
-                    selectors1 := selectors
-                ].
-
-                distances := selectors1 collect:[:each | each spellAgainst:selectorSoFar].
-                distances sortWith:selectors1.
-                selectors1 reverse.
-                selectors := selectors1.
-
-                selectors2 notEmptyOrNil ifTrue:[
-                    distances := selectors2 collect:[:each | each spellAgainst:selectorSoFar].
-                    distances sortWith:selectors2.
-                    selectors2 reverse.
-                    selectors1 := selectors1 collect:[:sel | sel allBold].
-                    selectors := selectors1,selectors2.
-                ].
-                
-                best := self askUserForCompletion:'selector' for:codeView at:(node start) from:selectors.
-                best isNil ifTrue:[^ self].
-
-                rest := best copyFrom:selectorSoFar size.
-                codeView
-                    undoableDo:[ 
-                        codeView 
-                            replaceFromCharacterPosition:crsrPos+1 
-                            to:crsrPos+1 
-                            with:rest 
-                    ]
-                    info:'Completion'.
-                codeView cursorToCharacterPosition:(crsrPos+1 + rest size - 1).    
-            ].
-            codeView cursorRight. "/ kludge to make it visible   
+    self 
+        codeCompletionForMethodSpec:node
+        into:
+            [:suggestions :action :whatIsIt |
+
+            |chosen|
+
+            chosen := self askUserForCompletion:whatIsIt for:codeView at:node start from:suggestions.
+            action value:(suggestions indexOf:chosen)
         ].
-    ].
+
+"/    |crsrPos
+"/     selectorSoFar matchingSelectors
+"/     selectors distances best rest 
+"/     allExistingMethods nameBag namesByCount selectors1 selectors2|  
+"/
+"/    crsrPos := codeView characterPositionOfCursor - 1.
+"/
+"/    selectorSoFar := ''.
+"/    node selectorParts doWithIndex:[:partToken :argNr|
+"/        |part|
+"/
+"/        part := partToken value.
+"/        selectorSoFar := selectorSoFar , part.
+"/
+"/        (crsrPos >= partToken start
+"/        and:[crsrPos <= partToken stop]) ifTrue:[
+"/            (classOrNil notNil and:[classOrNil isMeta]) ifTrue:[
+"/                matchingSelectors := Smalltalk allClasses
+"/                                    inject:(Set new)
+"/                                    into:[:theSet :eachClass |
+"/                                        |md|
+"/
+"/                                        md := eachClass theMetaclass methodDictionary.
+"/                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
+"/                                        theSet.
+"/                                    ].
+"/                "/ dont forget the stuff in the class-line
+"/                Metaclass withAllSuperclassesDo:[:cls |
+"/                    matchingSelectors addAll:(cls methodDictionary keys select:[:sel |sel startsWith:selectorSoFar]).
+"/                ].
+"/            ] ifFalse:[
+"/                matchingSelectors := Smalltalk allClasses
+"/                                    inject:(Set new)
+"/                                    into:[:theSet :eachClass |
+"/                                        |md|
+"/
+"/                                        md := eachClass theNonMetaclass methodDictionary.
+"/                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
+"/                                        theSet.
+"/                                    ].
+"/            ].
+"/            selectors := matchingSelectors asOrderedCollection.
+"/
+"/            "/ if there is only one, and user has already entered it, he might want to complete the argument-name    
+"/            (selectors size == 1 
+"/            and:[selectors first = selectorSoFar]) ifTrue:[
+"/                selectorSoFar numArgs == 0 ifTrue:[ ^ self ].
+"/
+"/                allExistingMethods := (Smalltalk allImplementorsOf:selectorSoFar asSymbol)
+"/                                        collect:[:cls | cls compiledMethodAt:selectorSoFar asSymbol].
+"/                nameBag := Bag new.
+"/                allExistingMethods do:[:eachMethod | nameBag addAll:(eachMethod methodArgNames ? #())].
+"/                namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
+"/                "/ take the one which occurs most often     
+"/                best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
+"/
+"/                codeView
+"/                    undoableDo:[
+"/                        (crsrPos+1) >= codeView contents size ifTrue:[
+"/                            codeView paste:best.
+"/                        ] ifFalse:[
+"/                            codeView insertString:best atCharacterPosition:crsrPos+1.
+"/                        ]
+"/                    ]
+"/                    info:'completion'.
+"/                codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
+"/            ] ifFalse:[
+"/                "the ones implemented in superclasses are shown first"
+"/                classOrNil notNil ifTrue:[
+"/                    selectors1 := selectors select:[:sel | classOrNil respondsTo:sel].  "/ in super
+"/                    selectors2 := selectors reject:[:sel | selectors1 includes:sel ].   "/ not in super
+"/                ] ifFalse:[
+"/                    selectors1 := selectors
+"/                ].
+"/
+"/                distances := selectors1 collect:[:each | each spellAgainst:selectorSoFar].
+"/                distances sortWith:selectors1.
+"/                selectors1 reverse.
+"/                selectors := selectors1.
+"/
+"/                selectors2 notEmptyOrNil ifTrue:[
+"/                    distances := selectors2 collect:[:each | each spellAgainst:selectorSoFar].
+"/                    distances sortWith:selectors2.
+"/                    selectors2 reverse.
+"/                    selectors1 := selectors1 collect:[:sel | sel allBold].
+"/                    selectors := selectors1,selectors2.
+"/                ].
+"/                
+"/                best := self askUserForCompletion:'selector' for:codeView at:(node start) from:selectors.
+"/                best isNil ifTrue:[^ self].
+"/
+"/                rest := best copyFrom:selectorSoFar size.
+"/                codeView
+"/                    undoableDo:[ 
+"/                        codeView 
+"/                            replaceFromCharacterPosition:crsrPos+1 
+"/                            to:crsrPos+1 
+"/                            with:rest 
+"/                    ]
+"/                    info:'Completion'.
+"/                codeView cursorToCharacterPosition:(crsrPos+1 + rest size - 1).    
+"/            ].
+"/            codeView cursorRight. "/ kludge to make it visible   
+"/        ].
+"/    ].
 
     "Modified: / 04-07-2006 / 18:48:26 / fm"
     "Created: / 10-11-2006 / 13:46:44 / cg"
@@ -1846,128 +1988,14 @@
     "Modified: / 01-06-2012 / 20:31:36 / cg"
 !
 
-codeCompletionForMethod:node inClass:classOrNil codeView:codeView
+codeCompletionForMethodSpec:node into:actionBlock
     "completion in a method's selector pattern"
 
     |crsrPos
      selectorSoFar matchingSelectors
      selectors distances best rest 
-     allExistingMethods nameBag namesByCount selectors1 selectors2|  
-
-    crsrPos := codeView characterPositionOfCursor - 1.
-
-    selectorSoFar := ''.
-    node selectorParts doWithIndex:[:partToken :argNr|
-        |part|
-
-        part := partToken value.
-        selectorSoFar := selectorSoFar , part.
-
-        (crsrPos >= partToken start
-        and:[crsrPos <= partToken stop]) ifTrue:[
-            (classOrNil notNil and:[classOrNil isMeta]) ifTrue:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-                "/ dont forget the stuff in the class-line
-                Metaclass withAllSuperclassesDo:[:cls |
-                    matchingSelectors addAll:(cls methodDictionary keys select:[:sel |sel startsWith:selectorSoFar]).
-                ].
-            ] ifFalse:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theNonMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-            ].
-            selectors := matchingSelectors asOrderedCollection.
-
-            "/ if there is only one, and user has already entered it, he might want to complete the argument-name    
-            (selectors size == 1 
-            and:[selectors first = selectorSoFar]) ifTrue:[
-                selectorSoFar numArgs == 0 ifTrue:[ ^ self ].
-
-                allExistingMethods := (Smalltalk allImplementorsOf:selectorSoFar asSymbol)
-                                        collect:[:cls | cls compiledMethodAt:selectorSoFar asSymbol].
-                nameBag := Bag new.
-                allExistingMethods do:[:eachMethod | nameBag addAll:(eachMethod methodArgNames ? #())].
-                namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
-                "/ take the one which occurs most often     
-                best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
-
-                codeView
-                    undoableDo:[
-                        (crsrPos+1) >= codeView contents size ifTrue:[
-                            codeView paste:best.
-                        ] ifFalse:[
-                            codeView insertString:best atCharacterPosition:crsrPos+1.
-                        ]
-                    ]
-                    info:'completion'.
-                codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
-            ] ifFalse:[
-                "the ones implemented in superclasses are shown first"
-                classOrNil notNil ifTrue:[
-                    selectors1 := selectors select:[:sel | classOrNil respondsTo:sel].  "/ in super
-                    selectors2 := selectors reject:[:sel | selectors1 includes:sel ].   "/ not in super
-                ] ifFalse:[
-                    selectors1 := selectors
-                ].
-
-                distances := selectors1 collect:[:each | each spellAgainst:selectorSoFar].
-                distances sortWith:selectors1.
-                selectors1 reverse.
-                selectors := selectors1.
-
-                selectors2 notEmptyOrNil ifTrue:[
-                    distances := selectors2 collect:[:each | each spellAgainst:selectorSoFar].
-                    distances sortWith:selectors2.
-                    selectors2 reverse.
-                    selectors1 := selectors1 collect:[:sel | sel allBold].
-                    selectors := selectors1,selectors2.
-                ].
-                
-                best := self askUserForCompletion:'selector' for:codeView at:(node start) from:selectors.
-                best isNil ifTrue:[^ self].
-
-                rest := best copyFrom:selectorSoFar size.
-                codeView
-                    undoableDo:[ 
-                        codeView 
-                            replaceFromCharacterPosition:crsrPos+1 
-                            to:crsrPos+1 
-                            with:rest 
-                    ]
-                    info:'Completion'.
-                codeView cursorToCharacterPosition:(crsrPos+1 + rest size - 1).    
-            ].
-            codeView cursorRight. "/ kludge to make it visible   
-        ].
-    ].
-
-    "Modified: / 04-07-2006 / 18:48:26 / fm"
-    "Created: / 10-11-2006 / 13:46:44 / cg"
-    "Modified: / 16-02-2010 / 10:13:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-06-2012 / 20:31:36 / cg"
-!
-
-codeCompletionForMethod:node inClass:classOrNil codeView:codeView into:actionBlock
-    "completion in a method's selector pattern"
-
-    |crsrPos
-     selectorSoFar matchingSelectors
-     selectors distances best rest 
-     allExistingMethods nameBag namesByCount selectors1 selectors2|  
+     allExistingMethods nameBag namesByCount selectors1 selectors2 
+     editAction argNames|  
 
     "/ Transcript showCR:'m'.
     crsrPos := codeView characterPositionOfCursor - 1.
@@ -2020,138 +2048,30 @@
                 namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
                 "/ take the one which occurs most often     
                 "/ best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
-                actionBlock value:(namesByCount collect:[:a | a key]) value:nil.
+                argNames := (namesByCount collect:[:a | a key]).
+                editAction :=
+                        [:chosenIndex |
+                            |chosenName|
+
+                            chosenName := argNames at:chosenIndex.
+                            codeView
+                                undoableDo:[
+                                    (crsrPos+1) >= codeView contents size ifTrue:[
+                                        codeView paste:best.
+                                    ] ifFalse:[
+                                        codeView insertString:chosenName atCharacterPosition:crsrPos+1.
+                                    ].
+                                    codeView cursorToCharacterPosition:(crsrPos + chosenName size - 1).    
+                                ]
+                                info:'completion'.
+                        ].
+                actionBlock 
+                    value:argNames 
+                    value:editAction
+                    value:'argument'.
+
                 ^ self.
 
-                codeView
-                    undoableDo:[
-                        (crsrPos+1) >= codeView contents size ifTrue:[
-                            codeView paste:best.
-                        ] ifFalse:[
-                            codeView insertString:best atCharacterPosition:crsrPos+1.
-                        ]
-                    ]
-                    info:'completion'.
-                codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
-            ] ifFalse:[
-                "the ones implemented in superclasses are shown first"
-                classOrNil notNil ifTrue:[
-                    selectors1 := selectors select:[:sel | classOrNil respondsTo:sel].  "/ in super
-                    selectors2 := selectors reject:[:sel | selectors1 includes:sel ].   "/ not in super
-                ] ifFalse:[
-                    selectors1 := selectors
-                ].
-
-                distances := selectors1 collect:[:each | each spellAgainst:selectorSoFar].
-                distances sortWith:selectors1.
-                selectors1 reverse.
-                selectors := selectors1.
-
-                selectors2 notEmptyOrNil ifTrue:[
-                    distances := selectors2 collect:[:each | each spellAgainst:selectorSoFar].
-                    distances sortWith:selectors2.
-                    selectors2 reverse.
-                    selectors1 := selectors1 collect:[:sel | sel allBold].
-                    selectors := selectors1,selectors2.
-                ].
-                
-                "/ best := self askUserForCompletion:'selector' for:codeView at:(node start) from:selectors.
-                best := actionBlock value:selectors value:nil.
-                best isNil ifTrue:[^ self].
-
-                rest := best copyFrom:selectorSoFar size.
-                codeView
-                    undoableDo:[ 
-                        codeView 
-                            replaceFromCharacterPosition:crsrPos+1 
-                            to:crsrPos+1 
-                            with:rest 
-                    ]
-                    info:'Completion'.
-                codeView cursorToCharacterPosition:(crsrPos+1 + rest size - 1).    
-            ].
-            codeView cursorRight. "/ kludge to make it visible   
-        ].
-    ].
-
-    "Modified: / 04-07-2006 / 18:48:26 / fm"
-    "Created: / 10-11-2006 / 13:46:44 / cg"
-    "Modified: / 16-02-2010 / 10:13:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-06-2012 / 20:31:36 / cg"
-!
-
-codeCompletionForMethod:node into:actionBlock
-    "completion in a method's selector pattern"
-
-    |crsrPos
-     selectorSoFar matchingSelectors
-     selectors distances best rest 
-     allExistingMethods nameBag namesByCount selectors1 selectors2 editAction|  
-
-    "/ Transcript showCR:'m'.
-    crsrPos := codeView characterPositionOfCursor - 1.
-
-    selectorSoFar := ''.
-    node selectorParts doWithIndex:[:partToken :argNr|
-        |part|
-
-        part := partToken value.
-        selectorSoFar := selectorSoFar , part.
-
-        (crsrPos >= partToken start
-        and:[crsrPos <= partToken stop]) ifTrue:[
-            (classOrNil notNil and:[classOrNil isMeta]) ifTrue:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-                "/ dont forget the stuff in the class-line
-                Metaclass withAllSuperclassesDo:[:cls |
-                    matchingSelectors addAll:(cls methodDictionary keys select:[:sel |sel startsWith:selectorSoFar]).
-                ].
-            ] ifFalse:[
-                matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        md := eachClass theNonMetaclass methodDictionary.
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-            ].
-            selectors := matchingSelectors asOrderedCollection.
-
-            "/ if there is only one, and user has already entered it, he might want to complete the argument-name    
-            (selectors size == 1 
-            and:[selectors first = selectorSoFar]) ifTrue:[
-                selectorSoFar numArgs == 0 ifTrue:[ ^ self ].
-
-                allExistingMethods := (Smalltalk allImplementorsOf:selectorSoFar asSymbol)
-                                        collect:[:cls | cls compiledMethodAt:selectorSoFar asSymbol].
-                nameBag := Bag new.
-                allExistingMethods do:[:eachMethod | nameBag addAll:(eachMethod methodArgNames ? #())].
-                namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
-                "/ take the one which occurs most often     
-                "/ best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
-                actionBlock value:(namesByCount collect:[:a | a key]) value:nil.
-                ^ self.
-
-                codeView
-                    undoableDo:[
-                        (crsrPos+1) >= codeView contents size ifTrue:[
-                            codeView paste:best.
-                        ] ifFalse:[
-                            codeView insertString:best atCharacterPosition:crsrPos+1.
-                        ]
-                    ]
-                    info:'completion'.
-                codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
             ] ifFalse:[
                 "the ones implemented in superclasses are shown first"
                 classOrNil notNil ifTrue:[
@@ -2175,9 +2095,9 @@
                 ].
 
                 editAction := 
-                    [:selectedCOmpletionIndex |
-
-                        best := selectors at:selectedCOmpletionIndex.
+                    [:selectedCompletionIndex |
+
+                        best := selectors at:selectedCompletionIndex.
                         rest := best copyFrom:selectorSoFar size.
                         codeView
                             undoableDo:[ 
@@ -2192,8 +2112,10 @@
                     ].
                 
                 "/ best := self askUserForCompletion:'selector' for:codeView at:(node start) from:selectors.
-                best := actionBlock value:selectors value:editAction.
-                best isNil ifTrue:[^ self].
+                actionBlock 
+                    value:selectors 
+                    value:editAction
+                    value:'selector'.
             ].
         ].
     ].
@@ -2204,114 +2126,13 @@
     "Modified: / 01-06-2012 / 20:31:36 / cg"
 !
 
-codeCompletionForMethod:methodOrNilArg orClass:classOrNilArg context:contextOrNil codeView:codeViewArg into:actionBlock
-    "contextOrNil is the current context, if this is called from the debugger;
-     nil, if called from the browser.
-     If nonNil, we can make better guesses, because we actually know what a variable's type is.
-     This is not yet done, sigh"
-
-    |crsrPos char interval source node checkedNode|
-
-    methodOrNil := methodOrNilArg.
-    classOrNil := classOrNilArg.
-    codeView := codeViewArg.
-
-"/    classOrNil isNil ifTrue:[
-"/        self information:'No class'.
-"/        ^ self.
-"/    ].
-
-    crsrPos := codeView characterPositionOfCursor"-1".
-    char := codeView characterAtCharacterPosition:crsrPos.
-    [crsrPos > 1 and:[char isSeparator or:['.' includes:char]]] whileTrue:[
-        crsrPos := crsrPos - 1.
-        char := codeView characterAtCharacterPosition:crsrPos.
-    ].
-
-    interval := codeView selectedInterval.
-    interval isEmpty ifTrue:[
-        interval := crsrPos-1 to:crsrPos.
-    ].
-
-    source := codeView contentsAsString string.
-    "/ source := source copyTo:crsrPos.
-
-    "/ this is too naive and stupid; if there is a syntactic error,
-    "/ we will not find a node for a long time (stepping back more and more,
-    "/ until reaching the beginning). This leads to a thousand and more times reparsing
-    "/ without any progress.
-    "/ TODO: do it vice-versa, in that the parser does a callOut for every node generated
-    "/ as it parses the code. Stop, when the interval is hit.
-    "/ that will also work for syntactic incorrect source code.
-    classOrNil notNil ifTrue:[
-        node := self findNodeForInterval:interval in:source allowErrors:true mustBeMethod:true.   
-    ].
-    node isNil ifTrue:[
-        node := self findNodeForInterval:interval in:source allowErrors:true mustBeMethod:false.   
-    ].
-"/    [node isNil] whileTrue:[
-"/        "/ expand to the left ...
-"/        interval start > 1 ifFalse:[
-"/            self information:'No parseNode found'.
-"/            ^ self.
-"/        ].
-"/        interval start:(interval start - 1).
-"/        node := self findNodeForInterval:interval in:source allowErrors:true.
-"/    ].
-    node isNil ifTrue:[
-        Transcript showCR:'No parseNode found (syntax error before?)'.
-        self breakPoint:#cg.
-        self information:'No parseNode found (syntax error before?)'.
-        ^ self.
-    ].
-
-    (node isVariable
-    and:[ node parent notNil
-    and:[ node parent isMessage
-    and:[ node stop < (codeView characterPositionOfCursor-1) ]]]) ifTrue:[
-        node := node parent.
-    ].
-
-    node isVariable ifTrue:[
-        self codeCompletionForVariable:node into:actionBlock.
-        ^ self.
-    ].
-    node isLiteral ifTrue:[
-        node value isSymbol ifTrue:[
-            self codeCompletionForLiteralSymbol:node into:actionBlock.
-            ^ self.
-        ].
-        ^ self "/ huh - strings or what?
-    ].
-
-    checkedNode := node.
-    [checkedNode notNil] whileTrue:[
-        checkedNode isMessage ifTrue:[
-            "/ completion in a message-send
-            self codeCompletionForMessage:checkedNode into:actionBlock.
-            ^ self
-        ].
-        checkedNode isMethod ifTrue:[
-            "/ completion in a method's selector pattern
-            self codeCompletionForMethod:checkedNode into:actionBlock.
-            ^ self.
-        ].
-        checkedNode := checkedNode parent.
-    ].
-
-    self information:'Node is neither variable nor message.'.
-
-    "Modified: / 04-07-2006 / 18:48:26 / fm"
-    "Modified: / 16-09-2011 / 14:54:47 / cg"
-!
-
 codeCompletionForVariable:node into:actionBlock
     |nonMetaClass crsrPos nm parent
      allVariables allDistances variablesAlreadyAdded nodeVal
      char oldLen newLen 
      getDistanceComputeBlockWithWeight addWithFactorBlock names allTheBest bestAssoc
      globalFactor localFactor selectorOfMessageToNode tree implementors argIdx namesUsed kwPart
-     editAction suggestions nameIsOK|
+     editAction suggestions nameIsOK longerNames|
 
     "/ Transcript show:'var in '; show:methodOrNil; show:' / '; showCR:classOrNil.
     classOrNil notNil ifTrue:[
@@ -2362,6 +2183,8 @@
         ]
     ].
 
+    "/ this is pure voodoo magic (tries to make a good spelling weight,
+    "/ by weighting the number of startsWith characters into the spelling distance...)
     getDistanceComputeBlockWithWeight :=
         [:weight |
             [:each |
@@ -2514,7 +2337,11 @@
 
             "/ globals
             names := Smalltalk keys.
-            "/ names := names reject:[:nm | nm includes:$:].
+            names := names reject:
+                            [:nm | 
+                                (nm includes:$:) and:[ (Smalltalk at:nm) isBehavior not]
+                            ].
+
             names := names select:[:nm | nm isUppercaseFirst ] as:OrderedCollection.
             responders := names select:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
             nonResponders := names reject:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
@@ -2574,7 +2401,7 @@
         "/ also assuming, that nil is short so its usually typed in.
         addWithFactorBlock value:#('self') value:(2.5 * localFactor).
         addWithFactorBlock value:#('nil') value:(0.5 * localFactor).
-        addWithFactorBlock value:#('super' 'false') value:(2 * localFactor).
+        addWithFactorBlock value:#('super' 'false' 'true') value:(2 * localFactor).
         addWithFactorBlock value:#('thisContext') value:(1 * localFactor).
     ].
 
@@ -2597,16 +2424,34 @@
                                     ]
                                 ]
                       ].
-    allTheBest := allDistances select:[:entry | entry value >= (bestAssoc value * 0.5)].
+
+    allTheBest := allDistances.
+
     nameIsOK ifTrue:[
-        allTheBest := allTheBest select:[:assoc | assoc key startsWith:nm].
+        "/ if the name already exists, only allow longer names, if there are
+        longerNames := allTheBest select:[:assoc | assoc key startsWith:nm].
+        longerNames notEmpty ifTrue:[
+            allTheBest := longerNames.
+        ].
     ].
-
     allTheBest size > 15 ifTrue:[
-        allTheBest := allDistances select:[:entry | entry value >= (bestAssoc value * 0.8)].
+        "/ remove all those which are below some threshold
+        0.4 to:0.8 by:0.1 do:[:delta |
+            "/ if still too many, remove more and more
+            allTheBest size > 15 ifTrue:[
+                allTheBest := allDistances select:[:entry | (entry key startsWith:nm) or:[ entry value >= (bestAssoc value * delta) ]].
+            ]
+        ].
     ].
     suggestions := allTheBest collect:[:assoc | assoc key].
 
+    "/ finally, the trick is to bring them into a reasonable order...
+    "/ sort the prefix matchers by length, the others by spelling distance
+    "/ and bring the prefix-matchers towards the beginning
+    suggestions := ((suggestions select:[:s | s startsWith:nm]) sort:[:a :b | a size < b size ])
+                   ,
+                   (suggestions reject:[:s | s startsWith:nm]).
+
     editAction :=
         [:index |
             |answer start stop oldVar|
@@ -2617,19 +2462,26 @@
             stop := node stop.
             oldVar := (codeView textFromCharacterPosition:start to:stop) asString string withoutSeparators.
 
+            oldLen := stop - start + 1.
+            newLen := answer size.
+
             codeView
-                undoableDo:[ codeView replaceFromCharacterPosition:start to:stop with:answer ]
+                undoableDo:[ 
+                    codeView replaceFromCharacterPosition:start to:stop with:(answer).
+
+                    (answer startsWith:oldVar) ifTrue:[
+                        codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
+                        codeView dontReplaceSelectionOnInput
+                    ] ifFalse:[
+                        codeView selectFromCharacterPosition:start to:start+newLen-1.
+                        codeView dontReplaceSelectionOnInput
+                    ].
+                ]
                 info:'Completion'.
 
-            (answer startsWith:oldVar) ifTrue:[
-                oldLen := stop - start + 1.
-                newLen := answer size.
-                codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
-                codeView dontReplaceSelectionOnInput
-            ].
         ].
 
-    actionBlock value:suggestions value:editAction.
+    actionBlock value:suggestions value:editAction value:nil.
 
     "Created: / 10-11-2006 / 13:16:33 / cg"
     "Modified: / 16-02-2010 / 10:13:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2695,7 +2547,17 @@
 findNodeForInterval:interval in:source allowErrors:allowErrors mustBeMethod:mustBeMethod
     "if mustBeMethod is true, do not try a regular expression (as in a workspace)."
 
-    |"errCount" intersectingNodes smallestIntersectingNode firstIntersectingNode onErrorBlock nodeGenerationHook parser|
+    ^ self
+        findNodeForInterval:interval in:source allowErrors:allowErrors 
+        mustBeMethod:mustBeMethod mustBeExpression:false
+!
+
+findNodeForInterval:interval in:source allowErrors:allowErrors mustBeMethod:mustBeMethod mustBeExpression:mustBeExpression
+    "parse it as expression or method;
+     if mustBeMethod is true, do not try a regular expressions (as in a workspace);
+     if musBeExpression is true, do not try method"
+
+    |intersectingNodes smallestIntersectingNode firstIntersectingNode onErrorBlock nodeGenerationHook parser|
 
     interval isEmpty ifTrue: [^ nil].
     RBParser isNil ifTrue: [^ nil].
@@ -2731,10 +2593,9 @@
             [:node |
                 "/ we would like to return here as soon as the node has been created by the parser;
                 "/ however, at that time, its parent(chain) is not yet created and so we might not know
-                "/ what the semantic intepretation (especially: scope of variable) will be.
+                "/ what the semantic interpretation (especially: scope of variable) will be.
                 "/ therefore, we parse all, and return the found node at the end.
-                "//// ^ node.
-"/ self halt.
+
                 (node intersectsInterval:interval) ifTrue:[
                     intersectingNodes add:node.
                     firstIntersectingNode isNil ifTrue:[
@@ -2751,16 +2612,18 @@
                 ].
             ].
 
-        tree := RBParser
-                    parseMethod: source 
-                    setup:[:p | 
-                        parser := p.
-                        p rememberNodes:true.
-                        p rememberTokens:true.
-                        p nodeGenerationCallback:nodeGenerationHook
-                    ]
-                    onError: onErrorBlock.
-        parser notNil ifTrue:[ tokens := parser rememberedTokens ].
+        mustBeExpression ifFalse:[
+            tree := RBParser
+                        parseMethod: source 
+                        setup:[:p | 
+                            parser := p.
+                            p rememberNodes:true.
+                            p rememberTokens:true.
+                            p nodeGenerationCallback:nodeGenerationHook
+                        ]
+                        onError: onErrorBlock.
+            parser notNil ifTrue:[ tokens := parser rememberedTokens ].
+        ].
 
         mustBeMethod ifTrue:[
             "/ only cache parsed methods
@@ -2784,7 +2647,6 @@
                 parser notNil ifTrue:[ tokens := parser rememberedTokens ].
             ].
         ].
-"/ self halt.
         firstIntersectingNode notNil ifTrue:[ ^ firstIntersectingNode ].
     ].
 
@@ -2847,8 +2709,7 @@
 
 lookupClassForMessage:node inClass:classProvidingNamespaceOrNil instance:instanceOrNil
     ^ self 
-        lookupClassForMessage:node inClass:classProvidingNamespaceOrNil instance:instanceOrNil 
-        context:nil
+        lookupClassForMessage:node inClass:classProvidingNamespaceOrNil instance:instanceOrNil context:nil
 !
 
 lookupClassForMessage:node inClass:classProvidingNamespaceOrNil instance:instanceOrNil context:contextOrNil
@@ -2954,6 +2815,96 @@
     ^ tree
 
     "Modified: / 13-01-2012 / 11:54:30 / cg"
+!
+
+tryCodeCompletionWithSource:source nodeInterval:interval into:actionBlock
+    "this is tried twice; first with the source copied up to the cursor position,
+     then with the full source.
+     Either one may geive better results (for example, when completing
+     after a keyword selector, and the remaining code would lead to a syntactically
+     legal, but stupid message send to be parsed...
+     (which happens often after inserting)"
+
+    |node checkedNode characterBeforeCursor nodeIsInTemporaries|
+
+    "/ this is too naive and stupid; if there is a syntactic error,
+    "/ we will not find a node for a long time (stepping back more and more,
+    "/ until reaching the beginning). This leads to a thousand and more times reparsing
+    "/ without any progress.
+    "/ TODO: do it vice-versa, in that the parser does a callOut for every node generated
+    "/ as it parses the code. Stop, when the interval is hit.
+    "/ that will also work for syntactic incorrect source code.
+    classOrNil notNil ifTrue:[
+        node := self findNodeForInterval:interval in:source allowErrors:true mustBeMethod:true.   
+    ].
+    node isNil ifTrue:[
+        node := self findNodeForInterval:interval in:source allowErrors:true mustBeMethod:false mustBeExpression:true.   
+        node isNil ifTrue:[
+            Transcript showCR:'No parseNode found (syntax error before?)'.
+            self information:'No parseNode found (syntax error before?)'.
+            ^ self.
+        ].
+    ].
+
+    (node isVariable
+    and:[ node parent notNil
+    and:[ node parent isMessage
+    and:[ node stop < (codeView characterPositionOfCursor-1) ]]]) ifTrue:[
+        node := node parent.
+    ].
+
+    characterBeforeCursor := codeView characterBeforeCursor.
+    characterBeforeCursor isNil ifTrue:[ "at begin of line" ^ self].
+
+    node isVariable ifTrue:[
+        nodeIsInTemporaries :=
+            node parent notNil 
+            and:[ node parent isSequence 
+            and:[ node parent temporaries notEmptyOrNil
+            and:[ node stop <= node parent temporaries last stop ]]].
+        nodeIsInTemporaries ifFalse:[
+            "/ cursor must be right after the variable
+            codeView characterPositionOfCursor == (node stop + 1) ifTrue:[
+                self codeCompletionForVariable:node into:actionBlock.
+            ]
+        ].
+        ^ self.
+    ].
+    node isLiteral ifTrue:[
+        "/ cursor must bew right after the literal
+        codeView characterPositionOfCursor == (node stop + 1) ifTrue:[
+            node value isSymbol ifTrue:[
+                self codeCompletionForLiteralSymbol:node into:actionBlock.
+                ^ self.
+            ].
+        ].
+        ^ self "/ huh - strings or what?
+    ].
+
+    checkedNode := node.
+    [checkedNode notNil] whileTrue:[
+        (codeView characterPositionOfCursor < checkedNode stop) ifTrue:[
+            self information:'Inside a message node'.
+            ^ self.
+        ].
+
+        checkedNode isMessage ifTrue:[
+            "/ completion in a message-send
+            self codeCompletionForMessage:checkedNode into:actionBlock.
+            ^ self
+        ].
+        checkedNode isMethod ifTrue:[
+            "/ completion in a method's selector pattern
+            self codeCompletionForMethodSpec:checkedNode into:actionBlock.
+            ^ self.
+        ].
+        checkedNode := checkedNode parent.
+    ].
+
+    self information:'Node is neither variable nor message.'.
+
+    "Modified: / 04-07-2006 / 18:48:26 / fm"
+    "Modified: / 16-09-2011 / 14:54:47 / cg"
 ! !
 
 !DoWhatIMeanSupport methodsFor:'code completion-helpers-old'!
@@ -3708,10 +3659,10 @@
 !DoWhatIMeanSupport class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DoWhatIMeanSupport.st,v 1.128 2013-08-29 18:28:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DoWhatIMeanSupport.st,v 1.129 2013-08-30 22:54:03 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libwidg2/DoWhatIMeanSupport.st,v 1.128 2013-08-29 18:28:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DoWhatIMeanSupport.st,v 1.129 2013-08-30 22:54:03 cg Exp $'
 ! !