SmallSense__EditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 22 Oct 2013 03:29:26 +0100
changeset 134 e34ee6ceb7c8
parent 132 7c23c51d2cfd
child 135 f40d2ac07f38
permissions -rw-r--r--
Initial support for "electric snippets". Electric snippets are hard coded for now. Only following is supported now: - Smalltalk - select:/detect:/reject:/... -> ...: [:each| ... ]. - Java - catch/synchronized/if/while... -> ... ( ) { ... } - for - try

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#EditSupport
	instanceVariableNames:'service textView backspaceIsUndo completionController snippets'
	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>"
!

insertElectricBlockOpenedBy: openText closedBy: closeText
    | line col indent |

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

    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: / 22-10-2013 / 03:16:52 / 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."

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

    ^false

    "Created: / 24-07-2013 / 23:31:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 01:56:45 / 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.
    ] 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.
    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; 
                    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 / 02:16:23 / 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> $'
! !