merge with 174
authorClaus Gittinger
Wed, 26 Feb 2014 19:28:14 +0100
changeset 176 df6d3225d1e4
parent 175 1294a2f91053 (current diff)
parent 171 ff7e9e7c0ac5 (diff)
child 177 be588b60f4b2
merge with 174
Make.proto
SmallSense__ClassPO.st
SmallSense__ClassType.st
SmallSense__CodeNavigationService.st
SmallSense__CompletionContext.st
SmallSense__CompletionController.st
SmallSense__CompletionEngine.st
SmallSense__EditSupport.st
SmallSense__GroovyCompletionEngineSimple.st
SmallSense__JavaEditSupport.st
SmallSense__PO.st
SmallSense__SettingsAppl.st
SmallSense__SmalltalkCompletionEngine.st
SmallSense__SmalltalkEditSupport.st
SmallSense__SmalltalkParseNodeFinder.st
SmallSense__SmalltalkParser.st
bc.mak
extensions.st
jv_smallsense.st
smallsense.rc
--- a/SmallSense__CodeNavigationService.st	Wed Feb 26 19:24:50 2014 +0100
+++ b/SmallSense__CodeNavigationService.st	Wed Feb 26 19:28:14 2014 +0100
@@ -215,9 +215,26 @@
 !
 
 navigateToTypeReference: node
