SmallSenseSmalltalkEditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 25 Jul 2013 11:34:26 +0100
changeset 39 748389119d0a
child 40 85eaf579889b
permissions -rw-r--r--
Initial support for per-language edit support. Some work on Smalltalk edit support, namely on electric blocks. Works fine, but need more work to make it usable but not too intrusive.

"{ Package: 'jv:smallsense' }"

SmallSenseEditSupport subclass:#SmallSenseSmalltalkEditSupport
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Interface'
!

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

!SmallSenseSmalltalkEditSupport methodsFor:'editing'!

insertElectricBlockOpenedBy: openText closedBy: closeText
    | line col |

    textView undoableDo:[
        textView insertStringAtCursor: (openText ? '') , Character cr , Character cr, 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>"
! !

!SmallSenseSmalltalkEditSupport 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 ifFalse:[ ^ false ].

    key == #'CodeCompletion'  ifTrue: [
        self complete. 
        ^ true
    ].
    key == $^ ifTrue:[
        ^ self keyPressReturnToken
    ].
    key == #Return ifTrue:[
        ^ self keyPressReturn
    ]. 

    ^ false.

    "Created: / 07-03-2010 / 09:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-07-2013 / 00:12:00 / 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 ].
    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.
    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 ].
        (tokens at: i) == $[ ifTrue:[
            self insertElectricBlockOpenedBy: nil closedBy: ']'.
            ^ true
        ].

    ].
    ^ false.

    "Created: / 25-07-2013 / 00:02:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 25-07-2013 / 11:16:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

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

!SmallSenseSmalltalkEditSupport methodsFor:'private'!

complete
    |cls 
"/     crsrPos interval node checkedNode
"/     char start stop selectorSoFar matchingSelectors
    codeView |

    codeView := service codeView.

    cls := codeView classHolder value.
    cls isNil ifTrue:[
        codeView showInfo:'No class'.
        ^ self.
    ].
    UserInformation handle:[:ex |
        codeView showInfo:(ex messageText).
        ex proceed.
    ] do:[
        codeView withWaitCursorDo:[
            codeView textView keyRelease: #Control_L x:0 y:0.
            SmallSenseCompletionWindow openForView: codeView class: cls.
        ]
    ].
    ^ self.

"/
"/    interval := self selectedInterval.
"/    interval isEmpty ifTrue:[
"/        crsrPos := codeView characterPositionOfCursor - 1.
"/        char := codeView characterUnderCursor.
"/        [crsrPos > 1 and:[char isSeparator or:['.' includes:char]]] whileTrue:[
"/            crsrPos := crsrPos - 1.
"/            char := codeView characterAtCharacterPosition:crsrPos.
"/        ].
"/        interval := crsrPos to:crsrPos.
"/    ].
"/
"/    node := self findNodeForInterval:interval allowErrors:true.
"/    [node isNil] whileTrue:[
"/        "/ expand to the left ...
"/        interval start > 1 ifFalse:[
"/            self showInfo:'No parseNode found'.
"/            ^ self.
"/        ].
"/        interval start:(interval start - 1).
"/        node := self findNodeForInterval:interval allowErrors:true.
"/    ].
"/
"/    node isVariable ifTrue:[
"/        self codeCompletionForVariable:node inClass:cls.
"/        ^ self.
"/    ].
"/
"/    checkedNode := node.
"/    [checkedNode notNil] whileTrue:[
"/        checkedNode isMessage ifTrue:[
"/            self codeCompletionForMessage:checkedNode inClass:cls.
"/            ^ self
"/        ].
"/        checkedNode isMethod ifTrue:[
"/            self codeCompletionForMethod:checkedNode inClass:cls.
"/            ^ self.
"/        ].
"/        checkedNode := checkedNode parent.
"/    ].
"/
"/    self showInfo:'Node is neither variable nor message.'.

    "Modified: / 04-07-2006 / 18:48:26 / fm"
    "Modified: / 20-11-2006 / 12:30:59 / cg"
    "Created: / 07-03-2010 / 09:37:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-07-2013 / 23:29:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

indentAtCursorLine
    ^ (service textView listAt: service textView cursorLine) indexOfNonSeparator

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

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