DoWhatIMeanSupport.st
changeset 5505 485ae56088f2
parent 5504 dbae466ee892
child 5508 6215fe395e12
--- a/DoWhatIMeanSupport.st	Sun Feb 26 12:10:25 2017 +0100
+++ b/DoWhatIMeanSupport.st	Sun Feb 26 14:26:05 2017 +0100
@@ -1,8 +1,6 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -16,20 +14,20 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#DoWhatIMeanSupport
-        instanceVariableNames:'tree tokens languageOrNil classOrNil methodOrNil contextOrNil
-                instanceOrNil codeView rememberedScopeNodes rememberedNodes
-                codeAspect'
-        classVariableNames:'LastSource LastParseTree LastScanTokens LastChoices
-                LastCompletedSelectors Verbose'
-        poolDictionaries:''
-        category:'System-Support'
+	instanceVariableNames:'tree tokens languageOrNil classOrNil methodOrNil contextOrNil
+		instanceOrNil codeView rememberedScopeNodes rememberedNodes
+		codeAspect'
+	classVariableNames:'LastSource LastParseTree LastScanTokens LastChoices
+		LastCompletedSelectors Verbose'
+	poolDictionaries:''
+	category:'System-Support'
 !
 
 Array variableSubclass:#InputCompletionResult
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:DoWhatIMeanSupport
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:DoWhatIMeanSupport
 !
 
 !DoWhatIMeanSupport class methodsFor:'documentation'!
@@ -37,7 +35,7 @@
 copyright
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -59,11 +57,11 @@
     however, they are only needed for programmers, and some of the stuff is useful in multiple
     places.
     Therefore it is:
-        1) not needed for standalone executables
-        2) published here to avoid multiple implementations
+	1) not needed for standalone executables
+	2) published here to avoid multiple implementations
 
     [author:]
-        Claus Gittinger (cg@exept.de)
+	Claus Gittinger (cg@exept.de)
 
 "
 ! !
@@ -112,7 +110,7 @@
      This is not yet done, sigh"
 
     ^ self
-        codeCompletionForLanguage: nil class:classOrNil context:contextOrNil codeView:codeView
+	codeCompletionForLanguage: nil class:classOrNil context:contextOrNil codeView:codeView
 
     "Modified: / 18-09-2013 / 13:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -125,9 +123,9 @@
      This is not yet done, sigh"
 
     ^ self new
-        codeCompletionForMethod:methodOrNil orClass:classOrNil
-        context:contextOrNil
-        codeView:codeView into:actionBlock
+	codeCompletionForMethod:methodOrNil orClass:classOrNil
+	context:contextOrNil
+	codeView:codeView into:actionBlock
 ! !
 
 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
@@ -205,7 +203,7 @@
     "if mustBeMethod is true, do not try a regular expression (as in a workspace)."
 
     ^ self new
-        findNodeForInterval:interval in:source allowErrors:allowErrors mustBeMethod:mustBeMethod
+	findNodeForInterval:interval in:source allowErrors:allowErrors mustBeMethod:mustBeMethod
 !
 
 findNodeForInterval:interval inParseTree:parseTree
@@ -251,7 +249,7 @@
 classCategoryCompletion:aPartialCategory inEnvironment:anEnvironment
     "given a partial class category name, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching categories"
+		2nd: collection consisting of matching categories"
 
     |matches best lcName|
 
@@ -259,31 +257,31 @@
 
     "/ search for exact match
     anEnvironment allClassesDo:[:aClass |
-        |category|
-
-        category := aClass category.
-        (category notNil and:[category startsWith:aPartialCategory]) ifTrue:[
-            matches add:category
-        ]
+	|category|
+
+	category := aClass category.
+	(category notNil and:[category startsWith:aPartialCategory]) ifTrue:[
+	    matches add:category
+	]
     ].
     matches isEmpty ifTrue:[
-        "/ search for case-ignoring match
-        lcName := aPartialCategory asLowercase.
-        anEnvironment allClassesDo:[:aClass |
-            |category|
-
-            category := aClass category.
-            (category notNil and:[category asLowercase startsWith:lcName]) ifTrue:[
-                matches add:category
-            ].
-        ].
+	"/ search for case-ignoring match
+	lcName := aPartialCategory asLowercase.
+	anEnvironment allClassesDo:[:aClass |
+	    |category|
+
+	    category := aClass category.
+	    (category notNil and:[category asLowercase startsWith:lcName]) ifTrue:[
+		matches add:category
+	    ].
+	].
     ].
 
     matches isEmpty ifTrue:[
-        ^ Array with:aPartialCategory with:(Array with:aPartialCategory)
+	^ Array with:aPartialCategory with:(Array with:aPartialCategory)
     ].
     matches size == 1 ifTrue:[
-        ^ Array with:matches first with:(matches asArray)
+	^ Array with:matches first with:(matches asArray)
     ].
     matches := matches asSortedCollection.
     best := matches longestCommonPrefix.
@@ -498,12 +496,12 @@
 classnameCompletion:aPartialClassName inEnvironment:anEnvironment
     "given a partial classname, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching names"
+		2nd: collection consisting of matching names"
 
     ^ self
-        classnameCompletion:aPartialClassName
-        filter:[:cls | true]
-        inEnvironment:anEnvironment
+	classnameCompletion:aPartialClassName
+	filter:[:cls | true]
+	inEnvironment:anEnvironment
 
     "
      self classnameCompletion:'Arr'   inEnvironment:Smalltalk
@@ -520,19 +518,19 @@
     "this block can be used in a dialog to perform className completion"
 
     ^ [:contents :field  |
-          |s what m|
-
-          s := contents withoutSpaces.
-          field topView withCursor:(Cursor questionMark) do:[
-              what := self perform:completionSelector with:s with:Smalltalk.
-          ].
-
-          field contents:(what first).
-          (what at:2) size ~~ 1 ifTrue:[
-              UserPreferences current beepInEditor ifTrue:[
-                field device beep
-              ]
-          ]
+	  |s what m|
+
+	  s := contents withoutSpaces.
+	  field topView withCursor:(Cursor questionMark) do:[
+	      what := self perform:completionSelector with:s with:Smalltalk.
+	  ].
+
+	  field contents:(what first).
+	  (what at:2) size ~~ 1 ifTrue:[
+	      UserPreferences current beepInEditor ifTrue:[
+		field device beep
+	      ]
+	  ]
       ].
 
     "Created: / 10-08-2006 / 13:21:37 / cg"
@@ -541,7 +539,7 @@
 globalNameCompletion:aPartialGlobalName inEnvironment:anEnvironment
     "given a partial globalName, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching names"
+		2nd: collection consisting of matching names"
 
     ^ self globalNameCompletion:aPartialGlobalName inEnvironment:anEnvironment match:true
 
@@ -558,60 +556,60 @@
 globalNameCompletion:aPartialGlobalName inEnvironment:anEnvironment match:doMatch
     "given a partial globalName, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching names"
+		2nd: collection consisting of matching names"
 
     |searchName matches ignCaseMatches best isMatchString|
 
     searchName := aPartialGlobalName.
     searchName isEmpty ifTrue:[
-        ^ Array with:searchName with:#()
+	^ Array with:searchName with:#()
     ].
 
     (searchName at:1) isLowercase ifTrue:[
-        searchName := searchName copy asUppercaseFirst
+	searchName := searchName copy asUppercaseFirst
     ].
 
     isMatchString := doMatch and:[ searchName includesMatchCharacters ].
     matches := OrderedCollection new.
     ignCaseMatches := OrderedCollection new.
     anEnvironment keysDo:[:aGlobalName |
-        | addIt|
-
-        isMatchString ifTrue:[
-            addIt := searchName match:aGlobalName
-        ] ifFalse:[
-            addIt := aGlobalName startsWith:searchName
-        ].
-        addIt ifTrue:[
-            matches add:aGlobalName
-        ] ifFalse:[
-            "/ try ignoring case
-            isMatchString ifTrue:[
-                addIt := searchName match:aGlobalName caseSensitive:false
-            ] ifFalse:[
-                addIt := aGlobalName asLowercase startsWith:searchName asLowercase
-            ].
-            addIt ifTrue:[
-                ignCaseMatches add:aGlobalName
-            ]
-        ]
+	| addIt|
+
+	isMatchString ifTrue:[
+	    addIt := searchName match:aGlobalName
+	] ifFalse:[
+	    addIt := aGlobalName startsWith:searchName
+	].
+	addIt ifTrue:[
+	    matches add:aGlobalName
+	] ifFalse:[
+	    "/ try ignoring case
+	    isMatchString ifTrue:[
+		addIt := searchName match:aGlobalName caseSensitive:false
+	    ] ifFalse:[
+		addIt := aGlobalName asLowercase startsWith:searchName asLowercase
+	    ].
+	    addIt ifTrue:[
+		ignCaseMatches add:aGlobalName
+	    ]
+	]
     ].
 
     matches isEmpty ifTrue:[
-        matches := ignCaseMatches
+	matches := ignCaseMatches
     ].
 
     matches isEmpty ifTrue:[
-        ^ Array with:searchName with:(Array with:searchName)
+	^ Array with:searchName with:(Array with:searchName)
     ].
     matches size == 1 ifTrue:[
-        ^ Array with:matches first with:(matches asArray)
+	^ Array with:matches first with:(matches asArray)
     ].
     matches := matches asSortedCollection.
     isMatchString ifTrue:[
-        best := searchName.
+	best := searchName.
     ] ifFalse:[
-        best := matches longestCommonPrefix.
+	best := matches longestCommonPrefix.
     ].
     ^ Array with:best with:matches asArray
 
