SmallSense__EditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 27 Sep 2013 22:39:18 +0100
changeset 108 71471dc81e77
parent 100 6d2fb43e661b
child 109 59448a46a48f
permissions -rw-r--r--
Completion refactoring (part 1) - completion handling refactored to use new EditTextViewCompletionSupport - introduced new, hand-written CompletionView

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#EditSupport
	instanceVariableNames:'service textView backspaceIsUndo completionController'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core-Services'
!

EditTextViewCompletionSupport subclass:#CompletionController
	instanceVariableNames:'support'
	classVariableNames:''
	poolDictionaries:''
	privateIn:EditSupport
!

!EditSupport class methodsFor:'instance creation'!

forLanguage: aProgrammingLanguage
    aProgrammingLanguage notNil ifTrue:[
        aProgrammingLanguage isSmalltalk ifTrue:[
            ^ SmalltalkEditSupport new
        ].
        aProgrammingLanguage isJava ifTrue:[    
            ^ JavaEditSupport new
        ]
    ].

    ^GenericEditSupport new.

    "Created: / 24-07-2013 / 23:20:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2013 / 02:06:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'accessing'!

language
    ^ self subclassResponsibility.

    "Created: / 24-07-2013 / 23:44:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

service
    ^ service
! !

!EditSupport methodsFor:'editing'!

insertDo: aBlock
    textView hasSelection ifTrue:[
        textView undoableDo:[
            textView deleteSelection
        ].
    ].
    textView undoableDo: [
         aBlock value.
    ].
    backspaceIsUndo := true.

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

insertElectricBlockOpenedBy: openText closedBy: closeText
    | line col indent |

    indent := self indentAtCursorLine.

    textView undoableDo:[
        textView insertStringAtCursor: (openText ? '') , Character cr , Character cr, (String new:indent withAll:Character space) , closeText , Character cr.
        line := textView cursorLine - 1.
        col := textView cursorCol  + 3.
        textView cursorLine: line col: col.
    ].

    "Created: / 25-07-2013 / 10:41:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2013 / 02:15:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'event handling'!

doKeyPressComplete
    completionController notNil ifTrue:[
        completionController startCompletionProcess
    ].

    "Created: / 04-08-2013 / 02:33:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-09-2013 / 13:25:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress: key x:x y:y in: view

    "Handles an event in given view (a subview of codeView).
     If the method returns true, the event will not be processed
     by the view."

    key == #CodeCompletion  ifTrue: [
        self doKeyPressComplete. 
        ^ true.
    ].
    ^false

    "Created: / 24-07-2013 / 23:31:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-09-2013 / 13:15:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'initialization'!

initializeCompletion
    completionController := CompletionController for: service textView.
    completionController support: self.
    service textView completionSupport: completionController.

    "Created: / 27-09-2013 / 13:20:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeForService:aSmallSenseService
    service := aSmallSenseService.
    textView := aSmallSenseService textView.
    backspaceIsUndo := false.

    "Created: / 27-09-2013 / 13:19:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'private'!

indentAtCursorLine
    | line |

    line := service textView listAt: service textView cursorLine.
    ^ line isNil ifTrue:[
        service textView cursorCol - 1.
    ] ifFalse:[
        line indexOfNonSeparator - 1.
    ]

    "Created: / 25-07-2013 / 00:13:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2013 / 02:13:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

wordBeforeCursor
    | currentLine wordStart wordEnd |
    currentLine := textView list at: textView cursorLine.
    wordEnd := textView cursorCol - 1.
    wordEnd ~~ 0 ifTrue:[
        wordStart := wordEnd.
        [ wordStart > 0 and:[(currentLine at: wordStart) isAlphaNumeric] ] whileTrue:[
            wordStart := wordStart - 1.
        ].
        wordStart := wordStart + 1.
        wordStart <= wordEnd ifTrue:[
            ^ currentLine copyFrom: wordStart to: wordEnd.
        ].
    ].
    ^ ''

    "Created: / 27-09-2013 / 15:53:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'private-completion'!

computeCompletion
    "Compute completion and return a CompletionResult"

    self subclassResponsibility

    "Created: / 27-09-2013 / 13:14:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertCompletion: item
    "Insert given completion item at cursor position"

    | po stringToComplete stringAlreadyWritten stringToInsert |

    po := item.
    stringToComplete := po stringToComplete.
    stringAlreadyWritten := self wordBeforeCursor.
    stringToInsert := stringToComplete copyFrom: (stringAlreadyWritten size + 1).
    textView isCodeView2 ifTrue:[textView := textView textView].
    textView undoableDo:[
        (stringToComplete startsWith: stringAlreadyWritten) ifTrue:[
            textView insertStringAtCursor: stringToInsert.
        ] ifFalse:[
            | startCol endCol |

            endCol := textView cursorCol - 1.
            startCol := textView cursorCol - stringAlreadyWritten size.
            textView insertStringAtCursor: stringToComplete.
            textView deleteFromLine:textView cursorLine col: startCol toLine:textView cursorLine col:endCol.
            textView cursorCol: startCol + stringToComplete size.
        ].
    ].
    textView cursorCol: textView cursorCol - stringToComplete size + po cursorColumnAfterComplete.

    "Created: / 27-09-2013 / 15:40:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport::CompletionController methodsFor:'accessing'!

support
    ^ support
!

support:anEditSupport
    support := anEditSupport.
! !

!EditSupport::CompletionController methodsFor:'events'!

handleKeyPress:key x:x y:y

    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>"
! !

!EditSupport::CompletionController methodsFor:'private'!

complete
    support insertCompletion: completionView selection.
    self closeCompletionView.

    "Created: / 27-09-2013 / 15:38:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateCompletionList
    "called for keypress events"

    completionView isNil ifTrue:[
        super updateCompletionList
    ].

    "Created: / 27-09-2013 / 15:58:01 / 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:[:shortest :each |
            each stringToComplete size < shortest stringToComplete size 
                ifTrue:[each]
                ifFalse:[shortest]
        ]).
    ] ifFalse:[
        completionView selection: nil.
    ]

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

!EditSupport::CompletionController methodsFor:'private-API'!

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

    | completions |

    completions := support computeCompletion.
    completions notEmptyOrNil ifTrue:[
        editView sensor pushUserEvent: #updateCompletions: for: self withArgument: completions.
    ].

    "Created: / 27-09-2013 / 13:12:11 / 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|
    "/ move the window

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

updateCompletions: completionResult
    self openCompletionView: completionResult

    "Created: / 27-09-2013 / 13:52:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !