SmallSense__CompletionController.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 31 Mar 2014 23:43:25 +0200
changeset 185 75738108cc3f
parent 178 f98d96568600
child 187 7baeeea7d8ae
permissions -rw-r--r--
Support for Tab in code completion. Pressing Tab when code completion window is open completes longes common prefix of items matching already typed text. If no text can be completed, flashes the completion popup.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

EditTextViewCompletionSupport subclass:#CompletionController
	instanceVariableNames:'support seqno completeIfUnambiguous'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core'
!


!CompletionController class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!CompletionController class methodsFor:'testing'!

isAbstract
    ^ false

    "Created: / 17-10-2013 / 00:29:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController methodsFor:'accessing'!

support
    ^ support
!

support:anEditSupport
    support := anEditSupport.
! !

!CompletionController methodsFor:'events'!

handleKeyPress:key x:x y:y

    key == #Control_L ifTrue:[
        completionView notNil ifTrue:[
            ^ false.
        ].
    ].

    key == #CodeCompletion  ifTrue: [
        autoSelect := true.    
        self startCompletionProcess.
        ^ true
    ].

    (key == #BackSpace or:[key == #BasicBackspace]) ifTrue:[
        | c |

        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 updateSelection.
        ].
    ].
    ^ super handleKeyPress:key x:x y:y

    "Created: / 27-09-2013 / 15:38:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-03-2014 / 22:55:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

handleKeyPressTab
    "Tab has been pressed, try to complete longest common prefix"

    | prefix matching longest minlen |

    prefix := support wordBeforeCursor string.                                        
    matching := OrderedCollection new.
    minlen := SmallInteger maxVal.
    completionView list do:[:po |
        | s |

        s := po stringToComplete.
        (s startsWith: prefix) ifTrue:[
            matching add: po -> s.
            minlen := minlen min: s size.
        ].
    ].
    matching isEmpty ifTrue:[
        completionView flash.
        ^self.
    ].
    matching size == 1 ifTrue:[
        self complete: matching first key.
    ].

    longest := String streamContents:[:s |
        | i |

        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.
            ]
        ]
    ].
    longest size = prefix size ifTrue:[
        completionView flash.
        ^self.
    ].
    editView insertStringAtCursor:(longest copyFrom: prefix size + 1).

    "Created: / 31-03-2014 / 22:55:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

postKeyPress:key
    seqno := seqno + 1.
    seqno == SmallInteger maxVal ifTrue:[
        seqno := 0.
    ].

    UserPreferences current immediateCodeCompletion ifFalse:[
        "/ only update, if already open
        completionView isNil ifTrue:[^ self].
    ].

    (key == #BackSpace or:[key == #BasicBackspace]) ifTrue:[
        self closeCompletionView.
        ^ self
    ].

    key isCharacter ifTrue:[
        key isLetterOrDigit not ifTrue:[
            self closeCompletionView
        ] ifFalse:[
            | c |

            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>"
    "Modified: / 03-10-2013 / 11:01:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    "/ support := nil.
    seqno := 0.
    completeIfUnambiguous := UserPreferences current smallSenseCompleteIfUnambiguous.

    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 18-01-2014 / 23:10:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController methodsFor:'private'!

complete
    self complete: completionView selection.

    "Created: / 27-09-2013 / 15:38:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-03-2014 / 23:22:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

complete: item
    self closeCompletionView.
    item insert

    "Created: / 31-03-2014 / 23:21:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stopCompletionProcess
    "kill any background completion process"

    editView sensor flushUserEventsFor: self.     
    super stopCompletionProcess

    "Created: / 02-10-2013 / 15:09:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 11:03:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateCompletionList
    "called for keypress events"

    completionView isNil ifTrue:[
        super updateCompletionList
    ] ifFalse:[
         self updateSelection.
    ].

    "Created: / 27-09-2013 / 15:58:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-09-2013 / 00:15:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateSelection
    "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."

    | matches word |

    word := support wordBeforeCursor.
    matches := completionView list select:[:po | po stringToComplete startsWith: word ].
    matches notEmptyOrNil ifTrue:[
        matches size == 1 ifTrue:[
            completionView selection:  matches anElement.
            completeIfUnambiguous ifTrue:[
                self complete.
                ^ true
            ]
        ] ifFalse:[
            | selection |

            selection := matches inject: matches anElement into:[:mostrelevant :each |
                each relevance > mostrelevant relevance 
                    ifTrue:[each]
                    ifFalse:[mostrelevant]
            ].
            completionView selection: selection.
        ]
    ] ifFalse:[
        completionView selection: nil.
    ].
    ^ false.

    "Created: / 27-09-2013 / 16:16:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 18-01-2014 / 23:24:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController methodsFor:'private-API'!

closeCompletionView
    |v|

    self stopCompletionProcess.
    (v := completionView) notNil ifTrue:[
        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>"
    "Modified: / 04-10-2013 / 21:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

computeCompletions
    "Actually compute the completions and update the completion view."  

    | completions |

    editView sensor flushUserEventsFor: self.

    "/ Wait a while to give user chance finish typing.
    "/ This also reduces CPU consumption by avoiding
    "/ useless computation
    Delay waitForMilliseconds: 200. 
"/    self updateCompletions: support computeCompletion
    completions := support computeCompletion.
    completions notEmptyOrNil ifTrue:[
        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>"
    "Modified: / 03-10-2013 / 07:17:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

openCompletionView
    self openCompletionView: #()

    "Created: / 27-09-2013 / 16:17:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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 ].  

    x := (editView xOfCol:editView cursorCol  inVisibleLine:editView cursorLine)
            - 16"icon" - (editView widthOfString:  support wordBeforeCursor) - 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.

        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.
        ].
    ] ifFalse:[
        completionView list:list.
        self updateSelection.
"/        topView := completionView topView.
"/        topView ~~ completionView ifTrue:[
"/            topView origin:movePos.
"/            topView resizeToFit.
"/        ]
    ].

    "Created: / 27-09-2013 / 14:01:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-02-2014 / 10:13:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateCompletions: completionResult sequence: sequence
    seqno == sequence ifTrue:[
        self openCompletionView: completionResult 
    ].

    "Created: / 03-10-2013 / 07:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 11:02:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !