SmallSense__SmalltalkEditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 22 Oct 2013 17:25:26 +0100
changeset 137 12232e62cf54
parent 135 f40d2ac07f38
child 144 a43236d0c411
permissions -rw-r--r--
Fixes in electring snippets (both in API and Smalltalk snippets)

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

EditSupport subclass:#SmalltalkEditSupport
	instanceVariableNames:'lastTypedKey0 lastTypedKey1 lastTypedKey2 lastTypedKey3'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Smalltalk'
!


!SmalltalkEditSupport methodsFor:'accessing'!

language
    "superclass SmallSenseEditorSupport says that I am responsible to implement this method"

    ^SmalltalkLanguage instance

    "Modified: / 24-07-2013 / 23:46:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkEditSupport methodsFor:'accessing-classes'!

completionEngineClass
    ^ SmalltalkCompletionEngine

    "Created: / 02-10-2013 / 13:30:50 / 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."

    ^ Scanner

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

!SmalltalkEditSupport methodsFor:'editing'!

insertElectricSnippet
    lastTypedKey0 == Character space ifTrue:[
        ^ self insertElectricSnippetAfterSpace
    ].
    lastTypedKey0 == $: ifTrue:[
        ^ self insertElectricSnippetAfterDoubleColon
    ].

    ^ false.

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

insertElectricSnippetAfterDoubleColon
    | tokens lastToken0 lastValue0 |

    tokens := self scanLineAtCursor.
    tokens isEmptyOrNil ifTrue:[ ^ false ].
    lastToken0 := tokens at: (tokens size - 3).
    lastToken0 = 'Error' ifTrue:[ ^ false ].
    (tokens last > service textView cursorCol) ifTrue:[ ^ false ].

    ((lastToken0 == #Identifier) and:[(service textView cursorCol - 1) == tokens last]) ifTrue:[
        lastValue0 := tokens at: tokens size - 2.

        tokens size > 4 ifTrue:[
            (#(#do #select #reject #detect #contains #allSatisfy #anySatisfy) includes: lastValue0) ifTrue:[
                | collectionName eachName space part1 part2 |
                space := RBFormatter spaceAfterKeywordSelector ifTrue:[' '] ifFalse:[''].
                eachName := 'each'.
                tokens size > 4 ifTrue:[
                    ((collectionName := tokens at: tokens size - 6) last = $s) ifTrue:[
                        (collectionName endsWith: 'ses') ifTrue:[
                            eachName := collectionName copyButLast: 2  
                        ] ifFalse:[
                            eachName := collectionName copyButLast: 1
                        ].
                    ].
                ].
                part1 := ':', space , '[:' , eachName , ' | '.
                part2 := ' ]'.
                self insertElectric: part1 , part2 advanceCursorBy: part1 size.
                ^ true.
            ]. 
            RBFormatter spaceAfterKeywordSelector ifTrue:[
                self insertElectric: ': '.
                ^ true.
            ]
        ].

    ].
    ^ false.

    "Created: / 22-10-2013 / 03:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 12:00:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

insertElectricSnippetAfterSpace
    | tokens lastToken0 lastValue0 |

    tokens := self scanLineAtCursor.
    tokens isEmptyOrNil ifTrue:[ ^ false ].
    lastToken0 := tokens at: (tokens size - 3).
    lastToken0 = 'Error' ifTrue:[ ^ false ].
    (tokens last > service textView cursorCol) ifTrue:[ ^ false ].

    lastToken0 == #Keyword ifTrue:[
        lastValue0 := tokens at: tokens size - 2.

        tokens size > 4 ifTrue:[
            (#(#do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy:) includes: lastValue0) ifTrue:[
                | collectionName eachName part1 part2 |
                eachName := 'each'.
                tokens size > 4 ifTrue:[
                    (collectionName := (tokens at: tokens size - 6) last = $s) ifTrue:[
                        (collectionName endsWith: 'ses') ifTrue:[
                            eachName := collectionName copyButLast: 2  
                        ] ifFalse:[
                            eachName := collectionName copyButLast: 1
                        ].
                    ].
                ].
                part1 := ' [:' , eachName , ' | '.
                part2 := ' ]'.
                self insertElectric: part1 , part2 advanceCursorBy: part1 size.
                ^ true.
            ]. 
        ]
    ].
    ^ false.

    "Created: / 22-10-2013 / 03:00:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 12:00:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

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

    view ~~ textView ifTrue:[ ^ false ].

    lastTypedKey3 := lastTypedKey2.
    lastTypedKey2 := lastTypedKey1.
    lastTypedKey1 := lastTypedKey0.
    lastTypedKey0 := key.

    key == #BackSpace ifTrue:[
        backspaceIsUndo ifTrue:[
             textView undo.
             backspaceIsUndo := false.
             ^ true.
        ].
    ].
    backspaceIsUndo := false.


    key == $^ ifTrue:[
        ^ self keyPressReturnToken
    ].
    key == #Return ifTrue: [
        ^ self keyPressReturn
    ].

    key == $: ifTrue: [
        ^ self keyPressDoubleColon.
    ].

    key == $= ifTrue: [
        ^ self keyPressEqual
    ].

    ^ super keyPress: key x:x y:y in: view

    "Created: / 07-03-2010 / 09:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 11:09:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressDoubleColon
    ^ self insertElectricSnippetAfterDoubleColon

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