@@ -628,7 +626,7 @@
 methodProtocolCompletion:aPartialProtocolName inEnvironment:anEnvironment
     "given a partial method protocol name, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching protocols"
+		2nd: collection consisting of matching protocols"
 
     |matches best lcName|
 
@@ -636,31 +634,31 @@
 
     "/ search for exact match
     anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-        |protocol|
-
-        protocol := eachMethod category.
-        (protocol notNil and:[protocol startsWith:aPartialProtocolName]) ifTrue:[
-            matches add:protocol
-        ].
+	|protocol|
+
+	protocol := eachMethod category.
+	(protocol notNil and:[protocol startsWith:aPartialProtocolName]) ifTrue:[
+	    matches add:protocol
+	].
     ].
     matches isEmpty ifTrue:[
-        "/ search for case-ignoring match
-        lcName := aPartialProtocolName asLowercase.
-        anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-            |protocol|
-
-            protocol := eachMethod category.
-            (protocol notNil and:[protocol asLowercase startsWith:lcName]) ifTrue:[
-                matches add:protocol
-            ].
-        ].
+	"/ search for case-ignoring match
+	lcName := aPartialProtocolName asLowercase.
+	anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
+	    |protocol|
+
+	    protocol := eachMethod category.
+	    (protocol notNil and:[protocol asLowercase startsWith:lcName]) ifTrue:[
+		matches add:protocol
+	    ].
+	].
     ].
 
     matches isEmpty ifTrue:[
-        ^ Array with:aPartialProtocolName with:(Array with:aPartialProtocolName)
+	^ Array with:aPartialProtocolName with:(Array with:aPartialProtocolName)
     ].
     matches size == 1 ifTrue:[
-        ^ Array with:matches first with:(matches asArray)
+	^ Array with:matches first with:(matches asArray)
     ].
     matches := matches asSortedCollection.
     best := matches longestCommonPrefix.
@@ -679,12 +677,12 @@
 nameSpaceCompletion:aPartialClassName inEnvironment:anEnvironment
     "given a partial name, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching names"
+		2nd: collection consisting of matching names"
 
     ^ self
-        classnameCompletion:aPartialClassName
-        filter:[:cls | cls isNameSpace]
-        inEnvironment:anEnvironment
+	classnameCompletion:aPartialClassName
+	filter:[:cls | cls isNameSpace]
+	inEnvironment:anEnvironment
 
     "
      DoWhatIMeanSupport nameSpaceCompletion:'To'  inEnvironment:Smalltalk
@@ -745,12 +743,12 @@
 poolnameCompletion:aPartialClassName inEnvironment:anEnvironment
     "given a partial poolname, return an array consisting of
      2 entries: 1st: the best (longest) match
-                2nd: collection consisting of matching names"
+		2nd: collection consisting of matching names"
 
     ^ self
-        classnameCompletion:aPartialClassName
-        filter:[:cls | cls isSharedPool]
-        inEnvironment:anEnvironment
+	classnameCompletion:aPartialClassName
+	filter:[:cls | cls isSharedPool]
+	inEnvironment:anEnvironment
 
     "
      self poolnameCompletion:'Win' inEnvironment:Smalltalk
@@ -762,7 +760,7 @@
 resourceCompletion:aPartialResourceName inEnvironment:anEnvironment match:doMatch ignoreCase:ignoreCase
     "given a partial resource name, return an array consisting of
      2 entries: 1st: the longest match
-                2nd: collection consisting of matching defined resources"
+		2nd: collection consisting of matching defined resources"
 
     |matches best lcSym isMatch|
 
