#FEATURE by cg
authorClaus Gittinger <cg@exept.de>
Wed, 27 Apr 2016 15:01:40 +0200
changeset 5031 ea94aa3cb834
parent 5029 5f1d1837cbdf
child 5032 27a4f57eae4f
child 5033 743f882894d9
#FEATURE by cg class: DoWhatIMeanSupport changed: #codeCompletionForLiteralSymbol:element:considerAll:into: #codeCompletionForMessage:into:
DoWhatIMeanSupport.st
--- a/DoWhatIMeanSupport.st	Wed Apr 20 23:17:26 2016 +0200
+++ b/DoWhatIMeanSupport.st	Wed Apr 27 15:01:40 2016 +0200
@@ -1834,65 +1834,74 @@
     start := (nodeOrNil ? tokenOrNil) start.
     stop := (nodeOrNil ? tokenOrNil) stop.
     (codeView characterAtCharacterPosition:stop) == $' ifTrue:[
-	^ self.
+        ^ self.
     ].
 
     sym := (nodeOrNil ? tokenOrNil) value.
     possibleCompletions := Set new.
 
     addSymbol :=
-	[:aSymbol |
-	    (aSymbol startsWith:sym) ifTrue:[
-		(aSymbol = sym) ifFalse:[
-		    possibleCompletions add:aSymbol
-		].
-	    ].
-	].
+        [:aSymbol |
+            (aSymbol startsWith:sym) ifTrue:[
+                (aSymbol = sym) ifFalse:[
+                    possibleCompletions add:aSymbol
+                ].
+            ].
+        ].
 
     (nodeOrNil notNil
     and:[ (parent := nodeOrNil parent) notNil
     and:[ parent isMessage ]]) ifTrue:[
-	parentSelector := parent selector.
-	( #( perform: perform:ifNotUnderstood: ) includes: parentSelector) ifTrue:[
-	    symbolSelectorClass := self classOfNode:parent receiver.
-	].
-	( #( #'onChangeSend:' ) includes: parentSelector) ifTrue:[
-	    "/ assume that send-target will be self.
-	    (methodOrNil notNil and:[ methodOrNil selector notNil and:[ methodOrNil selector isUnarySelector ]]) ifTrue:[
-		addSymbol value:(methodOrNil selector,'Changed').
-	    ].
-	    symbolSelectorClass := classOrNil.
-	].
-	( #( #'onChangeSend:to:' ) includes: parentSelector) ifTrue:[
-	    symbolSelectorClass := self classOfNode:parent arguments second.
-	].
-
-	symbolSelectorClass notNil ifTrue:[
-	    symbolSelectorClass withAllSuperclassesDo:[:cls |
-		cls ~~ Object ifTrue:[
-		    cls ~~ Model ifTrue:[
-			cls methodDictionary keysDo:addSymbol.
-		    ]
-		]
-	    ]
-	].
+        parentSelector := parent selector.
+        ( #( perform: perform:ifNotUnderstood: ) includes: parentSelector) ifTrue:[
+            symbolSelectorClass := self classOfNode:parent receiver.
+        ].
+        ( #( #'onChangeSend:' ) includes: parentSelector) ifTrue:[
+            "/ assume that send-target will be self.
+            (methodOrNil notNil and:[ methodOrNil selector notNil and:[ methodOrNil selector isUnarySelector ]]) ifTrue:[
+                addSymbol value:(methodOrNil selector,'Changed').
+            ].
+            symbolSelectorClass := classOrNil.
+        ].
+        ( #( #'onChangeSend:to:' ) includes: parentSelector) ifTrue:[
+            symbolSelectorClass := self classOfNode:parent arguments second.
+        ].
+
+        symbolSelectorClass notNil ifTrue:[
+            symbolSelectorClass withAllSuperclassesDo:[:cls |
+                cls ~~ Object ifTrue:[
+                    cls ~~ Model ifTrue:[
+                        cls methodDictionary keysDo:addSymbol.
+                    ]
+                ]
+            ]
+        ].
     ].
 
     (considerAll or:[classOrNil isNil]) ifTrue:[
-	Smalltalk allClassesDo:[:cls |
-	    cls theNonMetaclass methodDictionary keys do:addSymbol.
-	    cls theMetaclass methodDictionary keys do:addSymbol.
-	].
-
-	"/ Symbol allInstancesDo:addSymbol.
+        Smalltalk allClassesDo:[:cls |
+            cls theNonMetaclass methodDictionary keys do:addSymbol.
+            cls theMetaclass methodDictionary keys do:addSymbol.
+        ].
+
+        "/ Symbol allInstancesDo:addSymbol.
     ] ifFalse:[
-	Smalltalk allClassesInCategory:classOrNil do:[:cls |
-	    cls theNonMetaclass instAndClassMethodsDo:[:mthd |
-		mthd usedSymbols do:addSymbol
-	    ]
-	].
+        Smalltalk allClassesInCategory:classOrNil do:[:cls |
+            cls theNonMetaclass instAndClassMethodsDo:[:mthd |
+                mthd usedSymbols do:addSymbol
+            ]
+        ].
     ].
 
