SmallSense__JavaEditSupport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 13 Aug 2014 10:28:35 +0100
changeset 278 696843cd1f9d
parent 252 feba6ee5c814
child 279 1dcaf8e06968
permissions -rw-r--r--
Revamp of Java completion engine - use JDT's CompletionParser to parse source. Use CompletionParser from Eclipse to parse incomplete, edited tree and find node to complete. It also runs a Resolver to resolve types and create type bindings, so when JavaCompletionParser is called back all type informations should be in place. Now it supports completion for types and variables. More will come in next commits.

"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
"{ Package: 'stx:goodies/smallsense' }"

"{ NameSpace: SmallSense }"

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

!JavaEditSupport class methodsFor:'documentation'!

copyright
"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
! !

!JavaEditSupport methodsFor:'accessing'!

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

    | javaLanguageClass |

    javaLanguageClass := Smalltalk at:#JavaLanguage.
    ^ javaLanguageClass notNil ifTrue:[ javaLanguageClass instance ] ifFalse: [ nil ].

    "Modified: / 04-10-2013 / 08:42:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaEditSupport methodsFor:'accessing-classes'!

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

    OperatingSystem getLoginName = 'jv' ifTrue:[
        ^ SmallSense::JavaCompletionEngine
    ].
    ^ SmallSense::JavaCompletionEngineSimple

    "Created: / 03-10-2013 / 17:45:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-08-2014 / 10:53:54 / 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."

    ^ (Smalltalk at: #JavaScanner)

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

!JavaEditSupport methodsFor:'editing'!

electricInsertSnippet
    | tokens  lastToken0 |

    tokens := self scanLineAtCursor.
    tokens isEmptyOrNil ifTrue:[
        ^ false
    ].
    lastToken0 := tokens at:(tokens size - 3).
    lastToken0 = 'Error' ifTrue:[
        ^ false
    ].
    (tokens last > service textView cursorCol) ifTrue:[
        ^ false
    ].
    
    "/ Insert try { ... }
    
    lastToken0 == #try ifTrue:[
        (tokens size == 4 
            or:[ (tokens size > 4) and:[ (tokens at:tokens size - 7) ~~ $. ] ]) 
                ifTrue:[
                    self electricInsertBlockOpenedBy:' {' closedBy:'}'.
                    ^ true.
                ]
    ].
    
    "/ Insert catch (  ) { ... }
    
    lastToken0 == #catch ifTrue:[
        (tokens size > 4 and:[ (tokens at:tokens size - 7) == $} ]) ifTrue:[
            | cursorLine  cursorCol |

            cursorLine := service textView cursorLine.
            cursorCol := service textView cursorCol.
            self electricInsertBlockOpenedBy:' (  ) {' closedBy:'}'.
            service textView cursorLine:cursorLine col:cursorCol + 3.
            ^ true.
        ].
    ].
    
    "/ Insert finally { ... }
    
    lastToken0 == #finally ifTrue:[
        (tokens size > 4 and:[ (tokens at:tokens size - 7) == $} ]) ifTrue:[
            self electricInsertBlockOpenedBy:' {' closedBy:'}'.
            ^ true.
        ].
    ].
    
    "/ Insert if/while/synchronized ( )  { ... }
    
    (#( #if #while #synchronized ) includes:lastToken0) ifTrue:[
        (tokens size = 4) ifTrue:[
            | cursorLine  cursorCol |

            cursorLine := service textView cursorLine.
            cursorCol := service textView cursorCol.
            self electricInsertBlockOpenedBy:' (  ) {' closedBy:'}'.
            service textView cursorLine:cursorLine col:cursorCol + 3.
            ^ true.
        ].
    ].
    
    "/ Insert for ( ; ; )  { ... }
    
    (lastToken0 == #for) ifTrue:[
        (tokens size = 4) ifTrue:[
            | cursorLine  cursorCol |

            cursorLine := service textView cursorLine.
            cursorCol := service textView cursorCol.
            self electricInsertBlockOpenedBy:' ( ; ; ) {' closedBy:'}'.
            service textView cursorLine:cursorLine col:cursorCol + 3.
            ^ true.
        ].
    ].
    ^ false

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

!JavaEditSupport 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 ].

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

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

    key == #CodeCompletion ifTrue:[ 
        | controller |

        (controller := self textView completionSupport) notNil ifTrue:[
            ^ controller handleKeyPress:key x:x y:y 
        ].
        ^ false
    ].     

    key == ${ ifTrue:[
        ^ self keyPressOpenCurly
    ].

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

    ^ false

    "Created: / 07-03-2010 / 09:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-05-2014 / 12:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressOpenCurly
    | line tokens i |

    line := service codeView listAt: service codeView cursorLine.
    line notEmptyOrNil ifTrue:[
        i := line size.
        [ i > 0 and:[(line at: i) isSeparator] ] whileTrue:[ i := i - 1 ].
        (i ~~ 0 and:[service codeView cursorCol < i]) ifTrue:[
            ^ false.        ].
    ] ifFalse:[
        self electricInsertBlockOpenedBy:'{' closedBy:'}'. 
        ^ true
    ].

    tokens := self scanLineAtCursor.
    tokens notEmptyOrNil ifTrue:[
        | column |

        column := service textView cursorCol.
        (tokens at: tokens size - 3) = 'Error' ifTrue:[ ^ false ].
        1 to: tokens size - 3 by: 4 do:[:i |
            (column between: (tokens at: i + 2) and: (tokens at: i + 3)) ifTrue:[
                (tokens at: i) == #String ifTrue:[ ^ false ].

                self electricInsertBlockOpenedBy:'{' closedBy:'}'. 
                ^ true.
            ].
        ].
    ].

    self electricInsertBlockOpenedBy:'{' closedBy:'}'. 
    ^ true

    "Created: / 04-08-2013 / 01:54:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-10-2013 / 18:03:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaEditSupport methodsFor:'initialization'!

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

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

!JavaEditSupport methodsFor:'private'!

tokenAtCursorLine
    | scanner token |

    scanner := (Smalltalk at:#JavaScanner) for: (service textView listAt: service textView cursorLine) string.

    [ 
        [ 
            token := scanner nextToken.
            (token ~~ #EOF and:[ scanner tokenEndPosition + 1 < service textView cursorCol ])
        ] whileTrue.
    ] on: Error do:[
        token := nil.
    ].
    ^ token

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

tokensAtCursorLine
    | scanner token |

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

    "Created: / 04-08-2013 / 01:57:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaEditSupport class methodsFor:'documentation'!

version_HG

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