@@ -771,41 +769,41 @@
     isMatch := doMatch and:[aPartialResourceName includesMatchCharacters].
 
     anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-        eachMethod hasResource ifTrue:[
-            eachMethod resources keysDo:[:eachResourceName |
-                (isMatch
-                    ifTrue:[ (aPartialResourceName match:eachResourceName caseSensitive:ignoreCase not) ]
-                    ifFalse:[ ignoreCase
-                                ifTrue:[ (eachResourceName asLowercase startsWith:aPartialResourceName asLowercase) ]
-                                ifFalse:[ (eachResourceName startsWith:aPartialResourceName) ] ]
-                ) ifTrue:[
-                    matches add:eachResourceName
-                ].
-            ].
-        ].
+	eachMethod hasResource ifTrue:[
+	    eachMethod resources keysDo:[:eachResourceName |
+		(isMatch
+		    ifTrue:[ (aPartialResourceName match:eachResourceName caseSensitive:ignoreCase not) ]
+		    ifFalse:[ ignoreCase
+				ifTrue:[ (eachResourceName asLowercase startsWith:aPartialResourceName asLowercase) ]
+				ifFalse:[ (eachResourceName startsWith:aPartialResourceName) ] ]
+		) ifTrue:[
+		    matches add:eachResourceName
+		].
+	    ].
+	].
     ].
     (matches isEmpty and:[ignoreCase not]) ifTrue:[
-        "/ search for case-ignoring match
-        lcSym := aPartialResourceName asLowercase.
-        anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-            eachMethod hasResource ifTrue:[
-                eachMethod resources keysDo:[:eachResourceName |
-                    (isMatch
-                        ifTrue:[ (aPartialResourceName match:eachResourceName caseSensitive:false) ]
-                        ifFalse:[ (eachResourceName asLowercase startsWith:lcSym) ])
-                     ifTrue:[
-                        matches add:eachResourceName
-                    ].
-                ].
-            ].
-        ].
+	"/ search for case-ignoring match
+	lcSym := aPartialResourceName asLowercase.
+	anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
+	    eachMethod hasResource ifTrue:[
+		eachMethod resources keysDo:[:eachResourceName |
+		    (isMatch
+			ifTrue:[ (aPartialResourceName match:eachResourceName caseSensitive:false) ]
+			ifFalse:[ (eachResourceName asLowercase startsWith:lcSym) ])
+		     ifTrue:[
+			matches add:eachResourceName
+		    ].
+		].
+	    ].
+	].
     ].
 
     matches isEmpty ifTrue:[
-        ^ Array with:aPartialResourceName with:#()
+	^ Array with:aPartialResourceName with:#()
     ].
     matches size == 1 ifTrue:[
-        ^ Array with:matches first with:(matches asArray)
+	^ Array with:matches first with:(matches asArray)
     ].
     matches := matches asSortedCollection.
     best := matches longestCommonPrefix.
@@ -824,7 +822,7 @@
 selectorCompletion:aPartialSymbolName inEnvironment:anEnvironment
     "given a partial selector, return an array consisting of
      2 entries: 1st: the longest match
-                2nd: collection consisting of matching implemented selectors"
+		2nd: collection consisting of matching implemented selectors"
 
     ^ self selectorCompletion:aPartialSymbolName inEnvironment:anEnvironment match:false
 !
@@ -832,13 +830,13 @@
 selectorCompletion:aPartialSymbolName inEnvironment:anEnvironment match:doMatch
     "given a partial selector, return an array consisting of
      2 entries: 1st: the longest match
-                2nd: collection consisting of matching implemented selectors"
+		2nd: collection consisting of matching implemented selectors"
 
     ^ self
-        selectorCompletion:aPartialSymbolName
-        inEnvironment:anEnvironment
-        match:doMatch
-        ignoreCase:false
+	selectorCompletion:aPartialSymbolName
+	inEnvironment:anEnvironment
+	match:doMatch
+	ignoreCase:false
 
     "
      DoWhatIMeanSupport selectorCompletion:'inst*p' inEnvironment:Smalltalk match:true
@@ -855,7 +853,7 @@
 selectorCompletion:aPartialSymbolName inEnvironment:anEnvironment match:doMatch ignoreCase:ignoreCase
     "given a partial selector, return an array consisting of
      2 entries: 1st: the longest match
-                2nd: collection consisting of matching implemented selectors"
+		2nd: collection consisting of matching implemented selectors"
 
     |matches best lcSym isMatch|
 