+    "/ add symbolic literals (especially for spec methods)
+    classOrNil notNil ifTrue:[
+        classOrNil theMetaclass instAndClassMethodsDo:[:mthd |
+            mthd literalsDo:[:lit |
+                lit isSymbol ifTrue:[ addSymbol value: lit ]
+            ].    
+        ].    
+    ].
+    
     possibleCompletions := possibleCompletions asOrderedCollection sort.
 
     longest := possibleCompletions longestCommonPrefix.
@@ -1900,34 +1909,34 @@
     possibleCompletions addFirst: longest.
 
     editAction :=
-	[:chosenIndex |
-	    |chosen oldSym oldLen newLen|
-
-	    chosen := possibleCompletions at:chosenIndex.
-	    chosen notNil ifTrue:[
-		(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
-		].
-	    ]
-	].
+        [:chosenIndex |
+            |chosen oldSym oldLen newLen|
+
+            chosen := possibleCompletions at:chosenIndex.
+            chosen notNil ifTrue:[
+                (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'.
 
@@ -1936,6 +1945,8 @@
 !
 
 codeCompletionForMessage:node into:actionBlock
+    "find good completions for a message selector in a message-send node"
+    
     |selector lcSelector srchClass implClass
      bestSelectors selector2 bestSelectors2 bestSelectors3 allBest best info numArgs
      newParts nSelParts oldLen newLen selectorParts
@@ -1957,10 +1968,12 @@
                     allMessagesSentToVariable := Set new.
                     rememberedNodes do:[:eachNode |
                         eachNode allMessageNodesDo:[:eachMessage |
-                            eachMessage receiver isVariable ifTrue:[
-                                eachMessage receiver name = node name ifTrue:[
-                                    eachMessage selector ~= selector ifTrue:[
-                                        allMessagesSentToVariable add:eachMessage selector
+                            |msgReceiver msgSelector|
+                            
+                            (msgReceiver := eachMessage receiver) isVariable ifTrue:[
+                                msgReceiver name = node name ifTrue:[
+                                    (msgSelector := eachMessage selector) ~= selector ifTrue:[
+                                        allMessagesSentToVariable add:msgSelector
                                     ]
                                 ]
                             ]
@@ -2050,12 +2063,11 @@
         otherMessagesToReceiver notEmpty ifTrue:[
             possibleClassesFromOtherSends :=
                 Smalltalk 
-                    allClassesForWhich:
-                        [:cls |
-                            cls isLoaded
-                            and:[ otherMessagesToReceiver
-                                    conform:[:eachSelectorSent | cls includesSelector: "canUnderstand:" eachSelectorSent]]
-                        ].
+                    allClassesForWhich:[:cls |
+                        cls isLoaded
+                        and:[ otherMessagesToReceiver
+                                conform:[:eachSelectorSent | cls includesSelector: "canUnderstand:" eachSelectorSent]]
+                    ].
             possibleClasses := possibleClasses , possibleClassesFromOtherSends.
         ].
 
@@ -2286,10 +2298,14 @@
             ].
             all
         ].
+        
     "/ sort: prefixes first.
     selector2 notNil ifTrue:[
-        allBest := split value:allBest value:[:sel | (sel asLowercase startsWith:lcSelector) 
-                                                     or:[sel startsWith:selector2]].
+        allBest := split 
+                    value:allBest 
+                    value:[:sel | 
+                            (sel asLowercase startsWith:lcSelector) 
+                            or:[sel startsWith:selector2]].
     ].
 
     "/ if receiver is super, always include the method's own selector
@@ -2314,7 +2330,9 @@
     allBest isEmptyOrNil ifTrue:[ ^ self ].
 
     "/ the one's which are a prefix are moved towards the top of the list
-    allBest := split value:allBest value:[:sel | sel notNil and:[sel asLowercase startsWith:lcSelector]].
+    allBest := split 
+                    value:allBest 
+                    value:[:sel | sel notNil and:[sel asLowercase startsWith:lcSelector]].
 
     rememberedNodes notNil ifTrue:[
         selectorsSentInCode :=