*** empty log message *** cvs_MAIN
authorClaus Gittinger <cg@exept.de>
Tue, 26 Jan 2016 21:40:42 +0100
branchcvs_MAIN
changeset 917 c1a6a847be65
parent 916 8b0f48107fff
child 918 8f53c9895ce7
*** empty log message ***
SmallSense__CompletionController.st
SmallSense__EditSupport.st
SmallSense__Manager.st
SmallSense__SmalltalkEditSupport.st
SmallSense__SmalltalkLintService.st
extensions.st
--- a/SmallSense__CompletionController.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__CompletionController.st	Tue Jan 26 21:40:42 2016 +0100
@@ -5,7 +5,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -37,7 +37,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -64,17 +64,17 @@
     | engineClass |
 
     engineClass := self completionEngineClass.
-    ^ engineClass notNil 
-        ifTrue:[ engineClass new ]
-        ifFalse:[ nil ].
+    ^ engineClass notNil
+	ifTrue:[ engineClass new ]
+	ifFalse:[ nil ].
 
     "Created: / 18-05-2014 / 11:58:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 environment
-    ^ support notNil 
-        ifTrue:[support environment]
-        ifFalse:[Smalltalk].
+    ^ support notNil
+	ifTrue:[support environment]
+	ifFalse:[Smalltalk].
 
     "Created: / 18-05-2014 / 11:53:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -90,9 +90,9 @@
 !CompletionController methodsFor:'accessing-classes'!
 
 completionEngineClass
-    ^ support notNil 
-        ifTrue:[ support completionEngineClass ]
-        ifFalse:[ nil ].
+    ^ support notNil
+	ifTrue:[ support completionEngineClass ]
+	ifFalse:[ nil ].
 
     "Created: / 18-05-2014 / 11:55:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -102,41 +102,41 @@
 handleKeyPress:key x:x y:y
 
     key == #Control_L ifTrue:[
-        completionView notNil ifTrue:[
-            ^ false.
-        ].
+	completionView notNil ifTrue:[
+	    ^ false.
+	].
     ].
 
     key == #CodeCompletion  ifTrue: [
-        autoSelect := true.    
-        self startCompletionProcess.
-        ^ true
+	autoSelect := true.
+	self startCompletionProcess.
+	^ true
     ].
 
     (key == #BackSpace or:[key == #BasicBackspace]) ifTrue:[
-        | c |
+	| c |
 
-        c := editView characterBeforeCursor.
-        (c notNil and:[c isAlphaNumeric]) ifTrue:[
-             ^ false
-        ].
-    ].     
+	c := editView characterBeforeCursor.
+	(c notNil and:[c isAlphaNumeric]) ifTrue:[
+	     ^ false
+	].
+    ].
 
 
     completionView notNil ifTrue:[
-        (key == #Return and:[completionView hasSelection]) ifTrue:[
-            self complete.
-            ^ true.
-        ].
-        key == #Tab ifTrue:[ 
-            self handleKeyPressTab.  
-            ^ true
-        ].
-        key isCharacter ifTrue:[
-            (self updateSelectionAfterKeyPress: key) ifTrue:[ 
-                ^ true
-            ].
-        ].
+	(key == #Return and:[completionView hasSelection]) ifTrue:[
+	    self complete.
+	    ^ true.
+	].
+	key == #Tab ifTrue:[
+	    self handleKeyPressTab.
+	    ^ true
+	].
+	key isCharacter ifTrue:[
+	    (self updateSelectionAfterKeyPress: key) ifTrue:[
+		^ true
+	    ].
+	].
     ].
     ^ super handleKeyPress:key x:x y:y
 
@@ -154,43 +154,43 @@
     matching := OrderedCollection new.
     minlen := SmallInteger maxVal.
     completionView list do:[:po |
-        | s |
+	| s |
 
-        s := po stringToComplete.
-        (s startsWith: prefix) ifTrue:[
-            matching add: po -> s.
-            minlen := minlen min: s size.
-        ].
+	s := po stringToComplete.
+	(s startsWith: prefix) ifTrue:[
+	    matching add: po -> s.
+	    minlen := minlen min: s size.
+	].
     ].
     matching isEmpty ifTrue:[
-        completionView flash.
-        ^self.
+	completionView flash.
+	^self.
     ].
     matching size == 1 ifTrue:[
-        self complete: matching first key.
+	self complete: matching first key.
     ].
 
     longest := String streamContents:[:s |
-        | i |
+	| i |
 
-        s nextPutAll: prefix.
-        i := prefix size + 1.
-        [ i <= minlen ] whileTrue:[
-            | c |
+	s nextPutAll: prefix.
+	i := prefix size + 1.
+	[ i <= minlen ] whileTrue:[
+	    | c |
 
-            c := matching first value at: i.
-            (matching allSatisfy:[:e|(e value at: i) == c]) ifTrue:[
-                s nextPut:c.
-                i := i + 1.
-            ] ifFalse:[
-                "/ terminate the loop    
-                i := minlen + 2.
-            ]
-        ]
+	    c := matching first value at: i.
+	    (matching allSatisfy:[:e|(e value at: i) == c]) ifTrue:[
+		s nextPut:c.
+		i := i + 1.
+	    ] ifFalse:[
+		"/ terminate the loop
+		i := minlen + 2.
+	    ]
+	]
     ].
     longest size = prefix size ifTrue:[
-        completionView flash.
-        ^self.
+	completionView flash.
+	^self.
     ].
     editView insertStringAtCursor:(longest copyFrom: prefix size + 1).
 
@@ -201,12 +201,12 @@
 postKeyPress:key
     seqno := seqno + 1.
     seqno == SmallInteger maxVal ifTrue:[
-        seqno := 0.
+	seqno := 0.
     ].
 