@@ -864,33 +862,33 @@
     isMatch := doMatch and:[aPartialSymbolName includesMatchCharacters].
 
     anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-        (isMatch
-            ifTrue:[ (aPartialSymbolName match:eachSelector caseSensitive:ignoreCase not) ]
-            ifFalse:[ ignoreCase
-                        ifTrue:[ (eachSelector asLowercase startsWith:aPartialSymbolName asLowercase) ]
-                        ifFalse:[ (eachSelector startsWith:aPartialSymbolName) ] ])
-         ifTrue:[
-            matches add:eachSelector
-        ].
+	(isMatch
+	    ifTrue:[ (aPartialSymbolName match:eachSelector caseSensitive:ignoreCase not) ]
+	    ifFalse:[ ignoreCase
+			ifTrue:[ (eachSelector asLowercase startsWith:aPartialSymbolName asLowercase) ]
+			ifFalse:[ (eachSelector startsWith:aPartialSymbolName) ] ])
+	 ifTrue:[
+	    matches add:eachSelector
+	].
     ].
     (matches isEmpty and:[ignoreCase not]) ifTrue:[
-        "/ search for case-ignoring match
-        lcSym := aPartialSymbolName asLowercase.
-        anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-            (isMatch
-                ifTrue:[ (aPartialSymbolName match:eachSelector caseSensitive:false) ]
-                ifFalse:[ (eachSelector asLowercase startsWith:lcSym) ])
-             ifTrue:[
-                matches add:eachSelector
-            ].
-        ].
+	"/ search for case-ignoring match
+	lcSym := aPartialSymbolName asLowercase.
+	anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
+	    (isMatch
+		ifTrue:[ (aPartialSymbolName match:eachSelector caseSensitive:false) ]
+		ifFalse:[ (eachSelector asLowercase startsWith:lcSym) ])
+	     ifTrue:[
+		matches add:eachSelector
+	    ].
+	].
     ].
 
     matches isEmpty ifTrue:[
-        ^ Array with:aPartialSymbolName with:#() "/ (Array with:aPartialSymbolName)
+	^ Array with:aPartialSymbolName with:#() "/ (Array with:aPartialSymbolName)
     ].
     matches size == 1 ifTrue:[
-        ^ Array with:matches first with:(matches asArray)
+	^ Array with:matches first with:(matches asArray)
     ].
     matches := matches asSortedCollection.
     best := matches longestCommonPrefix.
@@ -1106,47 +1104,47 @@
 
     "/ suffix change ?
     lastOldWOSuffix = lastNewWOSuffix ifTrue:[
-        lastOldName asFilename suffix ~= lastNewName asFilename suffix ifTrue:[
-            ^ (oldName asFilename withSuffix:(lastNewName asFilename suffix)) pathName
-        ].
+	lastOldName asFilename suffix ~= lastNewName asFilename suffix ifTrue:[
+	    ^ (oldName asFilename withSuffix:(lastNewName asFilename suffix)) pathName
+	].
     ].
 
     default := self goodRenameDefaultFor:oldWOSuffix lastOld:lastOldWOSuffix lastNew:lastNewWOSuffix.
     default notNil ifTrue:[
-        lastOldRest := lastOldName copyFrom:lastOldWOSuffix size + 1.
-        lastNewRest := lastNewName copyFrom:lastNewWOSuffix size + 1.
-        oldRest := oldName copyFrom:oldWOSuffix size + 1.
-
-        ^ default , lastNewRest
+	lastOldRest := lastOldName copyFrom:lastOldWOSuffix size + 1.
+	lastNewRest := lastNewName copyFrom:lastNewWOSuffix size + 1.
+	oldRest := oldName copyFrom:oldWOSuffix size + 1.
+
+	^ default , lastNewRest
     ].
 
     prefix := lastOldWOSuffix commonPrefixWith:oldWOSuffix.
     (lastNewWOSuffix startsWith:prefix) ifTrue:[
-        lastOldRest := lastOldWOSuffix copyFrom:prefix size + 1.
-        lastNewRest := lastNewWOSuffix copyFrom:prefix size + 1.
-        oldRest := oldWOSuffix copyFrom:prefix size + 1.
-
-        (lastNewRest endsWith:lastOldRest) ifTrue:[
-            t := lastNewRest copyButLast:lastOldRest size.
-            ^ ((prefix , t , oldRest) asFilename withSuffix:oldName asFilename suffix) name
-        ].
+	lastOldRest := lastOldWOSuffix copyFrom:prefix size + 1.
+	lastNewRest := lastNewWOSuffix copyFrom:prefix size + 1.
+	oldRest := oldWOSuffix copyFrom:prefix size + 1.
+
+	(lastNewRest endsWith:lastOldRest) ifTrue:[
+	    t := lastNewRest copyButLast:lastOldRest size.
+	    ^ ((prefix , t , oldRest) asFilename withSuffix:oldName asFilename suffix) name
+	].
     ].
 
     suffix := lastOldWOSuffix commonSuffixWith:lastNewWOSuffix.
     suffix size > 0 ifTrue:[
-        "/ last change changed something at the beginning
-        prefix := oldWOSuffix commonPrefixWith:lastOldWOSuffix.
-        prefix size > 0 ifTrue:[
-            "/ this name starts with the same characters
-            lastRemoved := lastOldWOSuffix copyButLast:suffix size.
-            lastInserted := lastNewWOSuffix copyButLast:suffix size.
-            (lastRemoved startsWith:lastInserted) ifTrue:[
-                oldWOSuffix size >= lastInserted size ifTrue:[
-                    ^ (oldWOSuffix copyTo:lastInserted size) , (oldName copyFrom:lastRemoved size + 1)
-                ]
-            ].
-            ^ lastInserted , (oldName copyFrom:lastRemoved size + 1)
-        ].
+	"/ last change changed something at the beginning
+	prefix := oldWOSuffix commonPrefixWith:lastOldWOSuffix.
+	prefix size > 0 ifTrue:[
+	    "/ this name starts with the same characters
+	    lastRemoved := lastOldWOSuffix copyButLast:suffix size.
+	    lastInserted := lastNewWOSuffix copyButLast:suffix size.
+	    (lastRemoved startsWith:lastInserted) ifTrue:[
+		oldWOSuffix size >= lastInserted size ifTrue:[
+		    ^ (oldWOSuffix copyTo:lastInserted size) , (oldName copyFrom:lastRemoved size + 1)
+		]
+	    ].
+	    ^ lastInserted , (oldName copyFrom:lastRemoved size + 1)
+	].
     ].
 
     ^ nil
