SmallSense__JavaCompletionEngine.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 13 Aug 2014 10:28:35 +0100
changeset 278 696843cd1f9d
parent 267 b6fbf84b14ae
child 280 100db0f8279b
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 }"

AbstractJavaCompletionEngine subclass:#JavaCompletionEngine
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Java'
!

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

!JavaCompletionEngine methodsFor:'completion-individual'!

addMethodsForReceiver: maybeReceiverToken startingWith: prefix    
    ^ self addMethodsStartingWith: prefix

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

addVariablesInScope: scope
    ((scope kind == JAVA org eclipse jdt internal compiler lookup Scope METHOD_SCOPE) or:[
    scope kind == JAVA org eclipse jdt internal compiler lookup Scope BLOCK_SCOPE]) ifTrue:[ 
        1 to: scope localIndex do:[:i | 
            result add: (PO forLocalVariableNamed: (scope locals at:i) name) 
        ].
    ].

    "Created: / 12-08-2014 / 10:41:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompletionEngine methodsFor:'completion-nodes'!

completeOnFieldType: node in: scope
    node type completeUsingEngine: self in: scope.

    "Created: / 13-08-2014 / 01:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeOnSingleNameReference: node in: scope
    self addVariablesInScope: scope.

    "Created: / 13-08-2014 / 01:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeOnSingleTypeReference: node in: scope
    | prefix |

    prefix := node token.
    self addClassesStartingWith: prefix

    "Created: / 13-08-2014 / 01:48:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompletionEngine methodsFor:'completion-private'!

complete
    
    | position source rslt problemReporter parser tree searcher resolver node scope |

    position := context codeView characterPositionOfCursor.

    source := JAVA stx libjava tools Source new.
    source setContents: codeView list asStringWithoutEmphasis.
"/    parser := JAVA stx libjava tools parser Parser new.
    rslt := JAVA org eclipse jdt internal compiler CompilationResult
                new: source _: 1 _: 1 _: 1000.  
    problemReporter := JAVA org eclipse jdt internal compiler problem ProblemReporter
                new: JAVA org eclipse jdt internal compiler DefaultErrorHandlingPolicies proceedWithAllProblems
                  _: JAVA stx libjava tools parser Parser defaultCompilerOptions   
                  _: JAVA stx libjava tools parser Parser defaultProblemFactory.

    parser := JAVA org eclipse jdt internal codeassist complete CompletionParser 
                new: problemReporter _: true.

"/    tree := parser parse: source diet: true resolve: true.
    tree := parser dietParse: source _: rslt _: position - 1"Java is 0-based" - 1"cursor is actualy one fter the end of token".
    searcher := JAVA org eclipse jdt core dom NodeSearcher new: position - 1"Java is 0-based" - 1"cursor is actualy one fter the end of token".
    tree traverse: searcher _: tree scope.
    (searcher found notNil and:[searcher found isKindOf: JAVA org eclipse jdt internal compiler ast AbstractMethodDeclaration]) ifTrue:[ 
        parser parseBlockStatements: searcher found _: tree.
    ].


    "
    (SmallSense::ParseTreeInspector new node:tree source: codeView list asString) open
    "

    resolver := (Java classForName: 'stx.libjava.tools.environment.Resolver') new: problemReporter.
    [ 
        resolver resolve: tree.
    ] on: JAVA org eclipse jdt internal codeassist complete CompletionNodeFound do:[:ex |  
        node := ex astNode.
        scope := ex scope.
    ].

    context node: node position: position.

    (node isNil or:[scope isNil]) ifTrue:[
        result := JavaCompletionEngineSimple new complete: context.
    ] ifFalse:[
        node completeUsingEngine: self in: scope.
    ].

    ^ result

    "Created: / 02-10-2013 / 13:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2014 / 01:56:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !