SmallSense__EditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 20 Jan 2014 09:34:34 +0000
changeset 155 d792aed09149
parent 144 a43236d0c411
child 156 9b02027653ed
permissions -rw-r--r--
Initial support for ignoring keystrokes to avoid duplicate text when electric insert is active.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

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


!EditSupport class methodsFor:'instance creation'!

forLanguage: aProgrammingLanguage
    aProgrammingLanguage notNil ifTrue:[
        aProgrammingLanguage isSmalltalk ifTrue:[
            ^ SmalltalkEditSupport new
        ].
        (aProgrammingLanguage askFor: #isJava) ifTrue:[    
            ^ JavaEditSupport new
        ].
        (aProgrammingLanguage askFor: #isGroovy) ifTrue:[    
            ^ GroovyEditSupport new
        ]  
    ].

    ^GenericEditSupport new.

    "Created: / 24-07-2013 / 23:20:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-10-2013 / 08:41:09 / 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:'accessing-classes'!

completionEngineClass
    "Returns a code completion engine class or nil, of 
     no completion is supported"

    ^ nil

    "Created: / 03-10-2013 / 17:43:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

scannerClass
    "Returns a class to use for scanning lines. If nil, scanning is
     not supported and scanLine* methods will return an empty array."

    ^ nil

    "Created: / 22-10-2013 / 00:33:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'editing'!

