SmallSense__CompletionController.st
branchcvs_MAIN
changeset 917 c1a6a847be65
parent 285 a5640bc14376
child 926 c2a35f71f675
--- 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>"