SmallSense__CompletionController.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 18 Jan 2014 22:56:44 +0000
changeset 153 b04d591c8788
parent 143 038fdc3940f3
child 154 b96fbde91144
permissions -rw-r--r--
Added relevance value to completion item. Pre-select the most relevant item in complection view. The relevance value says how much likely the item is what user wants to complete. It's complection engine's responsibility to fill in that value. Currently, only Smalltalk engine uses it to prefer instance variables already used in edited method.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

EditTextViewCompletionSupport subclass:#CompletionController
	instanceVariableNames:'support seqno'
	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 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: / 30-09-2013 / 15:00:49 / 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.

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

    "Modified: / 03-10-2013 / 07:11:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionController methodsFor:'private'!

complete
    | selection |

    selection := completionView selection.
    self closeCompletionView.
    selection insert

    "Created: / 27-09-2013 / 15:38:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-10-2013 / 01:08:31 / 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

    | matches word |

    word := support wordBeforeCursor.
    matches := completionView list select:[:po | po stringToComplete startsWith: word ].
    matches notEmptyOrNil ifTrue:[
        completionView selection: (matches inject: matches anElement into:[:mostrelevant :each |
            each relevance > mostrelevant relevance 
                ifTrue:[each]
                ifFalse:[mostrelevant]
        ]).
    ] ifFalse:[
        completionView selection: nil.
    ].

    "Created: / 27-09-2013 / 16:16:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-01-2014 / 22:51:38 / 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 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.
        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: / 18-01-2014 / 22:23:26 / 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> $'
! !