@@ -1207,28 +1205,28 @@
 
     lang := UserPreferences current language.
     lang == #de ifTrue:[
-        ^ #(
-               '1234567890-'
-               '*qwertzuiop'
-               '**asdfghjkl:'
-               '***yxcvbnm'
-        ).
+	^ #(
+	       '1234567890-'
+	       '*qwertzuiop'
+	       '**asdfghjkl:'
+	       '***yxcvbnm'
+	).
     ].
 
     lang == #fr ifTrue:[
-        ^ #(
-               '1234567890'
-               '*azertyuiop'
-               '**qsdfghjklm'
-               '***wxcvbn,'
-        ).
+	^ #(
+	       '1234567890'
+	       '*azertyuiop'
+	       '**qsdfghjklm'
+	       '***wxcvbn,'
+	).
     ].
 
     ^ #(
-           '1234567890-'
-           '*qwertyuiop'
-           '**asdfghjkl:'
-           '***zxcvbnm'
+	   '1234567890-'
+	   '*qwertyuiop'
+	   '**asdfghjkl:'
+	   '***zxcvbnm'
     ).
 
     "
@@ -1738,7 +1736,7 @@
 codeCompletionForMethod:methodOrNilArg orClass:classOrNilArg context:contextOrNilArg codeView:codeViewArg into:actionBlock
     <resource: #obsolete>
     ^ self
-        codeCompletionForSmalltalkMethod:methodOrNilArg orClass:classOrNilArg context:contextOrNilArg codeView:codeViewArg into:actionBlock
+	codeCompletionForSmalltalkMethod:methodOrNilArg orClass:classOrNilArg context:contextOrNilArg codeView:codeViewArg into:actionBlock
 ! !
 
 !DoWhatIMeanSupport methodsFor:'code completion-helpers'!
@@ -1784,46 +1782,46 @@
 
     list := allTheBest.
     LastChoices notNil ifTrue:[
-        lastChoice := LastChoices at:what ifAbsent:nil.
-        lastChoice notNil ifTrue:[
-            list := {lastChoice. nil. } , (list copyWithout:lastChoice).
-        ].
+	lastChoice := LastChoices at:what ifAbsent:nil.
+	lastChoice notNil ifTrue:[
+	    list := {lastChoice. nil. } , (list copyWithout:lastChoice).
+	].
     ].
 
     list size < 30 ifTrue:[
-        |menu idx exitKey|
-
-        menu := PopUpMenu labels:list.
-        menu hideOnKeyFilter:[:key | |hide|
-                hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
-                hide ifTrue:[
-                    exitKey := key.
-                ].
-                hide].
-
-        idx := menu startUp.
-        idx == 0 ifTrue:[
-            exitKey notNil ifTrue:[
-                codeView keyPress:exitKey x:0 y:0.
-            ].
-            ^ nil
-        ].
-        choice := list at:idx.
+	|menu idx exitKey|
+
+	menu := PopUpMenu labels:list.
+	menu hideOnKeyFilter:[:key | |hide|
+		hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
+		hide ifTrue:[
+		    exitKey := key.
+		].
+		hide].
+
+	idx := menu startUp.
+	idx == 0 ifTrue:[
+	    exitKey notNil ifTrue:[
+		codeView keyPress:exitKey x:0 y:0.
+	    ].
+	    ^ nil
+	].
+	choice := list at:idx.
     ] ifFalse:[
-        resources := codeView application isNil
-                        ifTrue:[ codeView resources]
-                        ifFalse:[ codeView application resources ].
-
-        choice := Dialog
-           choose:(resources string:'Choose ',what)
-           fromList:list
-           lines:20
-           title:(resources string:'Code completion').
-        choice isNil ifTrue:[^ nil].
+	resources := codeView application isNil
+			ifTrue:[ codeView resources]
+			ifFalse:[ codeView application resources ].
+
+	choice := Dialog
+	   choose:(resources string:'Choose ',what)
+	   fromList:list
+	   lines:20
+	   title:(resources string:'Code completion').
+	choice isNil ifTrue:[^ nil].
     ].
 
     LastChoices isNil ifTrue:[
-        LastChoices := Dictionary new.
+	LastChoices := Dictionary new.
     ].
     LastChoices at:what put:choice.
     ^ choice
