Merge jv
authorMerge Script
Mon, 18 Jan 2016 06:55:36 +0100
branchjv
changeset 4935 127cb7e78672
parent 4932 f5eddfa983ab (current diff)
parent 4934 9b2c18bd9e9c (diff)
child 4937 3441e9190e9f
Merge
DoWhatIMeanSupport.st
--- a/DoWhatIMeanSupport.st	Sun Jan 17 06:49:48 2016 +0100
+++ b/DoWhatIMeanSupport.st	Mon Jan 18 06:55:36 2016 +0100
@@ -17,7 +17,8 @@
 	instanceVariableNames:'tree tokens languageOrNil classOrNil methodOrNil contextOrNil
 		instanceOrNil codeView rememberedScopeNodes rememberedNodes
 		codeAspect'
-	classVariableNames:'LastSource LastParseTree LastScanTokens LastChoices'
+	classVariableNames:'LastSource LastParseTree LastScanTokens LastChoices
+		LastCompletedSelectors'
 	poolDictionaries:''
 	category:'System-Support'
 !
@@ -1546,41 +1547,38 @@
                     actions := listOfActions.
                     title := titleWhenAsking.
                 ].
-            suggestions notEmptyOrNil ifTrue:[
-                actionBlock value:suggestions value:actions value:title.
-                ^ self.
-            ].
         ].
     ].