insertDo: aBlock
    textView completionSupport notNil ifTrue:[
        textView completionSupport 
            stopCompletionProcess;
            closeCompletionView.
    ].  
    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>"
    "Modified: / 22-10-2013 / 03:15:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectric: text
    self insertElectric:text advanceCursorBy:nil.

    "Created: / 22-10-2013 / 11:08:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectric:stringOrLines advanceCursorBy:offsetOrNil 
    ^ self insertElectric:stringOrLines advanceCursorBy:offsetOrNil ignoreKeystrokes: nil

    "Created: / 22-10-2013 / 11:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-01-2014 / 20:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectric:stringOrLines advanceCursorBy:offsetOrNil ignoreKeystrokes: ignoreKeystrokeSequence 
    "Insert given stringOrLines. If offsetOrNil is not nil, then
     move cursor by `offsetOrNil` after the **begining** of
     inserted text. If `ignoreKeystrokeSequence` is not nil and not empty, then if
     subsequent key strokes are ignored (i.e, does nothing) if matches
     the given sequence. This is used to avoid duplication if user is not
     aware of electric insertion and types whole text that has been
     (electrically) inserted).

     `stringOrLines` could be either string or collection of strings (lines)
     `offsetOrNil` could be either integer (cursor is then advanced by
            offsetOrNil characters after **begining** of inserted text)
            or point (x,y, cursor is then advanced by x lines after current
            line and by y characters after beggining of the inserted text
            (if x == 0) or at set at column y (if x ~~ 0)
     `ignoreKeystrokeSequence` a sequenceable collection of keys (in a form
            as passed to #keyPress:x:y: method.
    "

    | lineOffset colOffset newCursorCol newCursorLine advanceCursor |

    advanceCursor := false.
    offsetOrNil notNil ifTrue:[
        lineOffset := offsetOrNil isPoint ifTrue:[offsetOrNil x] ifFalse:[0].
        colOffset := offsetOrNil isPoint ifTrue:[offsetOrNil y] ifFalse:[offsetOrNil].

        newCursorLine := textView cursorLine + lineOffset.
        newCursorCol := (lineOffset == 0 ifTrue:[textView cursorCol] ifFalse:[0]) + colOffset.

        advanceCursor := true.
    ].

    
    self 
        insertDo:[
            stringOrLines isString ifTrue:[
                "/ Simple string...    
                textView insertStringAtCursor:stringOrLines.
            ] ifFalse:[
                "/ Couple lines...
                textView 
                    insertLines: stringOrLines
                    withCR: false.   
            ].
            advanceCursor ifTrue:[
                (textView cursorLine ~~ newCursorLine or:[textView cursorCol ~~ newCursorCol]) ifTrue:[
                    textView cursorLine: newCursorLine col: newCursorCol.
                ].
            ].
        ].
    ignoreKeystrokeSequence notEmptyOrNil ifTrue:[
        ignoreKeystrokes := ignoreKeystrokeSequence.
        ignoreKeystrokesPosition := 1.
    ].

    "Created: / 19-01-2014 / 20:29:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-01-2014 / 09:24:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectricBlockOpenedBy: openText closedBy: closeText
    | indent lines autoIndent |

    textView completionSupport notNil ifTrue:[
        textView completionSupport 
            stopCompletionProcess;
            closeCompletionView.
    ].   

    indent := self indentAtCursorLine.

    autoIndent :=  textView autoIndent.
    textView autoIndent: false. 
    [
        textView undoableDo:[
            lines := Array 
                        with: openText ? ''
                        with: '' 
                        with: ((String new:indent withAll:Character space) , closeText ).
            self insertElectric: lines advanceCursorBy:  1 @ (indent + 5)

    "/        textView insertStringAtCursor: (openText ? '') , Character cr , Character cr,  , closeText , Character cr.
    "/        line := textView cursorLine - 1.
    "/        col := textView cursorCol  + 3.
    "/        textView cursorLine: line col: col.
        ].
    ] ensure:[
        textView autoIndent: autoIndent 
    ].

    "Created: / 25-07-2013 / 10:41:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-11-2013 / 12:29:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectricSnippet    
    ^ false

    "Created: / 22-10-2013 / 01:54:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'event handling'!

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.

     IMPORTANT: Never ever call `^ super keyPress: key x:x y:y in: view`,
     as keyPresIgnore... advances position and calling keyPressIgnore here
     and calling super would advance it twice!!
     "

    view ~~ textView ifTrue:[ ^ false ].

    (self keyPressIgnored: key) ifTrue:[
        ^ true.
    ].

    key == Character space ifTrue:[
        ^ self insertElectricSnippet
    ].

    ^false

    "Created: / 24-07-2013 / 23:31:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 20-01-2014 / 09:20:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressIgnored: key
    "raise an error: this method should be implemented (TODO)"

    ignoreKeystrokes notNil ifTrue:[
        ^ (ignoreKeystrokes at: ignoreKeystrokesPosition) == key ifTrue:[
            "/ Key stroke should be ignored...
            ignoreKeystrokesPosition := ignoreKeystrokesPosition + 1.
            ignoreKeystrokesPosition > ignoreKeystrokes size ifTrue:[
                "/ Nil out instvars if there's no more keys to ignore.
                ignoreKeystrokes := ignoreKeystrokesPosition := nil.
            ].
            true.
        ] ifFalse:[
            "/ Nil out instvars, user typed something else!!
            ignoreKeystrokes := ignoreKeystrokesPosition := nil.
            false.
        ].
    ].
    ^ false.

    "Created: / 20-01-2014 / 09:11:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressSpace
    ^ self insertElectricSnippet

    "Created: / 22-10-2013 / 01:43:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'initialization'!

initializeCompletion
    self completionEngineClass  notNil ifTrue:[
        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>"
    "Modified: / 03-10-2013 / 17:44:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

    "Created: / 27-09-2013 / 13:19:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 17:44:15 / 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) max: 0.
    ] ifFalse:[
        (line indexOfNonSeparator - 1) max: 0.
    ]

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

wordBeforeCursor
    | currentLine wordStart wordEnd |

    currentLine := textView list at: textView cursorLine.
    currentLine isNil ifTrue:[ ^ '' ].
    wordEnd := textView cursorCol - 1.
    wordEnd > currentLine size ifTrue:[ ^ '' ].
    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>"
    "Modified: / 17-10-2013 / 00:48:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'private-completion'!

computeCompletion
    | completionEngineClass codeView result |

    completionEngineClass := self completionEngineClass.
    completionEngineClass isNil ifTrue: [ ^ nil ].

    codeView := service codeView.
    UserInformation 
        handle: [:ex | 
            codeView showInfo: (ex messageText).
            ex proceed.
        ]
        do: [
            result := completionEngineClass new completeFor: codeView 
        ].
    ^ result.

    "Created: / 27-09-2013 / 13:21:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2013 / 13:31:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport methodsFor:'private-scanning'!

scanLineAt: lineNumber 
    "Scans line at given line number.

     Returns and array of tokens, **excluding** EOF. Each token is represented
     by four subsequent items in the array: token type, token value, start position, end position.
     Thus, returned array size is always multiple of 4."

    ^ self scanLineAt: lineNumber using: self scannerClass

    "Created: / 22-10-2013 / 00:34:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

scanLineAt: lineNumber using: scannerClass
    "Scans line at given line number using given scanner class.

     Returns and array of tokens, **excluding** EOF. Each token is represented
     by four subsequent items in the array: token type, token value, start position, end position.
     Thus, returned array size is always multiple of 4."

    | line scanner token tokenLastEndPosition |

    scannerClass isNil ifTrue:[ ^ #() ].
    line := (service textView listAt: service textView cursorLine).
    line isNil ifTrue:[ ^ #() ].
    scanner := scannerClass for: line string.
    tokenLastEndPosition := 0.
    ^ OrderedCollection streamContents:[:tokens |
        [
            [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
                tokens 
                    nextPut: token; 
                    nextPut: (scanner tokenName notNil ifTrue:[scanner tokenName] ifFalse:[ scanner tokenValue printString ]); 
                    nextPut: scanner tokenStartPosition;
                    nextPut: (tokenLastEndPosition := scanner tokenEndPosition).
            ].
        ] on: Error do:[
                tokens 
                    nextPut: 'Error'; 
                    nextPut: (line copyFrom: tokenLastEndPosition + 1 to: line size); 
                    nextPut: tokenLastEndPosition + 1;
                    nextPut: line size.
        ].
    ].

    "Created: / 22-10-2013 / 00:31:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 12:01:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

scanLineAtCursor
    "Scans current cursor line.

     Returns and array of tokens, **excluding** EOF. Each token is represented
     by four subsequent items in the array: token type, token value, start position, end position.
     Thus, returned array size is always multiple of 4."

    ^ self scanLineAt: service codeView textView cursorLine using: self scannerClass

    "Created: / 22-10-2013 / 00:34:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditSupport class methodsFor:'documentation'!

version_HG

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