@@ -2456,7 +2454,7 @@
 "/
 "/    info := best storeString.
 "/    implClass notNil ifTrue:[
-"/        info := implClass name , ' » ' , info.
+"/        info := implClass name , ' » ' , info.
 "/    ].
 "/    self information:info.
 "/].
@@ -3915,8 +3913,8 @@
 
 findNodeForInterval:interval in:source allowErrors:allowErrors
     ^ self
-        findNodeForInterval:interval in:source allowErrors:allowErrors
-        mustBeMethod:false
+	findNodeForInterval:interval in:source allowErrors:allowErrors
+	mustBeMethod:false
 
     "Modified: / 16-09-2011 / 14:52:28 / cg"
 !
@@ -3925,8 +3923,8 @@
     "if mustBeMethod is true, do not try a regular expression (as in a workspace)."
 
     ^ self
-        findNodeForInterval:interval in:source allowErrors:allowErrors
-        mustBeMethod:mustBeMethod mustBeExpression:false
+	findNodeForInterval:interval in:source allowErrors:allowErrors
+	mustBeMethod:mustBeMethod mustBeExpression:false
 !
 
 findNodeForInterval:interval in:source allowErrors:allowErrors mustBeMethod:mustBeMethod mustBeExpression:mustBeExpression
@@ -4127,10 +4125,10 @@
 
     node := parseTree whichNodeIsContainedBy:interval.
     node isNil ifTrue:[
-        node := parseTree whichNodeIntersects:interval.
-        node isNil ifTrue: [
-            node := self findNodeIn:parseTree forInterval:interval
-        ].
+	node := parseTree whichNodeIntersects:interval.
+	node isNil ifTrue: [
+	    node := self findNodeIn:parseTree forInterval:interval
+	].
     ].
     ^ node
 
@@ -4216,53 +4214,53 @@
 
     list := allTheBest.
     LastChoices notNil ifTrue:[
-        lastChoice := LastChoices at:what ifAbsent:nil.
-        lastChoice notNil ifTrue:[
-            "/ move tha last choice to the top of the list, if it is in.
-            (list includes: lastChoice) ifTrue:[
-                (list indexOf: lastChoice) < 10 ifTrue:[
-                    list := {lastChoice allBold } , (list copyWithout:lastChoice).
-                ]
-            ]
-        ].
+	lastChoice := LastChoices at:what ifAbsent:nil.
+	lastChoice notNil ifTrue:[
+	    "/ move tha last choice to the top of the list, if it is in.
+	    (list includes: lastChoice) ifTrue:[
+		(list indexOf: lastChoice) < 10 ifTrue:[
+		    list := {lastChoice allBold } , (list copyWithout:lastChoice).
+		]
+	    ]
+	].
     ].
 
     list size < 30 ifTrue:[
-        |menu idx exitKey|
-
-        menu := PopUpMenu labels:list.
-        menu hideOnKeyFilter:[:key | |hide|
-                hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
-                hide ifTrue:[
-                    exitKey := key.
-                ].
-                hide].
-        menu memorizeLastSelection:3 "sigh, not 1 because of heading!!".
-        idx := menu startUpWithHeading:'Choose ',what.
-        idx == 0 ifTrue:[
-            exitKey notNil ifTrue:[
-                codeView keyPress:exitKey x:0 y:0.
-            ].
-            ^ nil
-        ].
-        choice := list at:idx.
+	|menu idx exitKey|
+
+	menu := PopUpMenu labels:list.
+	menu hideOnKeyFilter:[:key | |hide|
+		hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
+		hide ifTrue:[
+		    exitKey := key.
+		].
+		hide].
+	menu memorizeLastSelection:3 "sigh, not 1 because of heading!!".
+	idx := menu startUpWithHeading:'Choose ',what.
+	idx == 0 ifTrue:[
+	    exitKey notNil ifTrue:[
+		codeView keyPress:exitKey x:0 y:0.
+	    ].
+	    ^ nil
+	].
+	choice := list at:idx.
     ] ifFalse:[
-        resources := codeView application isNil
-                        ifTrue:[ codeView resources]
-                        ifFalse:[ codeView application resources ].
-
-        choice := Dialog
-           choose:(resources string:'Choose ',what)
-           fromList:list
-           lines:20
-           initialSelection:(list firstIfEmpty:nil)
-           title:(resources string:'Code completion').
-        choice isNil ifTrue:[^ nil].
+	resources := codeView application isNil
+			ifTrue:[ codeView resources]
+			ifFalse:[ codeView application resources ].
+
+	choice := Dialog
+	   choose:(resources string:'Choose ',what)
+	   fromList:list
+	   lines:20
+	   initialSelection:(list firstIfEmpty:nil)
+	   title:(resources string:'Code completion').
+	choice isNil ifTrue:[^ nil].
     ].
     choice := choice string.
 
     LastChoices isNil ifTrue:[
-        LastChoices := Dictionary new.
+	LastChoices := Dictionary new.
     ].
     LastChoices at:what put:choice.
     ^ choice
@@ -4348,26 +4346,26 @@
     |tree|
 
     source = LastSource ifTrue:[
-        tree := LastParseTree.
+	tree := LastParseTree.
     ] ifFalse:[
-        tree := RBParser
-                parseMethod:source
-                onError: [:str :err :nodesSoFar :parserOrNil|
-                        allowErrors ifTrue:[
-                            "/ parserOrNil isNil if raised by the scanner
-                            parserOrNil notNil ifTrue:[
-                                ^ parserOrNil currentMethodNode
-                            ]
-                        ].
-                        ^ nil
-                    ]
-                proceedAfterError:false
-                rememberNodes:true.
-
-        tree notNil ifTrue:[
-            LastSource := source.
-            LastParseTree := tree.
-        ]
+	tree := RBParser
+		parseMethod:source
+		onError: [:str :err :nodesSoFar :parserOrNil|
+			allowErrors ifTrue:[
+			    "/ parserOrNil isNil if raised by the scanner
+			    parserOrNil notNil ifTrue:[
+				^ parserOrNil currentMethodNode
+			    ]
+			].
+			^ nil
+		    ]
+		proceedAfterError:false
+		rememberNodes:true.
+
+	tree notNil ifTrue:[
+	    LastSource := source.
+	    LastParseTree := tree.
+	]
     ].
     ^ tree
 
@@ -4386,6 +4384,8 @@
 
     |node nodeParent checkedNode characterBeforeCursor|
 
+    characterPositionOfCursor < 1 ifTrue:[^ self].
+
     "/ 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
@@ -4656,7 +4656,7 @@
     self information:'Node is neither variable nor message.'.
 
     "Modified: / 04-07-2006 / 18:48:26 / fm"
-    "Modified: / 26-02-2017 / 11:59:23 / cg"
+    "Modified: / 26-02-2017 / 12:56:01 / cg"
 !
 
 withoutSelectorsUnlikelyFor:aClass from:selectorsArg forPartial:partialSelector
@@ -4773,18 +4773,18 @@
     possibleCompletions := OrderedCollection new.
 
     Symbol allInstancesDo:[:existingSym |
-        (existingSym startsWith:sym) ifTrue:[
-            (existingSym = sym) ifFalse:[
-                possibleCompletions add:existingSym
-            ].
-        ].
+	(existingSym startsWith:sym) ifTrue:[
+	    (existingSym = sym) ifFalse:[
+		possibleCompletions add:existingSym
+	    ].
+	].
     ].
     possibleCompletions sort.
 
     best := possibleCompletions longestCommonPrefix.
     (best = sym or:[(possibleCompletions includes:best) not]) ifTrue:[
-        best := self askUserForCompletion:'symbol literal' for:codeView at: node start from:possibleCompletions.
-        best isNil ifTrue:[^ self].
+	best := self askUserForCompletion:'symbol literal' for:codeView at: node start from:possibleCompletions.
+	best isNil ifTrue:[^ self].
     ].
 
 "/ self showInfo:best.
@@ -4792,24 +4792,24 @@
     start := node start.
     stop := node stop.
     (codeView characterAtCharacterPosition:start) == $# ifTrue:[
-        start := start + 1.
+	start := start + 1.
     ].
     (codeView characterAtCharacterPosition:start) == $' ifTrue:[
-        start := start + 1.
-        stop := stop - 1.
+	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'.
+	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
+	oldLen := stop - start + 1.
+	newLen := best size.
+	codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
+	codeView dontReplaceSelectionOnInput
     ].
 
     "Modified: / 16-02-2010 / 10:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -5028,7 +5028,7 @@
 "/
 "/    info := best storeString.
 "/    implClass notNil ifTrue:[
-"/        info := implClass name , ' » ' , info.
+"/        info := implClass name , ' » ' , info.
 "/    ].
 "/    self information:info.