-    | className classes |
+    | classType className classes |
+
+    classType := node resolvedType.
+    classType notNil ifTrue:[
+        className := node resolvedType leafComponentType compoundName asStringWith: $/.
+    ] ifFalse:[ 
+        | unit |
 
-    className := node resolvedType leafComponentType compoundName asStringWith: $/.
+        unit := service codeView syntaxElements tree.
+        "/ Search imports...
+        unit imports do:[:import | 
+            import tokens last = node token ifTrue:[ 
+                className := import tokens asStringWith:$/.
+            ].
+        ].
+        "/ If not imported, Try compilation unit's package...
+        className isNil ifTrue:[ 
+            className := (unit currentPackage tokens asStringWith: $/) , '/' , node token.
+        ].
+    ].
     "/ Kludge - support both old and new Java class naming scheme
     classes := (JavaClass canUnderstand: #binaryName) 
                     ifTrue:[self environment allClasses select:[:cls | cls isJavaClass and:[cls binaryName = className]]]
@@ -234,7 +251,7 @@
     self halt: 'Not yet supported'.
 
     "Created: / 24-09-2013 / 10:16:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 26-11-2013 / 22:59:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-02-2014 / 23:27:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CodeNavigationService::Navigator methodsFor:'navigation - Smalltalk'!
--- a/SmallSense__PO.st	Wed Feb 26 19:24:50 2014 +0100
+++ b/SmallSense__PO.st	Wed Feb 26 19:28:14 2014 +0100
@@ -151,22 +151,24 @@
     stringToInsert := stringToComplete copyFrom: (stringAlreadyWritten size + 1).
     textView isCodeView2 ifTrue:[textView := textView textView].
     (stringToComplete startsWith: stringAlreadyWritten) ifTrue:[
-        context support electricInsert:stringToInsert
-              ignoreKeystrokes:stringToInsert
+        context support 
+                electricInsert:stringToInsert
+                ignoreKeystrokes:stringToInsert.
+        textView cursorCol: textView cursorCol - stringToComplete size + (po cursorColumnAfterCompleteForLanguage: context language).
     ] ifFalse:[
+       | startCol endCol |
        textView undoableDo:[
-            | startCol endCol |
-
             endCol := textView cursorCol - 1.
             startCol := textView cursorCol - stringAlreadyWritten size.
             textView insertStringAtCursor: stringToComplete.
             textView deleteFromLine:textView cursorLine col: startCol toLine:textView cursorLine col:endCol.
         ].
+        textView cursorCol: startCol + (po cursorColumnAfterCompleteForLanguage: context language).
+
     ].
-    textView cursorCol: textView cursorCol - stringToComplete size + (po cursorColumnAfterCompleteForLanguage: context language).
 
     "Created: / 17-10-2013 / 01:08:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 21-01-2014 / 23:30:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-02-2014 / 00:02:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PO methodsFor:'displaying'!
--- a/SmallSense__SmalltalkParser.st	Wed Feb 26 19:24:50 2014 +0100
+++ b/SmallSense__SmalltalkParser.st	Wed Feb 26 19:28:14 2014 +0100
@@ -578,6 +578,7 @@
     super markBracketAt:pos
 
     "Created: / 03-04-2011 / 22:39:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 25-02-2014 / 23:06:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 markFrom:pos1 to:pos2 withEmphasis:fontEmp color:clrIn
--- a/SmallSense__SmalltalkSyntaxHighlighter.st	Wed Feb 26 19:24:50 2014 +0100
+++ b/SmallSense__SmalltalkSyntaxHighlighter.st	Wed Feb 26 19:28:14 2014 +0100
@@ -305,7 +305,7 @@
 
 !SmalltalkSyntaxHighlighter methodsFor:'parsing-expressions'!
 
-_binaryExpressionFor:receiverArg
+binaryExpressionFor:receiverArg
     "parse a binary-expression; return a node-tree, nil or #Error"
 
     |receiver expr arg sel pos1 pos2 lno|
@@ -316,300 +316,69 @@
     "special kludge: since Scanner cannot know if -digit is a binary
      expression or a negative constant, handle cases here"
 
-    [(tokenType == #BinaryOperator)
+    [(tokenType == #BinaryOperator) 
      or:[(tokenType == $|)
      or:[(tokenType == $^ and:[parserFlags allowCaretAsBinop])
-	 or:[((tokenType == #Integer) or:[tokenType == #Float])
-	     and:[tokenValue < 0]]]]
+         or:[((tokenType == #Integer) or:[tokenType == #Float])
+             and:[tokenValue < 0]]]]
     ] whileTrue:[
-	"/ kludge alarm: in a function-call argList, #, is not a binarySelector
-	inFunctionCallArgument == true ifTrue:[
-	    ((tokenType == #BinaryOperator) and:[tokenName = ',']) ifTrue:[
-		^ receiver
-	    ].
-	].
+        "/ kludge alarm: in a function-call argList, #, is not a binarySelector
+        inFunctionCallArgument == true ifTrue:[
+            ((tokenType == #BinaryOperator) and:[tokenName = ',']) ifTrue:[
+                ^ receiver
+            ].
+        ].
 
-	pos1 := tokenPosition.
-	lno := tokenLineNr.
+        pos1 := tokenPosition.
+        lno := tokenLineNr.
 
-	"/ kludge alarm: bar, caret and minus are not scanned as binop
-	(tokenType == $|) ifTrue:[
-	    sel := '|'.
-	    sel := self selectorCheck:sel for:receiver position:tokenPosition to:tokenPosition.
-	    self nextToken.
-	] ifFalse:[
-	    (tokenType == $^) ifTrue:[
-		sel := '^'.
-		sel := self selectorCheck:sel for:receiver position:tokenPosition to:tokenPosition.
-		self nextToken.
-	    ] ifFalse:[
-		(tokenType == #BinaryOperator) ifTrue:[
-		    sel := tokenName.
-		    sel := self selectorCheck:sel for:receiver position:tokenPosition to:(tokenPosition + tokenName size - 1).
-		    self nextToken
-		] ifFalse:[
-		    sel := '-'.
-		    token := tokenValue := tokenValue negated.
-		    tokenPosition := tokenPosition + 1. "/ to skip the sign
-		]
-	    ].
-	].
+        "/ kludge alarm: bar, caret and minus are not scanned as binop
+        (tokenType == $|) ifTrue:[
+            sel := '|'.
+            sel := self selectorCheck:sel for:receiver position:tokenPosition to:tokenPosition.
+            self nextToken.
+        ] ifFalse:[
+            (tokenType == $^) ifTrue:[
+                sel := '^'.
+                sel := self selectorCheck:sel for:receiver position:tokenPosition to:tokenPosition.
+                self nextToken.
+            ] ifFalse:[
+                (tokenType == #BinaryOperator) ifTrue:[
+                    sel := tokenName.
+                    sel := self selectorCheck:sel for:receiver position:tokenPosition to:(tokenPosition + tokenName size - 1).
+                    self nextToken
+                ] ifFalse:[
+                    sel := '-'.
+                    token := tokenValue := tokenValue negated.
+                    tokenPosition := tokenPosition + 1. "/ to skip the sign
+                ]
+            ].
+        ].
 
-	pos2 := pos1 + sel size - 1.
-	self markSelector:sel from:pos1 to:pos2 receiverNode:receiver.
-	lastSelectorElement := nil.
+        pos2 := pos1 + sel size - 1.
+        self markSelector:sel from:pos1 to:pos2 receiverNode:receiver.
+        lastSelectorElement := nil.
 
-	arg := self unaryExpression.
-	(arg == #Error) ifTrue:[^ #Error].
+        arg := self unaryExpression.
+        (arg == #Error) ifTrue:[^ #Error].
 
-	expr := BinaryNode receiver:receiver selector:sel arg:arg fold:foldConstants.
-	expr isErrorNode ifTrue:[
-	    self parseError:(expr errorString) position:pos1 to:tokenPosition.
-	    errorFlag := false. "ok, user wants it - so he'll get it"
-	    expr := BinaryNode receiver:receiver selector:sel arg:arg fold:nil.
-	].
-	expr lineNumber:lno.
-	expr selectorPosition:pos1.
+        expr := BinaryNode receiver:receiver selector:sel arg:arg fold:foldConstants.
+        expr isErrorNode ifTrue:[
+            self parseError:(expr errorString) position:pos1 to:tokenPosition.
+            errorFlag := false. "ok, user wants it - so he'll get it"
+            expr := BinaryNode receiver:receiver selector:sel arg:arg fold:nil.
+        ].
+        expr lineNumber:lno.
+        expr selectorPosition:pos1.
 
-	self checkPlausibilityOf:expr from:pos1 to:pos2.
-	parseForCode ifFalse:[
-	    self rememberSelectorUsed:sel receiver:receiver
-	].
-	receiver := expr.   "/ for next message
+        self checkPlausibilityOf:expr from:pos1 to:pos2.
+        receiver := expr.   "/ for next message
     ].
     ^ receiver
 
     "Modified: / 09-01-1998 / 19:05:18 / stefan"
     "Modified: / 14-02-2010 / 17:54:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 19-01-2012 / 10:46:49 / cg"
-    "Created: / 16-02-2012 / 21:54:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-_keywordExpressionFor:receiverArg
-    "parse a keyword-expression; return a node-tree, nil or #Error.
-
-     keywordExpression ::= binaryexpression
-			   | { KEYWORD-PART binaryExpression }
-    "
-
-    |expr receiver sel arg args posR1 posR2 pos1 pos2 lno positions constVal|
-
-    receiver := receiverArg.
-    posR1 := tokenPosition.
-    (tokenType == #Keyword) ifFalse:[^ receiver].
-
-    pos1 := posR2 := tokenPosition.
-    pos2 := tokenPosition + tokenName size - 1.
-    positions := OrderedCollection with:(pos1 to:pos2).
-    sel := tokenName.
-    lno := tokenLineNr.
-    self nextToken.
-    arg := self binaryExpression.
-    (arg == #Error) ifTrue:[^ #Error].
-    args := Array with:arg.
-    [tokenType == #Keyword] whileTrue:[
-	sel := sel , tokenName.
-	pos2 := tokenPosition + tokenName size - 1.
-	positions add:(tokenPosition to:pos2).
-	self nextToken.
-	arg := self binaryExpression.
-	(arg == #Error) ifTrue:[^ #Error].
-	args := args copyWith:arg.
-    ].
-
-    positions do:[:p |
-	self markSelector:sel from:p start to:p stop receiverNode:receiver.
-    ].
-    lastSelectorElement := nil.
-    sel := self selectorCheck:sel for:receiver positions:positions.
-
-    ignoreWarnings ifFalse:[
-	(Class definitionSelectors includes:sel) ifTrue:[
-	    (receiver isVariable and:[receiver isUndeclared]) ifTrue:[
-		"this is not an error - the undefined class may be loaded after this code!!"
-		self warning:('as yet undefined superclass: ' , receiver name) position:pos1 to:pos2.
-	    ].
-	].
-    ].
-
-    expr := MessageNode receiver:receiver selector:sel args:args fold:foldConstants.
-    expr isErrorNode ifTrue:[
-	self parseError:(expr errorString) position:pos1 to:pos2.
-	errorFlag := false. "ok, user wants it - so he'll get it"
-	expr := MessageNode receiver:receiver selector:sel args:args fold:nil.
-    ].
-    expr lineNumber:lno.
-    self checkPlausibilityOf:expr from:pos1 to:pos2.
-    parseForCode ifFalse:[
-	self rememberSelectorUsed:sel receiver:receiver
-    ].
-
-"/        (contextToEvaluateIn isNil and:[selfValue isNil]) ifTrue:[    "/ do not check this for doits
-"/            receiver isSuper ifTrue:[
-"/                sel ~= selector ifTrue:[
-"/                    self warnCommonMistake:'possible bad super message (selector should be same as in current method) ?'
-"/                                  position:posR1 to:posR2-1
-"/                ].
-"/            ].
-"/        ].
-"/
-
-    (sel = #ifTrue: or:[sel = #ifFalse: or:[sel = #ifTrue:ifFalse: or:[sel = #ifFalse:ifTrue:]]]) ifTrue:[
-	(expr receiver withConstantValueDo:[:val | constVal := val]) ifTrue:[
-	    |indexOfArgNotExecuted|
-
-	    "/ receiver evaluates to a constant
-	    constVal == true ifTrue:[
-		(sel startsWith: #ifFalse:) ifTrue:[
-		    indexOfArgNotExecuted := 1.
-		] ifFalse:[
-		    indexOfArgNotExecuted := 2.
-		]
-	    ].
-	    constVal == false ifTrue:[
-		(sel startsWith: #ifTrue:) ifTrue:[
-		    indexOfArgNotExecuted := 1.
-		] ifFalse:[
-		    indexOfArgNotExecuted := 2.
-		]
-	    ].
-	    indexOfArgNotExecuted == 2 ifTrue:[
-		args size == 1 ifTrue:[ indexOfArgNotExecuted := nil]
-	    ].
-
-	    indexOfArgNotExecuted notNil ifTrue:[
-		|argIsNotExecuted|
-
-		"/ self warning:'receiver is constant; arg',indexOfArgNotExecuted printString,' is never executed' position:pos1 to:tokenPosition.
-		argIsNotExecuted := expr args at:indexOfArgNotExecuted.
-		argIsNotExecuted isBlockNode ifTrue:[
-		    self markCommentFrom:argIsNotExecuted startPosition to:argIsNotExecuted endPosition.
-		].
-	    ].
-	].
-    ].
-
-    (ignoreErrors or:[ignoreWarnings]) ifFalse:[
-	(sel = #and: or:[sel = #or:]) ifTrue:[
-	    expr arg1 isBlock ifFalse:[
-		(expr arg1 isVariable
-		and:[ (expr arg1 name asLowercase includesString:'block')]) ifFalse:[
-		    self warnCommonMistake:'(possible common mistake) missing block brackets ?'
-			      position:pos2+1 to:tokenPosition-1
-		]
-	    ].
-	    ^ expr.
-	].
-
-	(sel = #whileTrue: or:[sel = #whileFalse:]) ifTrue:[
-	    expr receiver isBlock ifFalse:[
-		(expr receiver isVariable
-		and:[ (expr receiver name asLowercase includesString:'block')]) ifFalse:[
-		    self warnCommonMistake:'(possible common mistake) missing block brackets ?'
-			      position:pos1 to:pos2
-		]
-	    ].
-	    ^ expr.
-	].
-
-	(sel = #ifTrue: or:[sel = #ifFalse:]) ifTrue:[
-	    expr receiver isMessage ifTrue:[
-		(expr receiver selector = #whileTrue or:[expr receiver selector = #whileFalse]) ifTrue:[
-		    self warnCommonMistake:'strange receiver expression'
-			      position:pos1 to:pos2
-		].
-	    ].
-	    ^ expr
-	].
-    ].
-
-    ^ expr.
-
-    "Modified: / 14-02-2010 / 17:58:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 19-01-2012 / 10:47:01 / cg"
-    "Created: / 16-02-2012 / 21:54:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-_unaryExpressionFor:receiverArg
-    "parse a unary-expression; return a node-tree, nil or #Error"
-
-    |receiver expr sel pos pos2 lNr arguments|
-
-    receiver := receiverArg.
-    (receiver == #Error) ifTrue:[^ #Error].
-
-    [ self isValidUnarySelector:tokenType ] whileTrue:[
-	pos := tokenPosition.
-	pos2 := pos + tokenName size - 1.
-	lNr := tokenLineNr.
-	sel := tokenName.
-
-	self markSelector:sel from:pos to:pos2 receiverNode:receiver.
-	lastSelectorElement := nil.
-
-	self nextToken.
-	tokenType == $( ifTrue:[
-	    parserFlags allowSqueakExtensions == true ifTrue:[
-		"/ croquet/squeak extension - c/java-style arguments
-		arguments := self functionCallArgList.
-		"/ synthetic selector: foo[:[with:[with:[...]]]]
-		arguments notEmpty ifTrue:[
-		    sel := sel , ':'.
-		    arguments size - 1 timesRepeat:[ sel := sel , 'with:' ].
-		].
-		sel := self selectorCheck:sel for:receiver position:pos to:pos2.
-		expr := MessageNode receiver:receiver selector:sel args:arguments fold:foldConstants.
-		expr isErrorNode ifTrue:[
-		    self parseError:(expr errorString) position:pos to:pos2.
-		    errorFlag := false. "ok, user wants it - so he'll get it"
-		    expr := MessageNode receiver:receiver selector:sel args:arguments fold:nil.
-		].
-		expr lineNumber:lNr.
-		self checkPlausibilityOf:expr from:pos to:pos2.
-		parseForCode ifFalse:[
-		    self rememberSelectorUsed:sel receiver:receiver
-		].
-		^ expr.
-	    ].
-	].
-
-	sel := self selectorCheck:sel for:receiver position:pos to:pos2.
-	expr := UnaryNode receiver:receiver selector:sel fold:foldConstants.
-	expr isErrorNode ifTrue:[
-	    self warning:(expr errorString , '.\\If you proceed, that error will happen at runtime.') withCRs position:pos to:pos2.
-	    errorFlag := false. "ok, user wants it - so he'll get it"
-	    expr := UnaryNode receiver:receiver selector:sel fold:nil.
-	].
-	expr lineNumber:lNr.
-
-	self checkPlausibilityOf:expr from:pos to:pos2.
-	parseForCode ifFalse:[
-	    self rememberSelectorUsed:sel receiver:receiver
-	].
-
-	receiver := expr.   "/ for next message
-    ].
-    ^ receiver
-
-    "Modified: / 14-02-2010 / 17:56:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 19-01-2012 / 10:47:37 / cg"
-    "Created: / 16-02-2012 / 21:54:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-binaryExpression
-    | node savedLastSelectorElement |
-
-    savedLastSelectorElement := lastSelectorElement.
-    lastSelectorElement := nil.
-    node := super binaryExpression.
-    (lastSelectorElement notNil and:[node ~~ #Error and:[node isMessage]]) ifTrue:[
-	lastSelectorElement node parent: node.
-    ].
-    lastSelectorElement := savedLastSelectorElement.
-    ^node
-
-    "Modified: / 19-01-2000 / 16:22:16 / cg"
-    "Created: / 16-02-2012 / 21:56:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 expression
@@ -723,44 +492,31 @@
 
 !SmalltalkSyntaxHighlighter methodsFor:'syntax detection'!
 
-markArgumentIdentifierFrom:pos1 to:pos2
-    | node el prevEl |
+markLocalVariableDeclaration: name from:pos1 to:pos2
+    | type node |
 
-    super markArgumentIdentifierFrom:pos1 to:pos2.
-    node := VariableNode methodArgumentNamed:(sourceText string copyFrom: pos1 to: pos2).
+    super markLocalVariableDeclaration: name from:pos1 to:pos2.
+
+    type := currentBlock notNil ifTrue:[#BlockVariable] ifFalse:[#MethodVariable].
+    node := VariableNode type: type name: name.
     node startPosition: pos1 endPosition: pos2.
-    el := elements newElementFor: node.
-    prevEl := lastVariableElements at:node name ifAbsent:[nil].
-    prevEl notNil ifTrue:[prevEl next:el].
-    lastVariableElements at:node name put:el.
-    elements add: el.
+    self rememberVariableElementFor: node from: pos1 to: pos2 assigned: false.
+
+    "Created: / 25-02-2014 / 20:22:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+markMethodArgumentIdentifierFrom:pos1 to:pos2
+    | node |
+
+    super markMethodArgumentIdentifierFrom:pos1 to:pos2.
+
+    node := VariableNode methodArgumentNamed:(sourceText string copyFrom: pos1 to: pos2).
+    node startPosition: pos1 endPosition: pos2.    
+    self rememberVariableElementFor: node from:pos1 to:pos2 assigned:false
 
     "Created: / 24-07-2010 / 09:25:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 21-08-2011 / 09:27:26 / cg"
-    "Modified: / 16-02-2012 / 22:34:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-markBadIdentifierFrom:pos1 to:pos2
-
-    super markBadIdentifierFrom:pos1 to:pos2
-
-    "Created: / 17-03-2012 / 19:02:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-markLocalIdentifierFrom:pos1 to:pos2
-    | node el prevEl |
-
-    super markLocalIdentifierFrom:pos1 to:pos2.
-    node := VariableNode methodLocalNamed:(sourceText string copyFrom: pos1 to: pos2).
-    node startPosition: pos1 endPosition: pos2.
-    el := elements newElementFor: node.
-    prevEl := lastVariableElements at:node name ifAbsent:[nil].
-    prevEl notNil ifTrue:[prevEl next:el].
-    lastVariableElements at:node name put:el.
-    elements add: el.
-
-    "Modified: / 21-08-2011 / 09:27:26 / cg"
-    "Created: / 16-02-2012 / 22:36:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 25-02-2014 / 12:15:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 markSelector:selectorString from:pos1 to:pos2 receiverNode:aReceiverNode
@@ -798,6 +554,33 @@
     "Modified: / 19-04-2012 / 09:53:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+markSelfFrom:pos1 to:pos2
+    | node |
+
+    super markSelfFrom:pos1 to:pos2.
+
+    node := SelfNode new.
+    node startPosition: pos1 endPosition: pos2.  
+    node type: #Self.
+    self rememberVariableElementFor: node from:pos1 to:pos2 assigned:false
+
+    "Created: / 21-08-2011 / 09:15:45 / cg"
+    "Modified: / 25-02-2014 / 21:56:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+markSuperFrom:pos1 to:pos2
+    | node |
+
+    super markSuperFrom:pos1 to:pos2.
+
+    node := SuperNode new.
+    node startPosition: pos1 endPosition: pos2.  
+    node type: #Super.
+    self rememberVariableElementFor: node from:pos1 to:pos2 assigned:false
+
+    "Created: / 25-02-2014 / 21:57:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 markUnknownIdentifierFrom:pos1 to:pos2
 
     ignoreBadIdentifier == true ifTrue:[ ^ self ].
@@ -806,6 +589,36 @@
 
     "Created: / 31.3.1998 / 19:09:26 / cg"
     "Modified: / 31.3.1998 / 19:10:30 / cg"
+!
+
+markVariable:v from:pos1 to:pos2 assigned:assigned
+    self rememberVariableElementFor:v from:pos1 to:pos2 assigned:assigned.
+    super markVariable:v from:pos1 to:pos2 assigned:assigned.
+
+    "Created: / 25-06-2010 / 13:03:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-08-2011 / 09:26:30 / cg"
+    "Modified: / 25-02-2014 / 14:07:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+rememberVariableElementFor:node from:pos1 to:pos2 assigned:assigned
+    |name typeSymbol element prev|
+
+    name := node name.
+    typeSymbol := node type.
+    prev := (lastVariableElements at:typeSymbol ifAbsentPut:[Dictionary new]) at:name ifAbsent:[nil].
+    (prev notNil and:[prev start == pos1]) ifTrue:[
+"/        prev assigned:assigned.
+        ^ self
+    ].
+
+    element := elements newElementFor: node.
+
+    prev notNil ifTrue:[prev next:element].
+    (lastVariableElements at:typeSymbol) at:name put:element.
+
+    elements add: element.
+
+    "Created: / 25-02-2014 / 12:13:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SmalltalkSyntaxHighlighter class methodsFor:'documentation'!
--- a/smallsense.rc	Wed Feb 26 19:24:50 2014 +0100
+++ b/smallsense.rc	Wed Feb 26 19:28:14 2014 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2011\nCopyright eXept Software AG 1998-2011\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Thu, 06 Feb 2014 20:27:12 GMT\0"
+      VALUE "ProductDate", "Wed, 29 Jan 2014 10:41:45 GMT\0"
     END
 
   END