-
-    "/ try parsing the partial source (from beginning up to the cursor)
-    self
-        tryCodeCompletionWithSource:partialSource nodeInterval:interval
-        at:crsrPos mustBeExpression:(classOrNilArg isNil and:[methodOrNilArg isNil])
-        into:[:listOfSuggestions :listOfActions :titleWhenAsking |
-            suggestions := listOfSuggestions.
-            actions := listOfActions.
-            title := titleWhenAsking.
-            "/ suggestions1 size>100 ifTrue:[ self halt].
+    
+    suggestions isEmptyOrNil ifTrue:[
+        "/ try parsing the partial source (from beginning up to the cursor)
+        self
+            tryCodeCompletionWithSource:partialSource nodeInterval:interval
+            at:crsrPos mustBeExpression:(classOrNilArg isNil and:[methodOrNilArg isNil])
+            into:[:listOfSuggestions :listOfActions :titleWhenAsking |
+                suggestions := listOfSuggestions.
+                actions := listOfActions.
+                title := titleWhenAsking.
+                "/ suggestions1 size>100 ifTrue:[ self halt].
+            ].
+
+        suggestions isEmptyOrNil ifTrue:[
+            "/ then try parsing the whole source
+            self
+                tryCodeCompletionWithSource:source nodeInterval:interval
+                at:crsrPos mustBeExpression:false
+                into:[:listOfSuggestions :listOfActions :titleWhenAsking |
+                    suggestions := listOfSuggestions.
+                    actions := listOfActions.
+                    title := titleWhenAsking.
+                ].
+            suggestions isEmptyOrNil ifTrue:[
+                "/ nothing found
+                ^ self
+            ].    
         ].
-
-    suggestions notEmptyOrNil ifTrue:[
-        actionBlock value:suggestions value:actions value:title.
-        ^ self.
-    ].
-
-    "/ then try parsing the whole source
-    self
-        tryCodeCompletionWithSource:source nodeInterval:interval
-        at:crsrPos mustBeExpression:false
-        into:[:listOfSuggestions :listOfActions :titleWhenAsking |
-            suggestions := listOfSuggestions.
-            actions := listOfActions.
-            title := titleWhenAsking.
-        ].
-    suggestions notEmptyOrNil ifTrue:[
-        actionBlock value:suggestions value:actions value:title.
-    ].
+    ].    
+    actionBlock value:suggestions value:actions value:title.
 
     "Created: / 18-09-2013 / 15:25:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -1951,7 +1949,7 @@
                 node isVariable ifTrue:[
                     allMessagesSentToVariable := Set new.
                     rememberedNodes do:[:eachNode |
-                        eachNode allMessageNodes do:[:eachMessage |
+                        eachNode allMessageNodesDo:[:eachMessage |
                             eachMessage receiver isVariable ifTrue:[
                                 eachMessage receiver name = node name ifTrue:[
                                     eachMessage selector ~= selector ifTrue:[
@@ -2021,40 +2019,39 @@
     ifTrue:[
         |classesFromAssignmentsToReceiver otherMessagesToReceiver possibleClasses possibleClassesFromOtherSends|
 
-        classesFromAssignmentsToReceiver := tree allAssignmentNodes
-                                    collect:[:eachAssignmentNode |
-                                                |cls|
-
-                                                (nodeReceiver = eachAssignmentNode variable
-                                                    and:[ (cls := self classOfNode:eachAssignmentNode value) notNil ]
-                                                ) ifTrue:[
-                                                    cls
-                                                ] ifFalse:[
-                                                    nil
-                                                ]
-                                            ]
-                                    thenSelect:[:classOrNil | classOrNil notNil].
+        classesFromAssignmentsToReceiver := 
+            tree allAssignmentNodes
+                collect:[:eachAssignmentNode |
+                            |cls|
+                            (nodeReceiver = eachAssignmentNode variable
+                                and:[ (cls := self classOfNode:eachAssignmentNode value) notNil ]
+                            ) ifTrue:[ cls ] ifFalse:[ nil ]
+                        ]
+                thenSelect:[:classOrNil | classOrNil notNil].
 
         possibleClasses := classesFromAssignmentsToReceiver.
 
-        otherMessagesToReceiver := tree allMessageNodes
-                                    select:[:eachMessageNode |
-                                                nodeReceiver = eachMessageNode receiver
-                                                and:[ selector ~= eachMessageNode selector]]
-                                    thenCollect:[:eachNode | eachNode selector].
+        otherMessagesToReceiver := Set new.
+        tree allMessageNodesDo:[:eachMessageNode |
+            (nodeReceiver = eachMessageNode receiver
+                and:[ selector ~= eachMessageNode selector]
+            ) ifTrue:[   
+                otherMessagesToReceiver add:eachMessageNode selector
+            ]
+        ].
         otherMessagesToReceiver notEmpty ifTrue:[
-            otherMessagesToReceiver := otherMessagesToReceiver asSet.
             possibleClassesFromOtherSends :=
-                Smalltalk allClassesForWhich:
-                            [:cls |
-                                cls isLoaded
-                                and:[ otherMessagesToReceiver
-                                        conform:[:eachSelectorSent | cls includesSelector: "canUnderstand:" eachSelectorSent]]
-                            ].
+                Smalltalk 
+                    allClassesForWhich:
+                        [:cls |
+                            cls isLoaded
+                            and:[ otherMessagesToReceiver
+                                    conform:[:eachSelectorSent | cls includesSelector: "canUnderstand:" eachSelectorSent]]
+                        ].
             possibleClasses := possibleClasses , possibleClassesFromOtherSends.
         ].
 
-        "/ if the receiver is a class/classInstVar,
+        "/ if the receiver is a classVar/classInstVar,
         "/ include the class of its current value and UndefinedObject.
         "/ This helps to complete class methods and (lazy) initializer code.
         (classOrNil notNil) ifTrue:[
@@ -2077,14 +2074,11 @@
         ].
 
         (possibleClasses notEmpty and:[possibleClasses size < 15]) ifTrue:[
-            bestSelectors := Set new.
-            possibleClasses do:[:eachClass |
-                |bestSelectorsForClass|
-
-                bestSelectorsForClass := Parser findBest:30 selectorsFor:selector in:eachClass forCompletion:true.
-                bestSelectors addAll:bestSelectorsForClass.
-            ].
-            bestSelectors := bestSelectors asOrderedCollection.
+            bestSelectors :=
+                (possibleClasses 
+                    collectAll:[:eachClass |
+                        Parser findBest:30 selectorsFor:selector in:eachClass forCompletion:true.
+                    ] as:Set) asOrderedCollection.
 
             "/ if any of those is a prefix-keyword of the selector,
             "/ do not offer it (i.e. ifTrue:ifFalse: is already present, don't offer ifTrue:ifFalse: again.
@@ -2118,11 +2112,7 @@
                     ].
                     argNames notEmptyOrNil ifTrue: [
                         argNames := argNames asOrderedCollection sort.
-                        actionBlock
-                            value:argNames
-                            value:[:selIndex |
-                                  ]
-                            value: 'argument name hint'.
+                        actionBlock value:argNames value:[:selIndex | ] value: 'argument name hint'.
                         ^ self.
                     ]
                 ]
@@ -2154,7 +2144,7 @@
             "/ if its a unary message AND the parent is a unary or binary node, try again, sending the partial message
             "/ as a keyword to the parent node.
             "/ this is the case when after "foo binOp bar if", which should include ifTrue: in the result.
-            "/ transform from
+            "/ transform from (the incorrectly parsed)
             "/    foo == (shift if)
             "/        nonKWsel-msg(parent)
             "/     /         \
@@ -2299,14 +2289,20 @@
     allBest := (bestSelectors3 ? #()) , allBest.
     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 startsWith:selector]].
+
+    rememberedNodes notNil ifTrue:[
+        selectorsSentInCode := 
+            (rememberedNodes
+                select:[:node | node isMessage]
+                thenCollect:[:node | node selector]) asSet.
+        selectorsSentInCode remove:selector ifAbsent:[].
+    ].    
     selectorsSentInCode notNil ifTrue:[
         "/ the one's already sent in the code are moved to the top of the list.
         allBest := split value:allBest value:[:sel | selectorsSentInCode includes:sel].
     ].
-
-    "/ 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 startsWith:selector]].
-
 "/false ifTrue:[
 "/    srchClass notNil ifTrue:[
 "/        implClass := srchClass whichClassIncludesSelector:best.
@@ -3375,19 +3371,19 @@
 
     interval isEmpty ifTrue: [^ nil].
     languageOrNil notNil ifTrue:[
-	parserClass := languageOrNil parserClass.
+        parserClass := languageOrNil parserClass.
     ] ifFalse:[
-	classOrNil notNil ifTrue:[
-	    parserClass := classOrNil programmingLanguage parserClass.
-	]
+        classOrNil notNil ifTrue:[
+            parserClass := classOrNil programmingLanguage parserClass.
+        ]
     ].
     parserClass notNil ifTrue:[
-	"/ hack
-	parserClass == Parser ifTrue: [
-	    parserClass := RBParser.
-	].
+        "/ hack
+        parserClass == Parser ifTrue: [
+            parserClass := RBParser.
+        ].
     ] ifFalse:[
-	parserClass := RBParser.
+        parserClass := RBParser.
     ].
     parserClass isNil ifTrue: [^ nil].
 
@@ -3396,136 +3392,136 @@
 
     "/ LastSource := nil.
     source = LastSource ifTrue:[
-	tree := LastParseTree.
-	tokens := LastScanTokens.
+        tree := LastParseTree.
+        tokens := LastScanTokens.
     ] ifFalse:[
-	intersectingNodes := OrderedCollection new.
-	currentScopeNodes := IdentitySet new.
-
-	onErrorBlock :=
-	    [:str :err :nodesSoFar |
-		|nodes|
-
-		allowErrors ifTrue:[
-		    rememberedScopeNodes := currentScopeNodes.
-		    firstIntersectingNode notNil ifTrue:[
-			^ firstIntersectingNode
-		    ].
-		    nodesSoFar notNil ifTrue:[
-			nodes := nodesSoFar asOrderedCollection
-				    collect:[:nd | nd whichNodeIntersects:interval]
-				    thenSelect:[:nd | nd notNil ].
-			nodes size == 1 ifTrue:[
-			    ^ nodes first
-			].
-		    ]
-		].
-		nil
-	    ].
-
-	self debuggingCodeFor:#cg is:[
-	    Transcript show:'looking for: '; showCR:interval.
-	].
-
-	nodeGenerationHook :=
-	    [:node |
-		rememberedNodes add:node.
-
-		"/ 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 interpretation (especially: scope of variable) will be.
-		"/ therefore, we parse all, and return the found node at the end.
-		(node isMethod or:[node isBlock or:[node isSequence]]) ifTrue:[
-		    currentScopeNodes add:node.
-		] ifFalse:[
-		    self debuggingCodeFor:#cg is:[
-			Transcript show:node; show:' '; show:node start; show:'->'; showCR:node stop.
-		    ].
-
-		    (node intersectsInterval:interval) ifTrue:[
-			self debuggingCodeFor:#cg is:[
-			    Transcript showCR:'yes'.
-			].
-			intersectingNodes add:node.
-			firstIntersectingNode isNil ifTrue:[
-			    firstIntersectingNode := lastIntersectingNode := smallestIntersectingNode := node
-			] ifFalse:[
-			    |lenNode lenSmallest|
-
-			    lenNode := (node stop - node start).
-			    lenSmallest := (smallestIntersectingNode stop - smallestIntersectingNode start).
-			    lenNode < lenSmallest ifTrue:[
-				smallestIntersectingNode := node.
-			    ].
-			    node start > lastIntersectingNode start ifTrue:[
-				lastIntersectingNode := node.
-			    ].
-			].
-		    ].
-		].
-	    ].
-
-	"/ one of the big problems when using the RBParser here is
-	"/ that it behaves badly when a syntax error is encountered;
-	"/ for example, a node's parent is usually set AFTER the children are
-	"/ completely parsed (for example, a blockNode gets the parent-method only
-	"/ after parsing). Thus, when an error is encountered, we cannot walk
-	"/ the parent chain, and therefore will not see the outer locals/args of
-	"/ an inner scope (allVariablesOnScope returns only a partial set).
-	"/ A walkaround is to remember Method/Block nodes as created in the above node generation.
-	"/ The disadvantage of it is that we do not have correct scope information, until the nodes
-	"/ parent gets set eventually, this we might consider locals from sibling blocks.
-	"/ See rememberedScopeNodes handling above.
-	"/ Those other nodes are only remembered for failed parses;
-	"/ if the parse is ok, rememberedScopeNodes will be nil.
-
-	mustBeExpression ifFalse:[
-	    tree := parserClass
-			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
-	    tree notNil ifTrue:[
-		LastSource := source.
-		LastParseTree := tree.
-		LastScanTokens := tokens.
-	    ].
-	] ifFalse:[
-	    (tree isNil or:[firstIntersectingNode isNil]) ifTrue:[
-		"/ try as an expression
-		tree := parserClass
-			    parseExpression: source
-			    setup:[:p |
-				parser := p.
-				p rememberNodes:true.
-				p rememberTokens:true.
-				p nodeGenerationCallback:nodeGenerationHook
-			    ]
-			    onError: onErrorBlock.
-		parser notNil ifTrue:[ tokens := parser rememberedTokens ].
-	    ].
-	].
-	lastIntersectingNode notNil ifTrue:[
-	    self debuggingCodeFor:#cg is:[
-		Transcript show:'last: '; showCR:lastIntersectingNode.
-	    ].
-	    ^ lastIntersectingNode
-	].
-	"/ firstIntersectingNode notNil ifTrue:[ ^ firstIntersectingNode ].
+        intersectingNodes := OrderedCollection new.
+        currentScopeNodes := IdentitySet new.
+
+        onErrorBlock :=
+            [:str :err :nodesSoFar |
+                |nodes|
+
+                allowErrors ifTrue:[
+                    rememberedScopeNodes := currentScopeNodes.
+                    firstIntersectingNode notNil ifTrue:[
+                        ^ firstIntersectingNode
+                    ].
+                    nodesSoFar notNil ifTrue:[
+                        nodes := nodesSoFar asOrderedCollection
+                                    collect:[:nd | nd whichNodeIntersects:interval]
+                                    thenSelect:[:nd | nd notNil ].
+                        nodes size == 1 ifTrue:[
+                            ^ nodes first
+                        ].
+                    ]
+                ].
+                nil
+            ].
+
+        self debuggingCodeFor:#cg is:[
+            Transcript show:'looking for: '; showCR:interval.
+        ].
+
+        nodeGenerationHook :=
+            [:node |
+                rememberedNodes add:node.
+
+                "/ 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 interpretation (especially: scope of variable) will be.
+                "/ therefore, we parse all, and return the found node at the end.
+                (node isMethod or:[node isBlock or:[node isSequence]]) ifTrue:[
+                    currentScopeNodes add:node.
+                ] ifFalse:[
+                    self debuggingCodeFor:#cg is:[
+                        Transcript show:node; show:' '; show:node start; show:'->'; showCR:node stop.
+                    ].
+
+                    (node intersectsInterval:interval) ifTrue:[
+                        self debuggingCodeFor:#cg is:[
+                            Transcript showCR:'yes'.
+                        ].
+                        intersectingNodes add:node.
+                        firstIntersectingNode isNil ifTrue:[
+                            firstIntersectingNode := lastIntersectingNode := smallestIntersectingNode := node
+                        ] ifFalse:[
+                            |lenNode lenSmallest|
+
+                            lenNode := (node stop - node start).
+                            lenSmallest := (smallestIntersectingNode stop - smallestIntersectingNode start).
+                            lenNode < lenSmallest ifTrue:[
+                                smallestIntersectingNode := node.
+                            ].
+                            node start > lastIntersectingNode start ifTrue:[
+                                lastIntersectingNode := node.
+                            ].
+                        ].
+                    ].
+                ].
+            ].
+
+        "/ one of the big problems when using the RBParser here is
+        "/ that it behaves badly when a syntax error is encountered;
+        "/ for example, a node's parent is usually set AFTER the children are
+        "/ completely parsed (for example, a blockNode gets the parent-method only
+        "/ after parsing). Thus, when an error is encountered, we cannot walk
+        "/ the parent chain, and therefore will not see the outer locals/args of
+        "/ an inner scope (allVariablesOnScope returns only a partial set).
+        "/ A walkaround is to remember Method/Block nodes as created in the above node generation.
+        "/ The disadvantage of it is that we do not have correct scope information, until the node's
+        "/ parent gets set eventually, thus we might consider locals from sibling blocks.
+        "/ See rememberedScopeNodes handling above.
+        "/ Those other nodes are only remembered for failed parses;
+        "/ if the parse is ok, rememberedScopeNodes will be nil.
+
+        mustBeExpression ifFalse:[
+            tree := parserClass
+                        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
+            tree notNil ifTrue:[
+                LastSource := source.
+                LastParseTree := tree.
+                LastScanTokens := tokens.
+            ].
+        ] ifFalse:[
+            (tree isNil or:[firstIntersectingNode isNil]) ifTrue:[
+                "/ try as an expression
+                tree := parserClass
+                            parseExpression: source
+                            setup:[:p |
+                                parser := p.
+                                p rememberNodes:true.
+                                p rememberTokens:true.
+                                p nodeGenerationCallback:nodeGenerationHook
+                            ]
+                            onError: onErrorBlock.
+                parser notNil ifTrue:[ tokens := parser rememberedTokens ].
+            ].
+        ].
+        lastIntersectingNode notNil ifTrue:[
+            self debuggingCodeFor:#cg is:[
+                Transcript show:'last: '; showCR:lastIntersectingNode.
+            ].
+            ^ lastIntersectingNode
+        ].
+        "/ firstIntersectingNode notNil ifTrue:[ ^ firstIntersectingNode ].
     ].
 
     bestNode := self findNodeForInterval:interval inParseTree:tree.
     self debuggingCodeFor:#cg is:[
-	Transcript show:'best: '; showCR:bestNode.
+        Transcript show:'best: '; showCR:bestNode.
     ].
     ^ bestNode
 
@@ -3822,6 +3818,8 @@
         nodeParent := node parent.
     ].
 
+    "/ move outward, until we find a message-send node,
+    "/ or the method's selector pattern node.
     checkedNode := node.
     [checkedNode notNil] whileTrue:[
         (characterPositionOfCursor < (checkedNode stop ? source size)) ifTrue:[
@@ -4164,7 +4162,7 @@
     findBest := [:node :selector |
         |srchClass bestSelectors bestPrefixes|
 
-        codeView topView withCursor:(Cursor questionMark) do:[
+        codeView withCursor:(Cursor questionMark) do:[
             srchClass := self classOfNode:node receiver.
             srchClass notNil ifTrue:[
                 bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.