-    UserPreferences current immediateCodeCompletion ifFalse:[
-        "/ only update, if already open
-        completionView isNil ifTrue:[^ self].
+    (UserPreferences current immediateCodeCompletion == true) ifFalse:[
+	"/ only update, if already open
+	completionView isNil ifTrue:[^ self].
     ].
 
 "/    (key == #BackSpace or:[key == #BasicBackspace]) ifTrue:[
@@ -215,25 +215,25 @@
 "/    ].
 
     key isCharacter ifTrue:[
-        key isLetterOrDigit not ifTrue:[
-            "/ Hack for Java - should be delegated to completion engine    
-            (key == $. and:[support notNil and:[ support language isJavaLike ]]) ifTrue:[ 
-                ^ self
-            ].
-            self closeCompletionView
-        ] ifFalse:[
-            | c |
+	key isLetterOrDigit not ifTrue:[
+	    "/ Hack for Java - should be delegated to completion engine
+	    (key == $. and:[support notNil and:[ support language isJavaLike ]]) ifTrue:[
+		^ self
+	    ].
+	    self closeCompletionView
+	] ifFalse:[
+	    | c |
 
-            c := editView characterBeforeCursor.
-            (c notNil and:[c isLetterOrDigit]) ifTrue:[
-                c := editView characterUnderCursor.
-                c isSeparator ifTrue:[
-                    autoSelect := false.
-                    self updateCompletionList.
-                ].
-            ]
-        ].
-        ^ self
+	    c := editView characterBeforeCursor.
+	    (c notNil and:[c isLetterOrDigit]) ifTrue:[
+		c := editView characterUnderCursor.
+		c isSeparator ifTrue:[
+		    autoSelect := false.
+		    self updateCompletionList.
+		].
+	    ]
+	].
+	^ self
     ].
 
     "Created: / 28-09-2013 / 00:21:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -248,7 +248,7 @@
     "/ please change as required (and remove this comment)
     "/ support := nil.
     seqno := 0.
-    completeIfUnambiguous := UserPreferences current smallSenseCompleteIfUnambiguous.
+    completeIfUnambiguous := (UserPreferences current smallSenseCompleteIfUnambiguous == true).
 
     "/ super initialize.   -- commented since inherited method does nothing
 
@@ -274,8 +274,8 @@
 complete: item afterKeyPress: keyOrNil
      self closeCompletionView.
      item insert.
-     keyOrNil notNil ifTrue:[  
-         support keyPressIgnored.
+     keyOrNil notNil ifTrue:[
+	 support keyPressIgnored.
      ].
 
     "Created: / 11-08-2014 / 14:53:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -284,14 +284,14 @@
 prefixAlreadyWritten
     | list first |
 
-    completionView notNil ifTrue:[ 
-        list := completionView list.
-        list notEmptyOrNil ifTrue:[ 
-            first := list first.
-            (completionView list allSatisfy:[:e | e class == first class ]) ifTrue:[ 
-                ^ first stringAlreadyWritten 
-            ]
-        ]
+    completionView notNil ifTrue:[
+	list := completionView list.
+	list notEmptyOrNil ifTrue:[
+	    first := list first.
+	    (completionView list allSatisfy:[:e | e class == first class ]) ifTrue:[
+		^ first stringAlreadyWritten
+	    ]
+	]
     ].
     ^ support wordBeforeCursor string .
 
@@ -302,7 +302,7 @@
 stopCompletionProcess
     "kill any background completion process"
 
-    editView sensor flushUserEventsFor: self.     
+    editView sensor flushUserEventsFor: self.
     super stopCompletionProcess
 
     "Created: / 02-10-2013 / 15:09:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -313,9 +313,9 @@
     "called for keypress events"
 
     completionView isNil ifTrue:[
-        super updateCompletionList
+	super updateCompletionList
     ] ifFalse:[
-         self updateSelection.
+	 self updateSelection.
     ].
 
     "Created: / 27-09-2013 / 15:58:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -323,7 +323,7 @@
 !
 
 updateSelection
-    "Updates selection in completion view based on currently typed partial 
+    "Updates selection in completion view based on currently typed partial
      text. Return true if the complection window should be closed or false
      if it shall be kept open. "
 
@@ -334,7 +334,7 @@
 !
 
 updateSelectionAfterKeyPress: keyOrNil
-    "Updates selection in completion view based on currently typed partial 
+    "Updates selection in completion view based on currently typed partial
      text. Return true if the complection window should be closed or false
      if it shall be kept open.
 
@@ -348,50 +348,50 @@
     matcher1 := CompletionEngine exactMatcher.
     matcher2 := CompletionEngine inexactMatcher.
     prefix := self prefixAlreadyWritten.
-    keyOrNil isCharacter ifTrue:[ 
-        prefix := prefix , keyOrNil
+    keyOrNil isCharacter ifTrue:[
+	prefix := prefix , keyOrNil
     ].
     matches1 := list select:[:po | matcher1 value: prefix value: po stringToComplete ].
     matches1 notEmptyOrNil ifTrue:[
-        matches1 size == 1 ifTrue:[
-            | selection |
+	matches1 size == 1 ifTrue:[
+	    | selection |
 
-            selection := matches1 anElement.
-            (completeIfUnambiguous and: [(editView sensor hasKeyEventFor:editView) not]) ifTrue:[
-                self complete: selection afterKeyPress: keyOrNil.
-                ^ true
-            ] ifFalse:[ 
-                completionView selection: selection
-            ].
-        ] ifFalse:[
-            | selection |
+	    selection := matches1 anElement.
+	    (completeIfUnambiguous and: [(editView sensor hasKeyEventFor:editView) not]) ifTrue:[
+		self complete: selection afterKeyPress: keyOrNil.
+		^ true
+	    ] ifFalse:[
+		completionView selection: selection
+	    ].
+	] ifFalse:[
+	    | selection |
 
-            selection := matches1 inject: matches1 anElement into:[:mostrelevant :each |
-                each relevance > mostrelevant relevance 
-                    ifTrue:[each]
-                    ifFalse:[mostrelevant]
-            ].
-            completionView selection: selection.
-        ].
-        ^ false
+	    selection := matches1 inject: matches1 anElement into:[:mostrelevant :each |
+		each relevance > mostrelevant relevance
+		    ifTrue:[each]
+		    ifFalse:[mostrelevant]
+	    ].
+	    completionView selection: selection.
+	].
+	^ false
     ].
 
     matches2 := completionView list select:[:po | matcher2 value: prefix value: po stringToComplete ].
     matches2 notEmptyOrNil ifTrue:[
-        matches2 size == 1 ifTrue:[
-            completionView selection:  matches2 anElement.
-        ] ifFalse:[
-            | selection |
+	matches2 size == 1 ifTrue:[
+	    completionView selection:  matches2 anElement.
+	] ifFalse:[
+	    | selection |
 
-            selection := matches2 inject: matches2 anElement into:[:mostrelevant :each |
-                each relevance > mostrelevant relevance 
-                    ifTrue:[each]
-                    ifFalse:[mostrelevant]
-            ].
-            completionView selection: selection.
-        ]
+	    selection := matches2 inject: matches2 anElement into:[:mostrelevant :each |
+		each relevance > mostrelevant relevance
+		    ifTrue:[each]
+		    ifFalse:[mostrelevant]
+	    ].
+	    completionView selection: selection.
+	]
     ] ifFalse:[
-        completionView selection: nil.
+	completionView selection: nil.
     ].
     ^ false.
 
@@ -406,11 +406,11 @@
 
     self stopCompletionProcess.
     (v := completionView) notNil ifTrue:[
-        completionView := nil.
-        "/ let it close itself - avoids synchronization problems
-        v sensor
-            pushUserEvent:#value
-            for:[ v topView destroy ].
+	completionView := nil.
+	"/ let it close itself - avoids synchronization problems
+	v sensor
+	    pushUserEvent:#value
+	    for:[ v topView destroy ].
     ].
 
     "Created: / 02-10-2013 / 13:57:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -418,7 +418,7 @@
 !
 
 computeCompletions
-    "Actually compute the completions and update the completion view."  
+    "Actually compute the completions and update the completion view."
 
     | completions |
 
@@ -427,11 +427,11 @@
     "/ Wait a while to give user chance finish typing.
     "/ This also reduces CPU consumption by avoiding
     "/ useless computation
-    Delay waitForMilliseconds: 200. 
+    Delay waitForMilliseconds: 200.
 
     completions := self computeCompletionsInContext.
     completions notEmptyOrNil ifTrue:[
-        editView sensor pushUserEvent: #updateCompletions:sequence: for: self withArguments: (Array with: completions with: seqno)
+	editView sensor pushUserEvent: #updateCompletions:sequence: for: self withArguments: (Array with: completions with: seqno)
     ].
 
     "Created: / 27-09-2013 / 13:12:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -453,9 +453,9 @@
     | engine |
 
     engine := self completionEngine.
-    ^engine notNil 
-        ifTrue:[ engine complete: aCompletionContext ]
-        ifFalse:[ nil ]
+    ^engine notNil
+	ifTrue:[ engine complete: aCompletionContext ]
+	ifFalse:[ nil ]
 
     "Created: / 18-05-2014 / 11:53:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -468,39 +468,39 @@
 
 openCompletionView: list
     "Makes sure the completion view is opened and with given `list`."
-    
+
     | movePos topView x y  windowExtent screenExtent |
     "/ move the window
 
     list isEmpty ifTrue:[ ^ self ].
-    list = #( 'Busy...' ) ifTrue:[ ^ self ].  
+    list = #( 'Busy...' ) ifTrue:[ ^ self ].
 
     x := (editView xOfCol:editView cursorCol  inVisibleLine:editView cursorLine)
-            - 16"icon" - (editView widthOfString:  "support wordBeforeCursor"list first stringAlreadyWritten) - 5"magic constant".
+	    - 16"icon" - (editView widthOfString:  "support wordBeforeCursor"list first stringAlreadyWritten) - 5"magic constant".
     y := editView yOfCursor + editView font maxHeight + 3.
     movePos := (editView originRelativeTo: nil) + (x @ y).
 
     completionView isNil ifTrue:[
 
-        completionView := CompletionView new.
-        completionView completionController: self.  
-        completionView list:list.
-        completionView font: editView font.
-        topView := completionView.
+	completionView := CompletionView new.
+	completionView completionController: self.
+	completionView list:list.
+	completionView font: editView font.
+	topView := completionView.
 
-        windowExtent := completionView extent copy.
-        screenExtent := Screen current monitorBoundsAt: movePos.
-        (screenExtent height) < (movePos y + windowExtent y) ifTrue:[
-            movePos y: (movePos y - windowExtent y - editView font maxHeight - 5).
-        ].
-        topView origin:movePos.
+	windowExtent := completionView extent copy.
+	screenExtent := Screen current monitorBoundsAt: movePos.
+	(screenExtent height) < (movePos y + windowExtent y) ifTrue:[
+	    movePos y: (movePos y - windowExtent y - editView font maxHeight - 5).
+	].
+	topView origin:movePos.
 "/        topView resizeToFit.
-        self updateSelection ifFalse:[
-            topView open.
-        ].
+	self updateSelection ifFalse:[
+	    topView open.
+	].
     ] ifFalse:[
-        completionView list:list.
-        self updateSelection.
+	completionView list:list.
+	self updateSelection.
 "/        topView := completionView topView.
 "/        topView ~~ completionView ifTrue:[
 "/            topView origin:movePos.
@@ -514,7 +514,7 @@
 
 updateCompletions: completionResult sequence: sequence
     seqno == sequence ifTrue:[
-        self openCompletionView: completionResult 
+	self openCompletionView: completionResult
     ].
 
     "Created: / 03-10-2013 / 07:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/SmallSense__EditSupport.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__EditSupport.st	Tue Jan 26 21:40:42 2016 +0100
@@ -5,7 +5,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -39,7 +39,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -56,15 +56,15 @@
 
 forLanguage: aProgrammingLanguage
     aProgrammingLanguage notNil ifTrue:[
-        aProgrammingLanguage isSmalltalk ifTrue:[
-            ^ SmalltalkEditSupport new
-        ].
-        (aProgrammingLanguage askFor: #isJava) ifTrue:[    
-            ^ JavaEditSupport new
-        ].
-        (aProgrammingLanguage askFor: #isGroovy) ifTrue:[    
-            ^ GroovyEditSupport new
-        ]  
+	aProgrammingLanguage isSmalltalk ifTrue:[
+	    ^ SmalltalkEditSupport new
+	].
+	(aProgrammingLanguage askFor: #isJava) ifTrue:[
+	    ^ JavaEditSupport new
+	].
+	(aProgrammingLanguage askFor: #isGroovy) ifTrue:[
+	    ^ GroovyEditSupport new
+	]
     ].
 
     ^GenericEditSupport new.
@@ -117,7 +117,7 @@
 !
 
 completionEngineClass
-    "Returns a code completion engine class or nil, of 
+    "Returns a code completion engine class or nil, of
      no completion is supported"
 
     ^ nil
@@ -136,26 +136,26 @@
 
 !EditSupport methodsFor:'editing'!
 
-electricDeleteCharacterAtCol: col 
+electricDeleteCharacterAtCol: col
     textView deleteCharAtLine: textView cursorLine col: col
 
     "Created: / 22-01-2014 / 21:17:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricDeleteCharacterAtLine:line col: col 
+electricDeleteCharacterAtLine:line col: col
     textView deleteCharAtLine: line col: col
 
     "Created: / 22-01-2014 / 21:16:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricDo:aBlock 
+electricDo:aBlock
     textView completionSupport notNil ifTrue:[
-        (textView completionSupport)
-            stopCompletionProcess;
-            closeCompletionView.
+	(textView completionSupport)
+	    stopCompletionProcess;
+	    closeCompletionView.
     ].
     textView hasSelection ifTrue:[
-        textView undoableDo:[ textView deleteSelection ].
+	textView undoableDo:[ textView deleteSelection ].
     ].
     textView undoableDo:[ aBlock value. ].
     backspaceIsUndo := true.
@@ -164,23 +164,23 @@
     "Modified: / 22-10-2013 / 03:15:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricInsert:text 
+electricInsert:text
     self electricInsert:text advanceCursorBy:nil.
 
     "Created: / 22-10-2013 / 11:08:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricInsert:stringOrLines advanceCursorBy:offsetOrNil 
-    ^ self 
-            electricInsert:stringOrLines
-            advanceCursorBy:offsetOrNil
-            ignoreKeystrokes:nil
+electricInsert:stringOrLines advanceCursorBy:offsetOrNil
+    ^ self
+	    electricInsert:stringOrLines
+	    advanceCursorBy:offsetOrNil
+	    ignoreKeystrokes:nil
 
     "Created: / 22-10-2013 / 11:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 19-01-2014 / 20:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricInsert:stringOrLines advanceCursorBy:offsetOrNil ignoreKeystrokes:ignoreKeystrokeSequence 
+electricInsert:stringOrLines advanceCursorBy:offsetOrNil ignoreKeystrokes:ignoreKeystrokeSequence
     "Insert given stringOrLines. If offsetOrNil is not nil, then
      move cursor by `offsetOrNil` after the **begining** of
      inserted text. If `ignoreKeystrokeSequence` is not nil and not empty, then if
@@ -191,49 +191,49 @@
 
      `stringOrLines` could be either string or collection of strings (lines)
      `offsetOrNil` could be either integer (cursor is then advanced by
-            offsetOrNil characters after **begining** of inserted text)
-            or point (x,y, cursor is then advanced by x lines after current
-            line and by y characters after beggining of the inserted text
-            (if x == 0) or at set at column y (if x ~~ 0)
+	    offsetOrNil characters after **begining** of inserted text)
+	    or point (x,y, cursor is then advanced by x lines after current
+	    line and by y characters after beggining of the inserted text
+	    (if x == 0) or at set at column y (if x ~~ 0)
      `ignoreKeystrokeSequence` a sequenceable collection of keys (in a form
-            as passed to #keyPress:x:y: method."
-    
+	    as passed to #keyPress:x:y: method."
+
     | lineOffset  colOffset  newCursorCol  newCursorLine  advanceCursor |
 
     advanceCursor := false.
     offsetOrNil notNil ifTrue:[
-        lineOffset := offsetOrNil isPoint ifTrue:[
-                offsetOrNil x
-            ] ifFalse:[ 0 ].
-        colOffset := offsetOrNil isPoint ifTrue:[
-                offsetOrNil y
-            ] ifFalse:[
-                offsetOrNil
-            ].
-        newCursorLine := textView cursorLine + lineOffset.
-        newCursorCol := (lineOffset == 0 
-                ifTrue:[ textView cursorCol ]
-                ifFalse:[ 0 ]) + colOffset.
-        advanceCursor := true.
+	lineOffset := offsetOrNil isPoint ifTrue:[
+		offsetOrNil x
+	    ] ifFalse:[ 0 ].
+	colOffset := offsetOrNil isPoint ifTrue:[
+		offsetOrNil y
+	    ] ifFalse:[
+		offsetOrNil
+	    ].
+	newCursorLine := textView cursorLine + lineOffset.
+	newCursorCol := (lineOffset == 0
+		ifTrue:[ textView cursorCol ]
+		ifFalse:[ 0 ]) + colOffset.
+	advanceCursor := true.
     ].
-    self 
-        electricDo:[
-            stringOrLines isString ifTrue:[
-                "/ Simple strin
-                textView insertStringAtCursor:stringOrLines.
-            ] ifFalse:[
-                "/ C
-                textView insertLines:stringOrLines withCR:false.
-            ].
-            advanceCursor ifTrue:[
-                (textView cursorLine ~~ newCursorLine 
-                    or:[ textView cursorCol ~~ newCursorCol ]) 
-                        ifTrue:[ textView cursorLine:newCursorLine col:newCursorCol. ].
-            ].
-        ].
+    self
+	electricDo:[
+	    stringOrLines isString ifTrue:[
+		"/ Simple strin
+		textView insertStringAtCursor:stringOrLines.
+	    ] ifFalse:[
+		"/ C
+		textView insertLines:stringOrLines withCR:false.
+	    ].
+	    advanceCursor ifTrue:[
+		(textView cursorLine ~~ newCursorLine
+		    or:[ textView cursorCol ~~ newCursorCol ])
+			ifTrue:[ textView cursorLine:newCursorLine col:newCursorCol. ].
+	    ].
+	].
     ignoreKeystrokeSequence notEmptyOrNil ifTrue:[
-        ignoreKeystrokes := ignoreKeystrokeSequence.
-        ignoreKeystrokesPosition := 1.
+	ignoreKeystrokes := ignoreKeystrokeSequence.
+	ignoreKeystrokesPosition := 1.
     ].
 
     "Created: / 19-01-2014 / 20:29:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -241,35 +241,35 @@
     "Modified (format): / 22-01-2014 / 21:13:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricInsert:text ignoreKeystrokes:ignore 
-    self 
-        electricInsert:text
-        advanceCursorBy:nil
-        ignoreKeystrokes:ignore
+electricInsert:text ignoreKeystrokes:ignore
+    self
+	electricInsert:text
+	advanceCursorBy:nil
+	ignoreKeystrokes:ignore
 
     "Created: / 21-01-2014 / 23:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-electricInsertBlockOpenedBy:openText closedBy:closeText 
+electricInsertBlockOpenedBy:openText closedBy:closeText
     | indent  lines  autoIndent |
 
     textView completionSupport notNil ifTrue:[
-        (textView completionSupport)
-            stopCompletionProcess;
-            closeCompletionView.
+	(textView completionSupport)
+	    stopCompletionProcess;
+	    closeCompletionView.
     ].
     indent := self indentAtCursorLine.
     autoIndent := textView autoIndent.
     textView autoIndent:false.
     [
-        textView 
-            undoableDo:[
-                lines := Array 
-                        with:openText ? ''
-                        with:''
-                        with:((String new:indent withAll:Character space) , closeText).
-                self electricInsert:lines advanceCursorBy:1 @ (indent + 5)
-            ].
+	textView
+	    undoableDo:[
+		lines := Array
+			with:openText ? ''
+			with:''
+			with:((String new:indent withAll:Character space) , closeText).
+		self electricInsert:lines advanceCursorBy:1 @ (indent + 5)
+	    ].
     ] ensure:[ textView autoIndent:autoIndent ].
 
     "Created: / 25-07-2013 / 10:41:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -297,11 +297,11 @@
     view ~~ textView ifTrue:[ ^ false ].
 
     (self keyPressIgnored: key) ifTrue:[
-        ^ true.
+	^ true.
     ].
 
     key == Character space ifTrue:[
-        ^ self electricInsertSnippet
+	^ self electricInsertSnippet
     ].
 
     ^false
@@ -313,12 +313,12 @@
 keyPressIgnored
     "Advance position in keyPressIgnore buffer. Return true if position has been edvanced, false othwrwise"
     ignoreKeystrokes notNil ifTrue:[
-        ignoreKeystrokesPosition := ignoreKeystrokesPosition + 1.
-        ignoreKeystrokesPosition > ignoreKeystrokes size ifTrue:[
-            "/ Nil out instvars if there's no more keys to ignore.
-            ignoreKeystrokes := ignoreKeystrokesPosition := nil.
-        ].
-        ^ true.
+	ignoreKeystrokesPosition := ignoreKeystrokesPosition + 1.
+	ignoreKeystrokesPosition > ignoreKeystrokes size ifTrue:[
+	    "/ Nil out instvars if there's no more keys to ignore.
+	    ignoreKeystrokes := ignoreKeystrokesPosition := nil.
+	].
+	^ true.
     ].
     ^ false.
 
@@ -327,19 +327,19 @@
 
 keyPressIgnored: key
     ignoreKeystrokes notNil ifTrue:[
-        (ignoreKeystrokes at: ignoreKeystrokesPosition) == key ifTrue:[
-            "/ Key stroke should be ignored...
-            ignoreKeystrokesPosition := ignoreKeystrokesPosition + 1.
-            ignoreKeystrokesPosition > ignoreKeystrokes size ifTrue:[
-                "/ Nil out instvars if there's no more keys to ignore.
-                ignoreKeystrokes := ignoreKeystrokesPosition := nil.
-            ].
-            ^ true.
-        ] ifFalse:[
-            "/ Nil out instvars, user typed something else!!
-            ignoreKeystrokes := ignoreKeystrokesPosition := nil.
-            ^ false.
-        ].
+	(ignoreKeystrokes at: ignoreKeystrokesPosition) == key ifTrue:[
+	    "/ Key stroke should be ignored...
+	    ignoreKeystrokesPosition := ignoreKeystrokesPosition + 1.
+	    ignoreKeystrokesPosition > ignoreKeystrokes size ifTrue:[
+		"/ Nil out instvars if there's no more keys to ignore.
+		ignoreKeystrokes := ignoreKeystrokesPosition := nil.
+	    ].
+	    ^ true.
+	] ifFalse:[
+	    "/ Nil out instvars, user typed something else!!
+	    ignoreKeystrokes := ignoreKeystrokesPosition := nil.
+	    ^ false.
+	].
     ].
     ^ false.
 
@@ -358,12 +358,12 @@
 initializeCompletion
     | controller |
 
-    UserPreferences current smallSenseCompletionEnabled ifTrue:[
-        self completionEngineClass notNil ifTrue:[
-            controller := self completionControllerClass for: service textView.
-            controller support: self.
-            service textView completionSupport: controller.
-        ].
+    (UserPreferences current smallSenseCompletionEnabled == true) ifTrue:[
+	self completionEngineClass notNil ifTrue:[
+	    controller := self completionControllerClass for: service textView.
+	    controller support: self.
+	    service textView completionSupport: controller.
+	].
     ].
 
     "Created: / 18-05-2014 / 12:40:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -387,9 +387,9 @@
 
     line := service textView listAt: service textView cursorLine.
     ^ line isNil ifTrue:[
-        (service textView cursorCol - 1) max: 0.
+	(service textView cursorCol - 1) max: 0.
     ] ifFalse:[
-        (line indexOfNonSeparator - 1) max: 0.
+	(line indexOfNonSeparator - 1) max: 0.
     ]
 
     "Created: / 25-07-2013 / 00:13:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -410,14 +410,14 @@
     wordEnd := textView cursorCol - 1.
     wordEnd > currentLine size ifTrue:[ ^ '' ].
     wordEnd ~~ 0 ifTrue:[
-        wordStart := wordEnd.
-        [ wordStart > 0 and:[characterMatchBlock value:(currentLine at: wordStart) ] ] whileTrue:[
-            wordStart := wordStart - 1.
-        ].
-        wordStart := wordStart + 1.
-        wordStart <= wordEnd ifTrue:[
-            ^ currentLine copyFrom: wordStart to: wordEnd.
-        ].
+	wordStart := wordEnd.
+	[ wordStart > 0 and:[characterMatchBlock value:(currentLine at: wordStart) ] ] whileTrue:[
+	    wordStart := wordStart - 1.
+	].
+	wordStart := wordStart + 1.
+	wordStart <= wordEnd ifTrue:[
+	    ^ currentLine copyFrom: wordStart to: wordEnd.
+	].
     ].
     ^ ''
 
@@ -427,7 +427,7 @@
 
 !EditSupport methodsFor:'private-scanning'!
 
-scanLineAt: lineNumber 
+scanLineAt: lineNumber
     "Scans line at given line number.
 
      Returns and array of tokens, **excluding** EOF. Each token is represented
@@ -454,21 +454,21 @@
     scanner := scannerClass for: line string.
     tokenLastEndPosition := 0.
     ^ OrderedCollection streamContents:[:tokens |
-        [
-            [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
-                tokens 
-                    nextPut: token; 
-                    nextPut: (scanner tokenName notNil ifTrue:[scanner tokenName] ifFalse:[ scanner tokenValue printString ]); 
-                    nextPut: scanner tokenStartPosition;
-                    nextPut: (tokenLastEndPosition := scanner tokenEndPosition).
-            ].
-        ] on: Error do:[
-                tokens 
-                    nextPut: 'Error'; 
-                    nextPut: (line copyFrom: tokenLastEndPosition + 1 to: line size); 
-                    nextPut: tokenLastEndPosition + 1;
-                    nextPut: line size.
-        ].
+	[
+	    [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
+		tokens
+		    nextPut: token;
+		    nextPut: (scanner tokenName notNil ifTrue:[scanner tokenName] ifFalse:[ scanner tokenValue printString ]);
+		    nextPut: scanner tokenStartPosition;
+		    nextPut: (tokenLastEndPosition := scanner tokenEndPosition).
+	    ].
+	] on: Error do:[
+		tokens
+		    nextPut: 'Error';
+		    nextPut: (line copyFrom: tokenLastEndPosition + 1 to: line size);
+		    nextPut: tokenLastEndPosition + 1;
+		    nextPut: line size.
+	].
     ].
 
     "Created: / 22-10-2013 / 00:31:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/SmallSense__Manager.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__Manager.st	Tue Jan 26 21:40:42 2016 +0100
@@ -5,7 +5,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -37,7 +37,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -68,8 +68,8 @@
 flushSingleton
     "flushes the cached singleton"
 
-    Instance notNil ifTrue:[ 
-        Instance release.
+    Instance notNil ifTrue:[
+	Instance release.
     ].
     Instance := nil
 
@@ -84,7 +84,7 @@
     "returns a singleton"
 
     Instance isNil ifTrue:[
-        Instance := self basicNew initialize.
+	Instance := self basicNew initialize.
     ].
     ^ Instance.
 
@@ -106,7 +106,7 @@
     | info |
 
     accessLock critical:[
-        info := self basicInfoForClass: class.
+	info := self basicInfoForClass: class.
     ].
     ^info
 
@@ -127,9 +127,9 @@
     class isNil ifTrue:[^nil].
 
     ^classes at: class name ifAbsentPut:[
-        ClassInfo new
-            setManager: self
-            className: class name
+	ClassInfo new
+	    setManager: self
+	    className: class name
     ].
 
     "Created: / 27-11-2011 / 16:47:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -140,25 +140,25 @@
 update:what with:param from:sender
     "Invoked when an object that I depend upon sends a change notification."
 
-    UserPreferences current smallSenseBackgroundTypingEnabled ifFalse:[ ^ self ].
+    (UserPreferences current smallSenseBackgroundTypingEnabled == true) ifFalse:[ ^ self ].
 
     sender ~~ Smalltalk ifTrue:[
-        super update:what with:param from:sender.
-        ^self.
+	super update:what with:param from:sender.
+	^self.
     ].
 
     what == #methodInClass ifTrue:[
-        "/ If this is anonymous class, do not bother...        
+	"/ If this is anonymous class, do not bother...
 
-        | nm |
+	| nm |
 
-        nm := param first name.
-        (nm isSymbol and:[ Smalltalk includesKey: nm ]) ifTrue:[
-            self updateInfoForMethod: (param first >> param second).
-        ].
-        ^self.
+	nm := param first name.
+	(nm isSymbol and:[ Smalltalk includesKey: nm ]) ifTrue:[
+	    self updateInfoForMethod: (param first >> param second).
+	].
+	^self.
     ].
-    
+
 
 "/    Transcript show: 'SmallSense: Smalltalk changed: ', what , ' with: ', param printString.
 
@@ -172,13 +172,13 @@
 
     classes := Dictionary new.
     accessLock := Semaphore forMutualExclusion.
-    updater := BackgroundQueueProcessingJob 
-                    named: 'SmallSense background updater' 
-                    on: [:classOrMethod|self delayedUpdateInfoForClassOrMethod: classOrMethod].
+    updater := BackgroundQueueProcessingJob
+		    named: 'SmallSense background updater'
+		    on: [:classOrMethod|self delayedUpdateInfoForClassOrMethod: classOrMethod].
     updater priority: Processor userBackgroundPriority - 1.
 
-    UserPreferences current smallSenseEnabled ifTrue:[
-        Smalltalk addDependent: self.
+    (UserPreferences current smallSenseEnabled == true) ifTrue:[
+	Smalltalk addDependent: self.
     ].
     seqno := 0
 
@@ -192,8 +192,8 @@
     accessLock := Semaphore forMutualExclusion.
     updater stopAndRemoveAll.
 
-    UserPreferences current smallSenseEnabled ifTrue:[
-        Smalltalk removeDependent: self.
+    (UserPreferences current smallSenseEnabled == true) ifTrue:[
+	Smalltalk removeDependent: self.
     ].
 
     "Created: / 21-11-2014 / 17:36:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -208,7 +208,7 @@
     class programmingLanguage isSmalltalk ifFalse:[ ^ self ].
     info := self infoForClassOrNil: class.
     (info isNil or:[(info seqno ? 0) < (seqno - 100)]) ifTrue:[
-        updater add: class
+	updater add: class
     ].
     seqno := seqno == SmallInteger maxVal ifTrue: [1] ifFalse:[seqno + 1]
 
@@ -223,9 +223,9 @@
     method programmingLanguage isSmalltalk ifFalse:[ ^ self ].
     info := self basicInfoForClass: method mclass.
     info isNil ifTrue:[
-        updater add: method mclass
+	updater add: method mclass
     ] ifFalse:[
-        updater add: method
+	updater add: method
     ]
 
     "Created: / 28-11-2011 / 19:30:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -243,40 +243,40 @@
     info isErrorneous ifTrue:[ ^ self ].
     info seqno: seqno.
     [
-        instVarNames := class allInstVarNames.
-        instVarTypes := instVarNames collect: [:instvar | info infoForInstvar: instvar ]. 
-        "/ Check for the source stream - if none, then do not add methods (one cannot
-        "/ infer types without a source anyway  and mark the class errorneous...
-        [ 
-            sourceStream := class sourceStream.
-        ] on: Error do:[ 
-            sourceStream := nil.
-        ].
-        sourceStream isNil ifTrue:[ 
-            info errorneous: true.
-            ^ self.
-        ].
-        class methodsDo:[:mthd|updater add:mthd].
+	instVarNames := class allInstVarNames.
+	instVarTypes := instVarNames collect: [:instvar | info infoForInstvar: instvar ].
+	"/ Check for the source stream - if none, then do not add methods (one cannot
+	"/ infer types without a source anyway  and mark the class errorneous...
+	[
+	    sourceStream := class sourceStream.
+	] on: Error do:[
+	    sourceStream := nil.
+	].
+	sourceStream isNil ifTrue:[
+	    info errorneous: true.
+	    ^ self.
+	].
+	class methodsDo:[:mthd|updater add:mthd].
 
-        probe := [:instance |
-            instVarTypes withIndexDo: [:instVarType :i | 
-                instVarType union: ((Type withClass: (instance instVarAt: i) class) type trustfullness: 70). 
-            ].
-            nprobed := nprobed + 1.
-            nprobed > 100 ifTrue:[
-                "/ Probe at most 100 instancess
-                ^ self
-            ].   
-        ].
-        nprobed := 0.
-        class allInstancesDo: probe.
-        "/ Maube an abstract class?
-        nprobed < 100 ifTrue:[ 
-            class allSubInstancesDo: probe
-        ].
-    ] on: Error do:[:ex |  
-        info errorneous: true.  
-        Logger error:'Error when infering instvars for %1: %2' with: class name with: ex description
+	probe := [:instance |
+	    instVarTypes withIndexDo: [:instVarType :i |
+		instVarType union: ((Type withClass: (instance instVarAt: i) class) type trustfullness: 70).
+	    ].
+	    nprobed := nprobed + 1.
+	    nprobed > 100 ifTrue:[
+		"/ Probe at most 100 instancess
+		^ self
+	    ].
+	].
+	nprobed := 0.
+	class allInstancesDo: probe.
+	"/ Maube an abstract class?
+	nprobed < 100 ifTrue:[
+	    class allSubInstancesDo: probe
+	].
+    ] on: Error do:[:ex |
+	info errorneous: true.
+	Logger error:'Error when infering instvars for %1: %2' with: class name with: ex description
     ]
 
     "Created: / 27-11-2011 / 18:04:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -287,22 +287,22 @@
     | currentThread |
 
     currentThread := Processor activeProcess.
-    updaterThread ~~ currentThread ifTrue:[ 
-        updaterThread := currentThread.
-        updaterThread addExitAction:[ 
-            updater stopAndRemoveAll.
-        ].
+    updaterThread ~~ currentThread ifTrue:[
+	updaterThread := currentThread.
+	updaterThread addExitAction:[
+	    updater stopAndRemoveAll.
+	].
     ].
 
     [
-        classOrMethod isBehavior ifTrue:[
-           self delayedUpdateInfoForClass: classOrMethod.
-        ].
-        classOrMethod isMethod ifTrue:[
-           self delayedUpdateInfoForMethod: classOrMethod.
-        ]
+	classOrMethod isBehavior ifTrue:[
+	   self delayedUpdateInfoForClass: classOrMethod.
+	].
+	classOrMethod isMethod ifTrue:[
+	   self delayedUpdateInfoForMethod: classOrMethod.
+	]
     ] on: Error do:[:ex|
-        Logger error: 'Error when infering for %1: %2' with: classOrMethod with: ex description.
+	Logger error: 'Error when infering for %1: %2' with: classOrMethod with: ex description.
     ]
 
     "Created: / 27-11-2011 / 18:01:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -314,13 +314,13 @@
     | inferencer |
 
     [
-        method mclass isNil ifTrue:["Obsolete method" ^ self ].
-        method mclass programmingLanguage isSmalltalk ifFalse: [ ^ self ].
+	method mclass isNil ifTrue:["Obsolete method" ^ self ].
+	method mclass programmingLanguage isSmalltalk ifFalse: [ ^ self ].
     "/    Transcript showCR: 'SmallSense: updating info for: ', method printString.
-        inferencer := SmalltalkInferencer forMethod: method.
-        inferencer process.
-    ] on: Error do:[:ex |  
-        Logger error:'Error when infering for method %1: %2' with: method printString with: ex description
+	inferencer := SmalltalkInferencer forMethod: method.
+	inferencer process.
+    ] on: Error do:[:ex |
+	Logger error:'Error when infering for method %1: %2' with: method printString with: ex description
     ]
 
     "Created: / 27-11-2011 / 18:06:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/SmallSense__SmalltalkEditSupport.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__SmalltalkEditSupport.st	Tue Jan 26 21:40:42 2016 +0100
@@ -5,7 +5,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -37,7 +37,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -54,17 +54,17 @@
 
 indent: text by: level
     ^ String streamContents:[ :out |
-        | in |
+	| in |
 
-        in := text readStream.
-        [ in atEnd ] whileFalse:[
-            in peek == Character cr ifTrue:[
-                out nextPut: in next.
-                out next: level put: Character space.
-            ] ifFalse:[
-                out nextPut: in next.
-            ].
-        ].
+	in := text readStream.
+	[ in atEnd ] whileFalse:[
+	    in peek == Character cr ifTrue:[
+		out nextPut: in next.
+		out next: level put: Character space.
+	    ] ifFalse:[
+		out nextPut: in next.
+	    ].
+	].
     ]
 
     "Created: / 04-05-2014 / 23:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -73,45 +73,45 @@
 undent: stringOrStringCollection
     | lines indent tabwidth ignoreIndentOfFirstLineIfZero indentOfFirstLineIsZero |
 
-    stringOrStringCollection isStringCollection ifTrue:[ 
-        ignoreIndentOfFirstLineIfZero := false.
-        stringOrStringCollection removeLast.
-        lines := stringOrStringCollection.
+    stringOrStringCollection isStringCollection ifTrue:[
+	ignoreIndentOfFirstLineIfZero := false.
+	stringOrStringCollection removeLast.
+	lines := stringOrStringCollection.
     ] ifFalse:[
-        ignoreIndentOfFirstLineIfZero := true.
-        lines := stringOrStringCollection asStringCollection.
+	ignoreIndentOfFirstLineIfZero := true.
+	lines := stringOrStringCollection asStringCollection.
     ].
     tabwidth := (ListView userDefaultTabPositions = ListView tab4Positions) ifTrue:[ 4 ] ifFalse: [ 8 ].
     indent := nil.
     indentOfFirstLineIsZero := false.
 
     1 to: lines size do:[:lineNo |
-        | line lineIndent |
+	| line lineIndent |
 
-        line := lines at: lineNo.
-        lineIndent := line indexOfNonSeparator.
-        (lineIndent ~~ 0) ifTrue:[
-            indent isNil ifTrue:[
-                indent := ((lineIndent - 1) // tabwidth) * tabwidth.
-            ] ifFalse:[ 
-                indent := (((lineIndent - 1) // tabwidth) * tabwidth) min: indent.
-            ].
-            indent == 0 ifTrue:[
-                (lineNo == 1 and:[ignoreIndentOfFirstLineIfZero]) ifTrue:[
-                    indent := nil.
-                    indentOfFirstLineIsZero := true.
-                ] ifFalse:[
-                    ^ stringOrStringCollection isStringCollection
-                        ifTrue:[ stringOrStringCollection asStringWithoutFinalCR ]
-                        ifFalse:[ stringOrStringCollection ]
-                ].
-            ].
-        ].
+	line := lines at: lineNo.
+	lineIndent := line indexOfNonSeparator.
+	(lineIndent ~~ 0) ifTrue:[
+	    indent isNil ifTrue:[
+		indent := ((lineIndent - 1) // tabwidth) * tabwidth.
+	    ] ifFalse:[
+		indent := (((lineIndent - 1) // tabwidth) * tabwidth) min: indent.
+	    ].
+	    indent == 0 ifTrue:[
+		(lineNo == 1 and:[ignoreIndentOfFirstLineIfZero]) ifTrue:[
+		    indent := nil.
+		    indentOfFirstLineIsZero := true.
+		] ifFalse:[
+		    ^ stringOrStringCollection isStringCollection
+			ifTrue:[ stringOrStringCollection asStringWithoutFinalCR ]
+			ifFalse:[ stringOrStringCollection ]
+		].
+	    ].
+	].
     ].
-    1 to: lines size do:[:lineNr |  
-        (lineNr ~~ 1 or:[indentOfFirstLineIsZero not]) ifTrue:[ 
-            lines at: lineNr put: ((lines at: lineNr) copyFrom: indent + 1).
-        ].
+    1 to: lines size do:[:lineNr |
+	(lineNr ~~ 1 or:[indentOfFirstLineIsZero not]) ifTrue:[
+	    lines at: lineNr put: ((lines at: lineNr) copyFrom: indent + 1).
+	].
     ].
     ^ lines asStringWithoutFinalCR
 
@@ -152,22 +152,22 @@
     | ignore |
 
     (stringOrLines isString and:[ stringOrLines first == lastTypedKey0 ]) ifTrue:[
-        ignore := stringOrLines copyFrom:2.
+	ignore := stringOrLines copyFrom:2.
     ].
     ^ self
-            electricInsert:stringOrLines
-            advanceCursorBy:offsetOrNil
-            ignoreKeystrokes:ignore
+	    electricInsert:stringOrLines
+	    advanceCursorBy:offsetOrNil
+	    ignoreKeystrokes:ignore
 
     "Created: / 20-01-2014 / 09:27:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 electricInsertSnippet
     lastTypedKey0 == Character space ifTrue:[
-        ^ self electricInsertSnippetAfterSpace
+	^ self electricInsertSnippetAfterSpace
     ].
     lastTypedKey0 == $: ifTrue:[
-        ^ self electricInsertSnippetAfterDoubleColon
+	^ self electricInsertSnippetAfterDoubleColon
     ].
     ^ false.
 
@@ -179,49 +179,49 @@
 
     tokens := self scanLineAtCursor.
     tokens isEmptyOrNil ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 := tokens at:(tokens size - 3).
     lastToken0 = 'Error' ifTrue:[
-        ^ false
+	^ false
     ].
     (tokens last > service textView cursorCol) ifTrue:[
-        ^ false
+	^ false
     ].
     ((lastToken0 == #Identifier)
-        and:[ (service textView cursorCol - 1) == tokens last ])
-            ifTrue:[
-                lastValue0 := tokens at:tokens size - 2.
-                tokens size > 4 ifTrue:[
-                    (#( #do #select #reject #detect #contains #allSatisfy #anySatisfy )
-                        includes:lastValue0)
-                            ifTrue:[
-                                | collectionName  eachName  space  part1  part2 |
+	and:[ (service textView cursorCol - 1) == tokens last ])
+	    ifTrue:[
+		lastValue0 := tokens at:tokens size - 2.
+		tokens size > 4 ifTrue:[
+		    (#( #do #select #reject #detect #contains #allSatisfy #anySatisfy )
+			includes:lastValue0)
+			    ifTrue:[
+				| collectionName  eachName  space  part1  part2 |
 
-                                space := RBFormatter spaceAfterKeywordSelector ifTrue:[
-                                        ' '
-                                    ] ifFalse:[ '' ].
-                                eachName := 'each'.
-                                tokens size > 4 ifTrue:[
-                                    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
-                                        (collectionName endsWith:'ses') ifTrue:[
-                                            eachName := collectionName copyButLast:2
-                                        ] ifFalse:[
-                                            eachName := collectionName copyButLast:1
-                                        ].
-                                    ].
-                                ].
-                                part1 := ':' , space , '[:' , eachName , ' | '.
-                                part2 := ' ]'.
-                                self electricInsert:part1 , part2 advanceCursorBy:part1 size.
-                                ^ true.
-                            ].
-                    RBFormatter spaceAfterKeywordSelector ifTrue:[
-                        self electricInsert:': '.
-                        ^ true.
-                    ]
-                ].
-            ].
+				space := RBFormatter spaceAfterKeywordSelector ifTrue:[
+					' '
+				    ] ifFalse:[ '' ].
+				eachName := 'each'.
+				tokens size > 4 ifTrue:[
+				    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
+					(collectionName endsWith:'ses') ifTrue:[
+					    eachName := collectionName copyButLast:2
+					] ifFalse:[
+					    eachName := collectionName copyButLast:1
+					].
+				    ].
+				].
+				part1 := ':' , space , '[:' , eachName , ' | '.
+				part2 := ' ]'.
+				self electricInsert:part1 , part2 advanceCursorBy:part1 size.
+				^ true.
+			    ].
+		    RBFormatter spaceAfterKeywordSelector ifTrue:[
+			self electricInsert:': '.
+			^ true.
+		    ]
+		].
+	    ].
     ^ false.
 
     "Created: / 22-10-2013 / 03:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -233,39 +233,39 @@
 
     tokens := self scanLineAtCursor.
     tokens isEmptyOrNil ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 := tokens at:(tokens size - 3).
     lastToken0 = 'Error' ifTrue:[
-        ^ false
+	^ false
     ].
     (tokens last > service textView cursorCol) ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 == #Keyword ifTrue:[
-        lastValue0 := tokens at:tokens size - 2.
-        tokens size > 4 ifTrue:[
-            (#( #do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy: )
-                includes:lastValue0)
-                    ifTrue:[
-                        | collectionName  eachName  part1  part2 |
+	lastValue0 := tokens at:tokens size - 2.
+	tokens size > 4 ifTrue:[
+	    (#( #do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy: )
+		includes:lastValue0)
+		    ifTrue:[
+			| collectionName  eachName  part1  part2 |
 
-                        eachName := 'each'.
-                        tokens size > 4 ifTrue:[
-                            ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
-                                (collectionName endsWith:'ses') ifTrue:[
-                                    eachName := collectionName copyButLast:2
-                                ] ifFalse:[
-                                    eachName := collectionName copyButLast:1
-                                ].
-                            ].
-                        ].
-                        part1 := ' [:' , eachName , ' | '.
-                        part2 := ' ]'.
-                        self electricInsert:part1 , part2 advanceCursorBy:part1 size.
-                        ^ true.
-                    ].
-        ]
+			eachName := 'each'.
+			tokens size > 4 ifTrue:[
+			    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
+				(collectionName endsWith:'ses') ifTrue:[
+				    eachName := collectionName copyButLast:2
+				] ifFalse:[
+				    eachName := collectionName copyButLast:1
+				].
+			    ].
+			].
+			part1 := ' [:' , eachName , ' | '.
+			part2 := ' ]'.
+			self electricInsert:part1 , part2 advanceCursorBy:part1 size.
+			^ true.
+		    ].
+	]
     ].
     ^ false.
 
@@ -284,7 +284,7 @@
     view ~~ textView ifTrue:[ ^ false ].
 
     (self keyPressIgnored: key) ifTrue:[
-        ^ true.
+	^ true.
     ].
 
     lastTypedKey3 := lastTypedKey2.
@@ -293,49 +293,49 @@
     lastTypedKey0 := key.
 
     key == #CodeCompletion ifTrue:[
-        | controller |
+	| controller |
 
-        (controller := self textView completionSupport) notNil ifTrue:[
-            ^ controller handleKeyPress:key x:x y:y
-        ].
-        ^ false
+	(controller := self textView completionSupport) notNil ifTrue:[
+	    ^ controller handleKeyPress:key x:x y:y
+	].
+	^ false
     ].
 
     key == #BackSpace ifTrue:[
-        backspaceIsUndo ifTrue:[
-             textView undo.
-             backspaceIsUndo := false.
-             ^ true.
-        ].
+	backspaceIsUndo ifTrue:[
+	     textView undo.
+	     backspaceIsUndo := false.
+	     ^ true.
+	].
     ].
     backspaceIsUndo := false.
 
     key == #Paste ifTrue:[
-        ^ self keyPressPaste.
+	^ self keyPressPaste.
     ].
 
 
     key == $^ ifTrue:[
-        ^ self keyPressReturnToken
+	^ self keyPressReturnToken
     ].
     key == #Return ifTrue: [
-        ^ self keyPressReturn
+	^ self keyPressReturn
     ].
 
     key == $: ifTrue: [
-        ^ self keyPressDoubleColon.
+	^ self keyPressDoubleColon.
     ].
 
     key == $= ifTrue: [
-        ^ self keyPressEqual
+	^ self keyPressEqual
     ].
 
     key == Character space ifTrue:[
-        ^ self electricInsertSnippet
+	^ self electricInsertSnippet
     ].
 
     key == $[ ifTrue:[
-        ^ self keyPressOpenBracket.
+	^ self keyPressOpenBracket.
     ].
 
     ^ false.
@@ -359,8 +359,8 @@
     line size > textView cursorCol ifTrue: [ ^ false ].
     line size < (textView cursorCol - 1) ifTrue: [ ^ false ].
     (line at: textView cursorCol - 1) == $: ifTrue: [
-        self electricInsert:'= '.
-        ^ true
+	self electricInsert:'= '.
+	^ true
     ].
     ^ false
 
@@ -375,26 +375,26 @@
 
     line := textView listAt: textView cursorLine.
     line notNil ifTrue:[
-        line := line string.
-        line size > textView cursorCol ifTrue: [
-            line size downTo: textView cursorCol - 1 do:[:i |
-                (line at:i) == Character space ifFalse:[ ^ false ].
-            ]
-        ].
+	line := line string.
+	line size > textView cursorCol ifTrue: [
+	    line size downTo: textView cursorCol - 1 do:[:i |
+		(line at:i) == Character space ifFalse:[ ^ false ].
+	    ]
+	].
     ].
 
     RBFormatter spaceAfterBlockStart ifTrue:[
-        RBFormatter spaceBeforeBlockEnd ifTrue:[
-            self electricInsert:'[  ]' advanceCursorBy: 2.
-        ] ifFalse:[
-            self electricInsert:'[ ]' advanceCursorBy: 2.
-        ].
+	RBFormatter spaceBeforeBlockEnd ifTrue:[
+	    self electricInsert:'[  ]' advanceCursorBy: 2.
+	] ifFalse:[
+	    self electricInsert:'[ ]' advanceCursorBy: 2.
+	].
     ] ifFalse:[
-        RBFormatter spaceBeforeBlockEnd ifTrue:[
-            self electricInsert:'[ ]' advanceCursorBy: 1.
-        ] ifFalse:[
-            self electricInsert:'[]' advanceCursorBy: 1.
-        ].
+	RBFormatter spaceBeforeBlockEnd ifTrue:[
+	    self electricInsert:'[ ]' advanceCursorBy: 1.
+	] ifFalse:[
+	    self electricInsert:'[]' advanceCursorBy: 1.
+	].
     ].
     ^ true.
 
@@ -405,27 +405,27 @@
 keyPressPaste
     | textSelected textPasted currentLineNo currentLine currentLineIsEmpty |
 
-    UserPreferences current smallSenseSmalltalkIndentOnPasteEnabled ifFalse:[ ^ false ].
+    (UserPreferences current smallSenseSmalltalkIndentOnPasteEnabled == true) ifFalse:[ ^ false ].
 
     textView checkModificationsAllowed ifTrue:[
-        textSelected := textPasted := textView getTextSelectionOrTextSelectionFromHistory.
-        currentLineNo := textView currentLine.
-        currentLineIsEmpty := true.
-        ((currentLineNo > textView list size)
-            or:[ (currentLine := textView list at: currentLineNo) isNil
-                or:[ (currentLineIsEmpty := currentLine indexOfNonSeparator == 0) ]]) ifTrue:[
-                    | indent |
+	textSelected := textPasted := textView getTextSelectionOrTextSelectionFromHistory.
+	currentLineNo := textView currentLine.
+	currentLineIsEmpty := true.
+	((currentLineNo > textView list size)
+	    or:[ (currentLine := textView list at: currentLineNo) isNil
+		or:[ (currentLineIsEmpty := currentLine indexOfNonSeparator == 0) ]]) ifTrue:[
+		    | indent |
 
-                    currentLineIsEmpty ifTrue:[
-                        indent := textView leftIndentForLine: currentLineNo.
-                        textView setCursorCol: indent + 1.
-                    ].
-                    textPasted := self class undent: textPasted.
-                    textPasted := self class indent: textPasted by: textView cursorCol - 1.
+		    currentLineIsEmpty ifTrue:[
+			indent := textView leftIndentForLine: currentLineNo.
+			textView setCursorCol: indent + 1.
+		    ].
+		    textPasted := self class undent: textPasted.
+		    textPasted := self class indent: textPasted by: textView cursorCol - 1.
 
-                ].
+		].
 
-        textView undoablePasteOrReplace: textPasted info: nil.
+	textView undoablePasteOrReplace: textPasted info: nil.
     ].
     ^ true
 
@@ -446,15 +446,15 @@
     "/ ']', then remeber it.
     closingBracketIndex := 0.
     line size > textView cursorCol ifTrue: [
-        line size downTo: ((textView cursorCol - 1) max: 1) do:[:i |
-            (c :=line at:i) == Character space ifFalse:[
-                (c == $] and:[closingBracketIndex == 0]) ifTrue:[
-                    closingBracketIndex := i.
-                ] ifFalse:[
-                    ^ false
-                ].
-            ].
-        ]
+	line size downTo: ((textView cursorCol - 1) max: 1) do:[:i |
+	    (c :=line at:i) == Character space ifFalse:[
+		(c == $] and:[closingBracketIndex == 0]) ifTrue:[
+		    closingBracketIndex := i.
+		] ifFalse:[
+		    ^ false
+		].
+	    ].
+	]
     ].
 
     (line indexOfAny:'[|/') == 0 ifTrue:[ ^ false ].
@@ -462,11 +462,11 @@
     "/ Insert "/ at the beggining of the line if current line starts with "/
     i := currentLineIndent := line indexOfNonSeparator.
     (i ~~ 0 and:[ i < line size and:[(line at:i) == $" and:[(line at:i + 1) == $/]]]) ifTrue:[
-        "/ OK, current line contains eol-comment. Split into
-        "/ two actions so backspace deletes only the inserted '"/ ' text
-        self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
-        self electricInsert:'"/ '.
-        ^ true
+	"/ OK, current line contains eol-comment. Split into
+	"/ two actions so backspace deletes only the inserted '"/ ' text
+	self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
+	self electricInsert:'"/ '.
+	^ true
     ].
 
     "/ Now insert/reindent closing bracket ( ']' ) for block, byt only
@@ -486,53 +486,53 @@
     [ (line at: i) isSeparator and:[i > 0] ] whileTrue:[ i := i - 1 ].
     i == 0 ifTrue:[ ^ false ].
     (line at: i) == $[ ifTrue:[
-        self electricDo:[
-            closingBracketIndex ~~ 0 ifTrue:[
-                self electricDeleteCharacterAtCol: closingBracketIndex
-            ].
-            self electricInsertBlockOpenedBy:nil closedBy:'].'.
-        ].
-        ^ true
+	self electricDo:[
+	    closingBracketIndex ~~ 0 ifTrue:[
+		self electricDeleteCharacterAtCol: closingBracketIndex
+	    ].
+	    self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	].
+	^ true
     ].
     tokens := self tokensAtCursorLine.
     tokens isEmpty ifTrue:[ ^ false ].
     i := tokens size.
     t := tokens at: i.
     t == $[ ifTrue:[
-        self electricDo:[
-            closingBracketIndex ~~ 0 ifTrue:[
-                self electricDeleteCharacterAtCol: closingBracketIndex
-            ].
-            self electricInsertBlockOpenedBy:nil closedBy:'].'.
-        ].
-        ^ true
+	self electricDo:[
+	    closingBracketIndex ~~ 0 ifTrue:[
+		self electricDeleteCharacterAtCol: closingBracketIndex
+	    ].
+	    self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	].
+	^ true
     ].
     t == $| ifTrue:[
-        i := i - 1.
-        [ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].
+	i := i - 1.
+	[ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].
 
-        (i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
-            self electricDo:[
-                closingBracketIndex ~~ 0 ifTrue:[
-                    self electricDeleteCharacterAtCol: closingBracketIndex
-                ].
-                self electricInsertBlockOpenedBy:nil closedBy:'].'.
-            ].
-            ^ true
-        ].
-        i := tokens size  - 1.
-        [ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
-        (i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
-            RBFormatter emptyLineAfterTemporaries ifTrue:[
-                self electricDo:[
-                    closingBracketIndex ~~ 0 ifTrue:[
-                        self electricDeleteCharacterAtCol: closingBracketIndex
-                    ].
-                    self electricInsert:#( '' '' '' ) advanceCursorBy:2 @ currentLineIndent.
-                ].
-                ^ true
-            ]
-        ]
+	(i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
+	    self electricDo:[
+		closingBracketIndex ~~ 0 ifTrue:[
+		    self electricDeleteCharacterAtCol: closingBracketIndex
+		].
+		self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	    ].
+	    ^ true
+	].
+	i := tokens size  - 1.
+	[ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
+	(i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
+	    RBFormatter emptyLineAfterTemporaries ifTrue:[
+		self electricDo:[
+		    closingBracketIndex ~~ 0 ifTrue:[
+			self electricDeleteCharacterAtCol: closingBracketIndex
+		    ].
+		    self electricInsert:#( '' '' '' ) advanceCursorBy:2 @ currentLineIndent.
+		].
+		^ true
+	    ]
+	]
     ].
     ^ false.
 
@@ -542,10 +542,10 @@
 
 keyPressReturnToken
     RBFormatter spaceAfterReturnToken ifTrue:[
-        self electricDo:[
-            textView insertStringAtCursor:'^ '
-        ].
-        ^ true
+	self electricDo:[
+	    textView insertStringAtCursor:'^ '
+	].
+	^ true
     ].
     ^ false
 
@@ -573,9 +573,9 @@
     line isEmpty ifTrue:[ ^ #() ].
     scanner := Scanner for: line.
     ^ OrderedCollection streamContents:[:tokens |
-        [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
-            tokens nextPut: token.
-        ].
+	[ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
+	    tokens nextPut: token.
+	].
     ].
 
     "Created: / 25-07-2013 / 00:07:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/SmallSense__SmalltalkLintService.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__SmalltalkLintService.st	Tue Jan 26 21:40:42 2016 +0100
@@ -90,7 +90,7 @@
 
 isAvailable
 
-    ^UserPreferences current smallSenseEnabled
+    ^(UserPreferences current smallSenseEnabled == true)
 
     "Created: / 04-02-2012 / 22:20:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -100,9 +100,9 @@
 annotationAtLine: lineNo
     | anns |
 
-    (anns := self annotations) notNil ifTrue:[ 
-        ^ annotationsPerLine at: lineNo ifAbsent:[nil].
-        ^ anns detect:[:annotation | annotation line = lineNo] ifNone:[ nil ]
+    (anns := self annotations) notNil ifTrue:[
+	^ annotationsPerLine at: lineNo ifAbsent:[nil].
+	^ anns detect:[:annotation | annotation line = lineNo] ifNone:[ nil ]
     ].
     ^ nil
 
@@ -111,31 +111,31 @@
 !
 
 annotations
-    (highlighter notNil and:[ highlighter sequenceNumber ~~ annotationsSequenceNumber ]) ifTrue:[ 
-        | rulesToIntervalsMap annotationsPerLineMap |
+    (highlighter notNil and:[ highlighter sequenceNumber ~~ annotationsSequenceNumber ]) ifTrue:[
+	| rulesToIntervalsMap annotationsPerLineMap |
 
-        rulesToIntervalsMap := highlighter rulesToIntervalsMap.
-        rulesToIntervalsMap notNil ifTrue:[ 
-            annotationsPerLineMap := Dictionary new.
-            rulesToIntervalsMap keysAndValuesDo:[ :rule :intervals |
-                intervals do:[:interval | 
-                    | line annotation r |
+	rulesToIntervalsMap := highlighter rulesToIntervalsMap.
+	rulesToIntervalsMap notNil ifTrue:[
+	    annotationsPerLineMap := Dictionary new.
+	    rulesToIntervalsMap keysAndValuesDo:[ :rule :intervals |
+		intervals do:[:interval |
+		    | line annotation r |
 
-                    line := codeView lineOfCharacterPosition: interval first.
-                    annotation := annotationsPerLineMap at: line ifAbsentPut:[ Tools::LintAnnotation new line: line ].
-                    (r := annotation rule) notNil ifTrue:[ 
-                        r isComposite 
-                            ifTrue: [ r addRule:rule "rules add: rule" ]
-                            ifFalse:[ annotation rule: (RBCompositeLintRule rules: (OrderedCollection with: r with: rule))]
-                    ] ifFalse:[ 
-                        annotation rule: rule
-                    ].
-                ].
-            ].
-            annotationsPerLine := annotationsPerLineMap.
-            annotations := annotationsPerLineMap values sort:[ :a :b | a line < b line ].
-            annotationsSequenceNumber := highlighter sequenceNumber.
-        ]
+		    line := codeView lineOfCharacterPosition: interval first.
+		    annotation := annotationsPerLineMap at: line ifAbsentPut:[ Tools::LintAnnotation new line: line ].
+		    (r := annotation rule) notNil ifTrue:[
+			r isComposite
+			    ifTrue: [ r addRule:rule "rules add: rule" ]
+			    ifFalse:[ annotation rule: (RBCompositeLintRule rules: (OrderedCollection with: r with: rule))]
+		    ] ifFalse:[
+			annotation rule: rule
+		    ].
+		].
+	    ].
+	    annotationsPerLine := annotationsPerLineMap.
+	    annotations := annotationsPerLineMap values sort:[ :a :b | a line < b line ].
+	    annotationsSequenceNumber := highlighter sequenceNumber.
+	]
     ].
     ^annotations
 
@@ -156,8 +156,8 @@
     "return/create the 'rulesHolder' value holder (automatically generated)"
 
     rulesHolder isNil ifTrue:[
-        rulesHolder := ValueHolder new.
-        rulesHolder addDependent:self.
+	rulesHolder := ValueHolder new.
+	rulesHolder addDependent:self.
     ].
     ^ rulesHolder
 !
@@ -168,16 +168,16 @@
     |oldValue newValue|
 
     rulesHolder notNil ifTrue:[
-        oldValue := rulesHolder value.
-        rulesHolder removeDependent:self.
+	oldValue := rulesHolder value.
+	rulesHolder removeDependent:self.
     ].
     rulesHolder := something.
     rulesHolder notNil ifTrue:[
-        rulesHolder addDependent:self.
+	rulesHolder addDependent:self.
     ].
     newValue := rulesHolder value.
     oldValue ~~ newValue ifTrue:[
-        self update:#value with:newValue from:rulesHolder.
+	self update:#value with:newValue from:rulesHolder.
     ].
 ! !
 
@@ -202,25 +202,25 @@
     "Invoked when an object that I depend upon sends a change notification."
 
     changedObject == rulesHolder ifTrue:[
-        UserPreferences current smallSenseBackgroundLintEnabled ifTrue:[
-            | rulesHierarchical ruleList disabledRules |
+	(UserPreferences current smallSenseBackgroundLintEnabled == true) ifTrue:[
+	    | rulesHierarchical ruleList disabledRules |
 
-            "/xxxx
-            rulesHierarchical := rulesHolder value.
-            rulesHierarchical notNil ifTrue:[
-                "/ remove globally disabled rules
-                disabledRules := SmalltalkChecker forceDisabledRules.
-                ruleList := rulesHierarchical flattened reject:[:each| disabledRules includes: each class name].
+	    "/xxxx
+	    rulesHierarchical := rulesHolder value.
+	    rulesHierarchical notNil ifTrue:[
+		"/ remove globally disabled rules
+		disabledRules := SmalltalkChecker forceDisabledRules.
+		ruleList := rulesHierarchical flattened reject:[:each| disabledRules includes: each class name].
 
-                "/ remove user-disabled rules
-                ruleList := rulesHierarchical flattened reject:[:each| SmalltalkChecker isRuleDisabled:each class].
-                ruleList := ruleList collect:[ :e | e class new ].
-                rules := RBCompositeLintRule rules: ruleList.
-                highlighter rules: ruleList.
-                self process.
-            ].
-        ].
-        ^ self.
+		"/ remove user-disabled rules
+		ruleList := rulesHierarchical flattened reject:[:each| SmalltalkChecker isRuleDisabled:each class].
+		ruleList := ruleList collect:[ :e | e class new ].
+		rules := RBCompositeLintRule rules: ruleList.
+		highlighter rules: ruleList.
+		self process.
+	    ].
+	].
+	^ self.
     ].
 
     super update:something with:aParameter from:changedObject
@@ -230,20 +230,20 @@
 
 !SmalltalkLintService methodsFor:'event handling'!
 
-buttonPress:button x:x y:y in:view 
+buttonPress:button x:x y:y in:view
     |lineNr|
 
     rules isNil ifTrue:[
-        ^ false
+	^ false
     ].
     view == gutterView ifTrue:[
-        button == 1 ifTrue:[
-            lineNr := textView yVisibleToLineNr:y.
-            lineNr notNil ifTrue:[ 
-                ^ self showInfoWindowForLine: lineNr 
-            ].
-            ^ false.
-        ].
+	button == 1 ifTrue:[
+	    lineNr := textView yVisibleToLineNr:y.
+	    lineNr notNil ifTrue:[
+		^ self showInfoWindowForLine: lineNr
+	    ].
+	    ^ false.
+	].
     ].
     ^ false
 
@@ -254,12 +254,12 @@
 
     | browser |
 
-    UserPreferences current smallSenseBackgroundLintEnabled ifFalse:[ ^ self ].
+    (UserPreferences current smallSenseBackgroundLintEnabled == true) ifFalse:[ ^ self ].
 
     (browser := codeView browser) notNil ifTrue:[
-        browser navigationState canvasType ~~ #smallLintByRuleResultBrowserSpec ifTrue:[
-            self rulesHolder: (browser perform:#smalllintRulesOrDefaultHolder ifNotUnderstood:[browser smalllintRulesOrAllHolder])
-        ].
+	browser navigationState canvasType ~~ #smallLintByRuleResultBrowserSpec ifTrue:[
+	    self rulesHolder: (browser perform:#smalllintRulesOrDefaultHolder ifNotUnderstood:[browser smalllintRulesOrAllHolder])
+	].
     ].
 
     "Created: / 23-01-2012 / 10:43:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -281,11 +281,11 @@
 !SmalltalkLintService methodsFor:'private'!
 
 process
-    "(Re)starts the processing job. Should be called whenever a source 
+    "(Re)starts the processing job. Should be called whenever a source
      must be (re)processed."
 
     rules isNil ifTrue:[
-        ^self
+	^self
     ].
 
     ^super process.
@@ -303,12 +303,12 @@
 
     codeView codeAspect ~~ #method ifTrue:[ ^ self ].
     (lang := codeView language) isNil ifTrue: [ ^ self ].
-    lang isSmalltalk ifFalse: [ ^ self ]. 
+    lang isSmalltalk ifFalse: [ ^ self ].
     done := false.
     modified := false.
 
     cls := codeView klass.
-    cls isNil ifTrue:[^ self ].    
+    cls isNil ifTrue:[^ self ].
 
     Delay waitForMilliseconds: 200."Give user some time to write"
 
@@ -317,51 +317,51 @@
     "/ (codeView sensor hasUserEvent:#process for:self withArguments:nil) ifTrue:[^  self].
 
     (cls notNil and:[cls isObsolete]) ifTrue:[
-        cls isMeta ifTrue:[
-            cls := (Smalltalk at:cls theNonMetaclass name) class
-        ] ifFalse:[
-            cls := Smalltalk at:cls name
-        ].
+	cls isMeta ifTrue:[
+	    cls := (Smalltalk at:cls theNonMetaclass name) class
+	] ifFalse:[
+	    cls := Smalltalk at:cls name
+	].
     ].
 
     "textView" modified ifFalse:[
-        oldCodeList := textView list copy.
-        oldCodeList isEmptyOrNil ifTrue: [ ^ self ].
-        "textView" modified ifFalse:[
-            oldCodeList isNil ifFalse:[
-                oldCode := oldCodeList asStringWithoutEmphasis.
-                oldCode isEmptyOrNil ifTrue:[ ^ self ].
-                "textView" modified ifFalse:[
-                    Screen currentScreenQuerySignal answer:codeView device
-                    do:[
-                        Error handle:[:ex |
-                            | errMsg |
+	oldCodeList := textView list copy.
+	oldCodeList isEmptyOrNil ifTrue: [ ^ self ].
+	"textView" modified ifFalse:[
+	    oldCodeList isNil ifFalse:[
+		oldCode := oldCodeList asStringWithoutEmphasis.
+		oldCode isEmptyOrNil ifTrue:[ ^ self ].
+		"textView" modified ifFalse:[
+		    Screen currentScreenQuerySignal answer:codeView device
+		    do:[
+			Error handle:[:ex |
+			    | errMsg |
 
-                            Debugging == true ifTrue:[
-                                Debugging := false.    
-                                ex pass.
-                            ].
+			    Debugging == true ifTrue:[
+				Debugging := false.
+				ex pass.
+			    ].
 
 "/                            Transcript topView raiseDeiconified.
 "/                            Transcript showCR:'ParseError: ', ex description.
-                            errMsg := ex description asStringCollection first asString.
-                            self showInfo:(('Smalltalk Lint: ',errMsg) colorizeAllWith:Color red).
-                        ] do:[
-                            env := (SmallSense::SmalltalkUnacceptedMethodEnvironment onClass:cls methodSource: oldCode).
-                            rules rejectRules:[:rule | SmalltalkChecker isRuleDisabled:rule class].
+			    errMsg := ex description asStringCollection first asString.
+			    self showInfo:(('Smalltalk Lint: ',errMsg) colorizeAllWith:Color red).
+			] do:[
+			    env := (SmallSense::SmalltalkUnacceptedMethodEnvironment onClass:cls methodSource: oldCode).
+			    rules rejectRules:[:rule | SmalltalkChecker isRuleDisabled:rule class].
 "/ Transcript showCR:rules.
 "/ Transcript showCR:rules rules.
-                            SmalltalkChecker runRule: rules onEnvironment: env
-                        ].
-                        delayed ifTrue:[
-                            codeView sensor pushUserEvent:#rehighlight: for:self withArgument: true.
-                        ] ifFalse:[
-                            self rehighlight: true.
-                        ]
-                    ]
-                ]
-            ]
-        ]
+			    SmalltalkChecker runRule: rules onEnvironment: env
+			].
+			delayed ifTrue:[
+			    codeView sensor pushUserEvent:#rehighlight: for:self withArgument: true.
+			] ifFalse:[
+			    self rehighlight: true.
+			]
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Created: / 24-01-2012 / 12:44:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -373,10 +373,10 @@
 
     service := self service: SmallSense::CodeHighlightingService name.
     service isNil ifTrue:[
-        service := self service: Tools::CodeHighlightingService name
+	service := self service: Tools::CodeHighlightingService name
     ].
     service notNil ifTrue:[
-        service sourceChanged: true.
+	service sourceChanged: true.
     ]
 
     "Created: / 27-01-2012 / 17:06:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -392,11 +392,11 @@
     codeView topView beMaster.
 
     CriticsWindow new
-        rule: ann rule;
-        codeView: codeView;
-        allButOpen;
-        "/ openWindowAt: (Screen current pointerPosition - (20@20)).
-        openWindowAs:#popUp at: (Screen current pointerPosition - (20@20)).
+	rule: ann rule;
+	codeView: codeView;
+	allButOpen;
+	"/ openWindowAt: (Screen current pointerPosition - (20@20)).
+	openWindowAs:#popUp at: (Screen current pointerPosition - (20@20)).
 
     ^true
 
@@ -405,7 +405,7 @@
 
 !SmalltalkLintService methodsFor:'redrawing'!
 
-drawLine:lineNo in:view atX:x y:y width:w height:h from:startCol to:endColOrNil with:fg and:bg 
+drawLine:lineNo in:view atX:x y:y width:w height:h from:startCol to:endColOrNil with:fg and:bg
     "Called by both gutterView and textView (well, not yet) to
      allow services to draw custom things on text view.
      Ask JV what the args means if unsure (I'm lazy to document
@@ -415,12 +415,12 @@
 
     "/ ((lang := codeView language) isNil or:[lang isSmalltalk not]) ifTrue:[ ^ self ].
 
-    UserPreferences current smallSenseBackgroundLintEnabled ifFalse:[ ^ self ].
+    (UserPreferences current smallSenseBackgroundLintEnabled == true) ifFalse:[ ^ self ].
 
     annotation :=  self annotationAtLine: lineNo.
     annotation notNil ifTrue:[
-        self drawAnnotationIcon: (ToolbarIconLibrary smalllintWarning16x16)
-                atX: x y: y  width: w height: h.
+	self drawAnnotationIcon: (ToolbarIconLibrary smalllintWarning16x16)
+		atX: x y: y  width: w height: h.
     ].
 
     "Created: / 30-01-2012 / 15:11:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/extensions.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/extensions.st	Tue Jan 26 21:40:42 2016 +0100
@@ -43,7 +43,7 @@
 
 hasSmallSenseEnabled
 
-    ^UserPreferences current smallSenseEnabled
+    ^(UserPreferences current smallSenseEnabled == true)
 
 
     "