keyPressEqual
    | line |

    line := textView listAt:textView cursorLine.
    line isNil ifTrue:[ ^ false ].
    line := line string.
    line size > textView cursorCol ifTrue: [ ^ false ].
    line size < (textView cursorCol - 1) ifTrue: [ ^ false ].
    (line at: textView cursorCol - 1) == $: ifTrue: [
        self insertElectric:'= '.  
        ^ true
    ].
    ^ false

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

keyPressReturn
    | line tokens i t |

    line := textView listAt: textView cursorLine.
    line isNil ifTrue:[ ^ false ].
    line := line string.
    line size > textView cursorCol ifTrue: [ ^ false ].
    (line indexOfAny:'[|/') == 0 ifTrue:[ ^ false ].

    "/ Insert "/ at the beggining of the line if current line starts with "/
    i := line indexOfNonSeparator.
    (i ~~ 0 and:[ i < line size and:[(line at:i) == $" and:[(line at:i + 1) == $/]]]) ifTrue:[
        "/ OK, current line contains eol-comment
        self insertDo:[
             textView insertCharAtCursor: Character cr. 
        ].
        self insertDo:[
            textView insertStringAtCursor: '"/ '
        ].
        ^ true   
    ].

    ('[|' includes: lastTypedKey1) ifFalse:[ ^ false ].
    i := line size.
    [ (line at: i) isSeparator and:[i > 0] ] whileTrue:[ i := i - 1 ].
    i == 0 ifTrue:[ ^ false ].
    (line at: i) == $[ ifTrue:[
        self insertElectricBlockOpenedBy: nil closedBy: '].'.
        ^ true
    ].
    tokens := self tokensAtCursorLine.
    tokens isEmpty ifTrue:[ ^ false ].
    i := tokens size.
    t := tokens at: i.
    t == $[ ifTrue:[
        self insertElectricBlockOpenedBy: nil closedBy: '].'.
        ^ true
    ].
    t == $| ifTrue:[
        i := i - 1.
        [ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].

        (i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
            self insertElectricBlockOpenedBy: nil closedBy: '].'.
            ^ true
        ].
        i := tokens size  - 1.
        [ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
        (i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
            RBFormatter emptyLineAfterTemporaries ifTrue:[
                textView undoableDo:[
                    textView insertStringAtCursor: (Character cr asString , Character cr , Character cr)
                ].
                ^ true
            ]
        ]
    ].
    ^ false.

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

keyPressReturnToken
    RBFormatter spaceAfterReturnToken ifTrue:[
        self insertDo:[ 
            textView insertStringAtCursor:'^ ' 
        ].
        ^ true
    ].
    ^ false

    "Created: / 24-07-2013 / 23:59:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2013 / 23:20:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkEditSupport methodsFor:'initialization'!

initializeForService: anEditService    
    super initializeForService: anEditService.
    service textView autoIndent:true.

    "Created: / 27-09-2013 / 13:22:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 17:44:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkEditSupport methodsFor:'private'!

tokensAtCursorLine
    | scanner token |

    scanner := Scanner for: (service textView listAt: service textView cursorLine) string.
    ^ OrderedCollection streamContents:[:tokens |
        [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
            tokens nextPut: token.
        ].
    ].

    "Created: / 25-07-2013 / 00:07:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkEditSupport class methodsFor:'documentation'!

version_HG

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