EditTextViewCompletionSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 26 Sep 2013 19:34:24 +0200
changeset 4797 7df6faa31f57
parent 4788 8ac7fbb56cb5
child 4805 dd3fd2a4f3e9
permissions -rw-r--r--
Completion support refactored: - created an abstract superclass to ease customization of completion support. - stx_libwidg class>>classNamesAndAttributes fixed so classes are listed in load order and package checker does not report any issues.

"{ Package: 'stx:libwidg' }"

Object subclass:#EditTextViewCompletionSupport
	instanceVariableNames:'completionView completionProcess editView autoSelect'
	classVariableNames:'LastCompletions'
	poolDictionaries:''
	category:'Views-Text'
!

!EditTextViewCompletionSupport class methodsFor:'documentation'!

documentation
"
    An abstract supperclass to support completion in text views.
    Individual completion engines may create a subclass of 
    EditTextCompletionSupport and customize it.

    Basucally, they have to implement #computeCompletions

    [author:]
        Claus Gittinger

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!EditTextViewCompletionSupport class methodsFor:'instance creation'!

for:anEditView
    ^ self new editView:anEditView
! !

!EditTextViewCompletionSupport class methodsFor:'queries'!

isAbstract
    ^true

    "Created: / 26-09-2013 / 16:22:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditTextViewCompletionSupport methodsFor:'accessing'!

editView:anEditTextView
    editView := anEditTextView.
! !

!EditTextViewCompletionSupport methodsFor:'events'!

buttonPress:button x:x y:y
    self closeCompletionView.
!

editViewLostFocus
    completionView notNil ifTrue:[
        self closeCompletionView
    ]
!

handleKeyPress:key x:x y:y
    "return true, if I have eaten this keypress"

    |ch completeImmediate eatCursorLeftOrRight|

    completeImmediate := UserPreferences current immediateCodeCompletion.
    
    "/ open on CTRL- or TAB-key?
    (completionView isNil or:[completionView realized not]) ifTrue:[
        editView hasSelection ifFalse:[
            ((ch := editView characterBeforeCursor) notNil "/ i.e. not at begin of line
            and:[ ch isSeparator not ]) ifTrue:[
                (key == #Control_L or:[ key == #Ctrl or:[ key == #Control_R or:[ key == #Control]]]) ifTrue:[
                    UserPreferences current codeCompletionOnControlKey ifTrue:[
                        autoSelect := true.
                        self updateCompletionList
                    ]
                ].
                (key == #Tab) ifTrue:[
                    UserPreferences current codeCompletionOnTabKey ifTrue:[
                        autoSelect := true.
                        self updateCompletionList.
                        ^ true
                    ].
                ]
            ].
        ].
        ^ false.
    ].

    "/ key for completion view ? (careful: do not forward too many, it would disturb user's typing)
    key isCharacter ifFalse:[
        "/ forward to menu
        (completionView notNil) ifTrue:[
            eatCursorLeftOrRight := false.
"/                                    completeImmediate not
"/                                    or:[ editView sensor shiftDown 
"/                                    or:[ editView sensor ctrlDown ]].
            (key == #CursorDown 
                or:[ (key == #CursorUp)
                or:[ ((key == #CursorLeft) and:[eatCursorLeftOrRight])
                or:[ ((key == #CursorRight) and:[eatCursorLeftOrRight])
                or:[ ((key == #Return) and:[ completionView hasSelection ])
            ]]]]) ifTrue:[
                "/ only with shift - normal user typing should not interfere with completion
                true "editView sensor shiftDown" ifTrue:[
                    "/ forward to completion view
                    completionView sensor pushUserEvent:#value for:[ completionView keyPress:key x:0 y:0 ].
                    ^ true.
                ].
            ].

            (key == #Control_L or:[ key == #Control_R or:[ key == #Control or:[ key == #Ctrl ]]]) ifTrue:[
                "/ CTRL is a toggle
                self closeCompletionView.   
                ^ true.
                "/ ^ false
            ].
            (key == #Escape) ifTrue:[
                self closeCompletionView.
                ^ true  "/ EAT
            ].
            "/ shift does not close
            (key == #Shift_L or:[ key == #Shift_R or:[ key == #Shift]]) ifTrue:[
                ^ false "/ don' eat
            ].

            self closeCompletionView.
            ^ false "/ don' eat
        ].
    ].
    ^ false.
!

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

    (key == #BackSpace or:[key == #BasicBackspace]) ifTrue:[
        autoSelect := false.
        self updateCompletionList.
        ^ self
    ].

    key isCharacter ifTrue:[
        key isSeparator ifTrue:[
            self closeCompletionView
        ] ifFalse:[
            autoSelect := false.
            self updateCompletionList.
        ].
        ^ self
    ].
! !

!EditTextViewCompletionSupport methodsFor:'private'!

release
    self stopCompletionProcess.
    self closeCompletionView.
    super release
!

startCompletionProcess
    "start the code completion process in the background"

    |initialList cursorX cursorY|

    "/ terminate any previous process
    self stopCompletionProcess.

    (editView sensor hasKeyPressEventFor:nil) ifTrue:[ 
        self closeCompletionView. 
        ^ self
    ].
    ((cursorX := editView xOfCursor) isNil
    or:[ (cursorY := editView yOfCursor) isNil ]) ifTrue:[
        "/ no cursor - user is selecting, or cursor has been scrolled out of sight.
        self closeCompletionView. 
        ^ self
    ].

    initialList := #( 'busy...' ).

    self openCompletionView.

    completionProcess := 
        [
            self computeCompletions.
        ] forkAt:(Processor activePriority - 1).

    "Modified: / 26-09-2013 / 17:36:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stopCompletionProcess
    "kill any background completion process"

    |p|

    (p := completionProcess) notNil ifTrue:[
        completionProcess := nil.
        p terminate.
    ].
!

updateCompletionList
    "called for keypress events"

    self startCompletionProcess.
! !

!EditTextViewCompletionSupport methodsFor:'private-API'!

closeCompletionView
    |v|

    (v := completionView) notNil ifTrue:[
        completionView := nil.
        "/ let it close itself - avoids synchronization problems
        v sensor
            pushUserEvent:#value
            for:[ v topView destroy ]
    ].
!

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

    self subclassResponsibility

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

openCompletionView
    "Opens the completion view with an initial list. Called as soon as
     completion is initiated but completion options are not yet computed."

    self openCompletionView: (Array with: 'Busy...')

    "Created: / 26-09-2013 / 17:06:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

openCompletionView: list
    "Makes sure the completion view is opened and with given `list`."
    
    | movePos topView |
    "/ move the window
    movePos := editView device translatePoint:(editView xOfCursor @ editView yOfCursor) fromView:editView toView:nil.
    movePos := movePos - (editView viewOrigin x @ 0).
    "/ currently, we have to stay away a bit, to avoid getting the focus
    movePos := movePos + (60 @ (editView font height)).

    completionView isNil ifTrue:[
        completionView := CodeCompletionHelpMenuView new.
        completionView name:'completion'.
        completionView level:0.
        completionView list:list.
        completionView enable:false.
        completionView extent:completionView preferredExtentForContents.
        completionView font: editView font.
        topView := CodeCompletionHelpView with:completionView.
        topView origin:movePos.
        topView resizeToFit.
        "/ topView open.
    ] ifFalse:[
        completionView list:list.
        topView := completionView topView.
        topView ~~ completionView ifTrue:[
            topView origin:movePos.
            topView resizeToFit.
        ]
    ].

    "Created: / 26-09-2013 / 17:07:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditTextViewCompletionSupport class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/EditTextViewCompletionSupport.st,v 1.1 2013-09-26 17:07:20 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libwidg/EditTextViewCompletionSupport.st,v 1.1 2013-09-26 17:07:20 vrany Exp $'
! !