Revamp of Java completion engine - use JDT's CompletionParser to parse source.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 13 Aug 2014 10:28:35 +0100
changeset 278 696843cd1f9d
parent 277 ca11f8442de1
child 279 1dcaf8e06968
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.
SmallSense__CompletionView.st
SmallSense__JavaCompletionEngine.st
SmallSense__JavaCompletionEngineTests.st
SmallSense__JavaEditSupport.st
SmallSense__PO.st
abbrev.stc
java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnFieldType.st
java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleNameReference.st
java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleTypeReference.st
java/extensions/org/eclipse/jdt/internal/compiler/ast/ASTNode.st
smallsense.rc
stx_goodies_smallsense.st
--- a/SmallSense__CompletionView.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/SmallSense__CompletionView.st	Wed Aug 13 10:28:35 2014 +0100
@@ -62,13 +62,13 @@
 
     completionContext := aCompletionContext.
     node := completionContext node.
-    (node notNil and:[node isMessage]) ifTrue:[ 
+    (node notNil and:[node askFor:#isMessage]) ifTrue:[ 
         helpHolder value: 'Receiver type: ', node receiver inferedType displayString
     ] ifFalse:[ 
         helpHolder value: 'Up/Down to select, Enter to paste' asText.
     ].
 
-    "Modified: / 09-04-2014 / 12:59:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-08-2014 / 10:54:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 completionController
--- a/SmallSense__JavaCompletionEngine.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/SmallSense__JavaCompletionEngine.st	Wed Aug 13 10:28:35 2014 +0100
@@ -21,7 +21,7 @@
 "{ NameSpace: SmallSense }"
 
 AbstractJavaCompletionEngine subclass:#JavaCompletionEngine
-	instanceVariableNames:'classTree methodTree'
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SmallSense-Java'
@@ -50,149 +50,101 @@
 "
 ! !
 
-!JavaCompletionEngine methodsFor:'completion'!
-
-completeNode: node
-    Transcript 
-        show: 'Java Simple Completion on node: ';
-        show: node printString;
-        show: ' [';
-        show: node class printString;
-        showCR: ']'.
-
-    "Created: / 20-10-2013 / 01:34:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
 !JavaCompletionEngine methodsFor:'completion-individual'!
 
-addFieldsStartingWith: prefix
-    | klass |
-
-    classTree notNil ifTrue:[
-        (classTree fields ? #()) do:[:field |
-            result add: (VariablePO instanceVariable: field name in: class).            
-        ].
-    ] ifFalse:[
-        klass := class.
-    ].
-
-    [ klass notNil ] whileTrue:[
-        klass instVarNames do:[:nm |
-            result add: (VariablePO instanceVariable: nm in: klass).
-        ].
-        klass := klass superclass.
-    ].
-
-    "Created: / 03-10-2013 / 11:16:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 20-10-2013 / 02:04:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-addImportsStartingWith: prefix
-    | packages |
-
-    packages := Set new.
-
-    "/ Class imports...
-    self javaClassesDo:[:cls|
-        | name i |
-
-        name := cls javaName.
-        (cls isPublic and:[name startsWith: prefix]) ifTrue:[
-            result add: (JavaImportPO new subject: name; klass: cls; yourself).        
-            packages add: cls javaPackage.
-        ].
-    ].
-    "/ Package imports...
-    packages do:[:each |
-        result add: (JavaImportPO new subject: (each , '.*'))
-    ].
-
-    "Created: / 19-10-2013 / 17:54:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 20-10-2013 / 00:35:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-addLocalsStartingWith: prefix
-    | queue |
-
-    methodTree isNil ifTrue:[ ^ self ].
-    methodTree scope isNil ifTrue:[ ^ self ].
-
-    queue := OrderedCollection with: methodTree scope.
-    [ queue notEmpty ] whileTrue:[
-        | scope |
-
-        scope := queue removeFirst.
-        1 to: scope localIndex do:[:i|
-            | nm |
-
-            nm := (scope locals at: i) name.
-            (nm startsWith: prefix) ifTrue:[
-                result add: (VariablePO instanceVariable: nm in: class). 
-            ].
-        ].
-    ].
-
-    "Created: / 03-10-2013 / 17:46:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 20-10-2013 / 02:15:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 addMethodsForReceiver: maybeReceiverToken startingWith: prefix    
     ^ self addMethodsStartingWith: prefix
 
     "Created: / 03-10-2013 / 17:46:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-addMethodsStartingWith: prefix    
-    ^ self addMethodsStartingWith: prefix stripOff: nil filter: [:m | m isJavaMethod ]
+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: / 03-10-2013 / 18:01:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 08-04-2014 / 21:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "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 parser tree finder node scope |
+    | 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.
-    tree := parser parse: source diet: true resolve: true.
+"/    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
     "
 
-    (tree notNil and:[tree types notEmptyOrNil]) ifTrue:[
-        classTree := tree types detect:[:t | (position - 1) between: t declarationSourceStart and: t declarationSourceEnd ] ifNone:[nil].
-        (classTree notNil and: [ classTree methods notEmptyOrNil ]) ifTrue:[
-            methodTree := classTree methods detect:[:m | (position - 1) between: m declarationSourceStart and: m declarationSourceEnd ] ifNone:[nil].
-            methodTree notNil ifTrue:[ 
-                methodTree parseStatements: parser in: tree.
-            ].
-        ].
-        finder := JAVA stx libjava tools ast ASTNodeFinder new.
-        finder setPosition: position - 1.
-        tree traverse: finder scope: tree scope.
-        node := finder node.
-        scope := finder scope.
+    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 ifTrue:[
+    (node isNil or:[scope isNil]) ifTrue:[
         result := JavaCompletionEngineSimple new complete: context.
     ] ifFalse:[
-        self completeNode: node.
+        node completeUsingEngine: self in: scope.
     ].
 
     ^ result
 
     "Created: / 02-10-2013 / 13:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 07-08-2014 / 10:05:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 01:56:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/SmallSense__JavaCompletionEngineTests.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/SmallSense__JavaCompletionEngineTests.st	Wed Aug 13 10:28:35 2014 +0100
@@ -64,6 +64,56 @@
 
 !JavaCompletionEngineTests methodsFor:'tests'!
 
+test_method_01
+
+    <skip>
+
+    self complete:'public class Foo {
+        public int bar(Object o) {
+            return o.has┃
+        }
+    }'.
+
+    self assert: result notEmpty.
+    self assert: (result contains:[:each | each isSmallSenseMethodPO
+                                                and:[ each selector == #'hashCode()I' ] ])
+
+    "Created: / 13-08-2014 / 02:05:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_types_01
+
+    <skip>
+
+    self complete:'public class Foo {
+        public int addTo(Arra┃
+        }
+    }'.
+
+    self assert: result notEmpty.
+    self assert: (result contains:[:each | each isSmallSenseClassPO 
+                                                and:[ each klass == JAVA java util ArrayList ] ])
+
+    "Created: / 13-08-2014 / 00:35:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 02:02:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_types_02
+
+    <skip>
+
+    self complete:'public class Foo {
+        protected Arra┃
+    }'.
+
+    self assert: result notEmpty.
+    self assert: (result contains:[:each | each isSmallSenseClassPO 
+                                                and:[ each klass == JAVA java util ArrayList ] ])
+
+    "Created: / 13-08-2014 / 00:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 02:02:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 test_variables_01
 
     <skip>
@@ -74,10 +124,13 @@
         }
     }'.
 
-    self assert: result size >= 2.
-    self assert: false "/ unfinished
+    self assert: result size == 2.
+    self assert: (result contains:[:each | each isSmallSenseVariablePO
+                                                and:[ each name = 'number1' ] ]).
+    self assert: (result contains:[:each | each isSmallSenseVariablePO
+                                                and:[ each name = 'number2' ] ]).
 
     "Created: / 07-08-2014 / 02:00:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 07-08-2014 / 10:24:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 02:03:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/SmallSense__JavaEditSupport.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/SmallSense__JavaEditSupport.st	Wed Aug 13 10:28:35 2014 +0100
@@ -69,13 +69,13 @@
     "Returns a code completion engine class or nil, of 
      no completion is supported"
 
-"/    OperatingSystem getLoginName = 'jv' ifTrue:[
-"/        ^ SmallSense::JavaCompletionEngine
-"/    ].
+    OperatingSystem getLoginName = 'jv' ifTrue:[
+        ^ SmallSense::JavaCompletionEngine
+    ].
     ^ SmallSense::JavaCompletionEngineSimple
 
     "Created: / 03-10-2013 / 17:45:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 20-10-2013 / 02:53:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-08-2014 / 10:53:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 scannerClass
--- a/SmallSense__PO.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/SmallSense__PO.st	Wed Aug 13 10:28:35 2014 +0100
@@ -96,6 +96,12 @@
     "Created: / 24-07-2014 / 16:50:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+forLocalVariableNamed: nm
+    ^ VariablePO variable: nm
+
+    "Created: / 12-08-2014 / 10:40:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 subject: anObject
     <resource: #obsolete>
 
@@ -347,10 +353,10 @@
 
     super printOn:aStream.
     aStream nextPut:$(.
-    self label.
+    aStream nextPutAll:self label.
     aStream nextPut:$).
 
-    "Modified: / 20-05-2014 / 11:18:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 01:53:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PO methodsFor:'queries'!
--- a/abbrev.stc	Mon Aug 11 21:30:19 2014 +0100
+++ b/abbrev.stc	Wed Aug 13 10:28:35 2014 +0100
@@ -1,13 +1,12 @@
 # automagically generated by the project definition
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
-SmallSense::BaseTestClass SmallSense__BaseTestClass stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
+SmallSense::AbstractTestCase SmallSense__AbstractTestCase stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::CodeHighlightingService SmallSense__CodeHighlightingService stx:goodies/smallsense 'SmallSense-Core-Services' 0
 SmallSense::CodeNavigationService SmallSense__CodeNavigationService stx:goodies/smallsense 'SmallSense-Core-Services' 0
 SmallSense::CompletionContext SmallSense__CompletionContext stx:goodies/smallsense 'SmallSense-Core' 0
 SmallSense::CompletionController SmallSense__CompletionController stx:goodies/smallsense 'SmallSense-Core' 0
 SmallSense::CompletionEngine SmallSense__CompletionEngine stx:goodies/smallsense 'SmallSense-Core' 0
-SmallSense::CompletionEngineTests SmallSense__CompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::CompletionResult SmallSense__CompletionResult stx:goodies/smallsense 'SmallSense-Core' 0
 SmallSense::CompletionView SmallSense__CompletionView stx:goodies/smallsense 'SmallSense-Core-Interface' 2
 SmallSense::CriticsWindow SmallSense__CriticsWindow stx:goodies/smallsense 'SmallSense-Core-Interface' 1
@@ -32,9 +31,7 @@
 SmallSense::SmalltalkQuickFixer SmallSense__SmalltalkQuickFixer stx:goodies/smallsense 'SmallSense-Smalltalk-Lint' 0
 SmallSense::SmalltalkSyntaxHighlighter SmallSense__SmalltalkSyntaxHighlighter stx:goodies/smallsense 'SmallSense-Smalltalk' 3
 SmallSense::SmalltalkUnacceptedMethodEnvironment SmallSense__SmalltalkUnacceptedMethodEnvironment stx:goodies/smallsense 'SmallSense-Smalltalk-Lint' 0
-SmallSense::TestCase SmallSense__TestCase stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::TokenPatternMatcher SmallSense__TokenPatternMatcher stx:goodies/smallsense 'SmallSense-Utils-Matcher' 0
-SmallSense::TokenPatternMatcherTests SmallSense__TokenPatternMatcherTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::TokenPatternParser SmallSense__TokenPatternParser stx:goodies/smallsense 'SmallSense-Utils-Matcher' 0
 SmallSense::TokenPatternToken SmallSense__TokenPatternToken stx:goodies/smallsense 'SmallSense-Utils-Matcher' 0
 SmallSense::TokenPatternTokenSet SmallSense__TokenPatternTokenSet stx:goodies/smallsense 'SmallSense-Utils-Matcher' 0
@@ -43,37 +40,40 @@
 SmallSense::TypeHolder SmallSense__TypeHolder stx:goodies/smallsense 'SmallSense-Smalltalk-Types' 0
 stx_goodies_smallsense stx_goodies_smallsense stx:goodies/smallsense '* Projects & Packages *' 3
 SmallSense::AbstractJavaCompletionEngine SmallSense__AbstractJavaCompletionEngine stx:goodies/smallsense 'SmallSense-Java' 0
-SmallSense::AbstractJavaCompletionEngineTests SmallSense__AbstractJavaCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::ClassInfo SmallSense__ClassInfo stx:goodies/smallsense 'SmallSense-Smalltalk-Types-Info' 0
 SmallSense::ClassPO SmallSense__ClassPO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::ClassType SmallSense__ClassType stx:goodies/smallsense 'SmallSense-Smalltalk-Types' 0
+SmallSense::CompletionEngineTests SmallSense__CompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::ConstantPO SmallSense__ConstantPO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
-SmallSense::FinderTests SmallSense__FinderTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::GenericEditSupport SmallSense__GenericEditSupport stx:goodies/smallsense 'SmallSense-Core-Services' 0
 SmallSense::JavaEditSupport SmallSense__JavaEditSupport stx:goodies/smallsense 'SmallSense-Java' 0
 SmallSense::JavaImportPO SmallSense__JavaImportPO stx:goodies/smallsense 'SmallSense-Java-Interface-PO' 0
 SmallSense::MethodInfo SmallSense__MethodInfo stx:goodies/smallsense 'SmallSense-Smalltalk-Types-Info' 0
 SmallSense::MethodPO SmallSense__MethodPO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
-SmallSense::RecognizerTests SmallSense__RecognizerTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::SmalltalkCompletionEngine SmallSense__SmalltalkCompletionEngine stx:goodies/smallsense 'SmallSense-Smalltalk' 0
 SmallSense::SmalltalkEditSupport SmallSense__SmalltalkEditSupport stx:goodies/smallsense 'SmallSense-Smalltalk' 0
 SmallSense::SmalltalkInferencer SmallSense__SmalltalkInferencer stx:goodies/smallsense 'SmallSense-Smalltalk-Types-Inference' 0
 SmallSense::SmalltalkParseNodeFinder SmallSense__SmalltalkParseNodeFinder stx:goodies/smallsense 'SmallSense-Smalltalk' 0
-SmallSense::SmalltalkParserTests SmallSense__SmalltalkParserTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::SnippetPO SmallSense__SnippetPO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::UnionType SmallSense__UnionType stx:goodies/smallsense 'SmallSense-Smalltalk-Types' 0
 SmallSense::UnknownType SmallSense__UnknownType stx:goodies/smallsense 'SmallSense-Smalltalk-Types' 1
 SmallSense::VariablePO SmallSense__VariablePO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::AbstractJavaCompletionEngineSimple SmallSense__AbstractJavaCompletionEngineSimple stx:goodies/smallsense 'SmallSense-Java' 2
-SmallSense::GroovyCompletionEngineSimpleTests SmallSense__GroovyCompletionEngineSimpleTests stx:goodies/smallsense 'SmallSense-Tests' 1
+SmallSense::AbstractJavaCompletionEngineTests SmallSense__AbstractJavaCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::GroovyEditSupport SmallSense__GroovyEditSupport stx:goodies/smallsense 'SmallSense-Groovy' 0
 SmallSense::JavaCompletionEngine SmallSense__JavaCompletionEngine stx:goodies/smallsense 'SmallSense-Java' 0
-SmallSense::JavaCompletionEngineTests SmallSense__JavaCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::JavaConstructorPO SmallSense__JavaConstructorPO stx:goodies/smallsense 'SmallSense-Java-Interface-PO' 0
 SmallSense::MethodKeywordRestPO SmallSense__MethodKeywordRestPO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::JavaCompletionEngineSimple SmallSense__JavaCompletionEngineSimple stx:goodies/smallsense 'SmallSense-Java' 2
+SmallSense::JavaCompletionEngineTests SmallSense__JavaCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::GroovyCompletionEngineSimple SmallSense__GroovyCompletionEngineSimple stx:goodies/smallsense 'SmallSense-Groovy' 2
-SmallSense::AbstractTestCase SmallSense__AbstractTestCase stx:goodies/smallsense 'SmallSense-Tests' 1
+SmallSense::BaseTestClass SmallSense__BaseTestClass stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::EditSupportTests SmallSense__EditSupportTests stx:goodies/smallsense 'SmallSense-Tests' 1
+SmallSense::FinderTests SmallSense__FinderTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
+SmallSense::GroovyCompletionEngineSimpleTests SmallSense__GroovyCompletionEngineSimpleTests stx:goodies/smallsense 'SmallSense-Tests' 1
+SmallSense::RecognizerTests SmallSense__RecognizerTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
 SmallSense::SmalltalkCompletionEngineTests SmallSense__SmalltalkCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
 SmallSense::SmalltalkEditSupportTests SmallSense__SmalltalkEditSupportTests stx:goodies/smallsense 'SmallSense-Tests' 1
+SmallSense::SmalltalkParserTests SmallSense__SmalltalkParserTests stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
+SmallSense::TestCase SmallSense__TestCase stx:goodies/smallsense 'SmallSense-Tests-Obsolete' 1
+SmallSense::TokenPatternMatcherTests SmallSense__TokenPatternMatcherTests stx:goodies/smallsense 'SmallSense-Tests' 1
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnFieldType.st	Wed Aug 13 10:28:35 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnFieldType') methodsFor:'* instance *'!
+
+completeUsingEngine: engine in: scope
+    engine completeOnFieldType: self in: scope
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleNameReference.st	Wed Aug 13 10:28:35 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnSingleNameReference') methodsFor:'* instance *'!
+
+completeUsingEngine: engine in: scope
+    engine completeOnSingleNameReference: self in: scope          
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleTypeReference.st	Wed Aug 13 10:28:35 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnSingleTypeReference') methodsFor:'* instance *'!
+
+completeUsingEngine: engine in: scope
+    engine completeOnSingleTypeReference: self in: scope          
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/compiler/ast/ASTNode.st	Wed Aug 13 10:28:35 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.compiler.ast.ASTNode') methodsFor:'* instance *'!
+
+completeUsingEngine: engine in: scope 
+    Transcript showCR: 'No completion for: ', self class name  
+! !
--- a/smallsense.rc	Mon Aug 11 21:30:19 2014 +0100
+++ b/smallsense.rc	Wed Aug 13 10:28:35 2014 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Jan Vrany 2013-2014\0"
       VALUE "ProductName", "SmallSense\0"
       VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Mon, 11 Aug 2014 17:38:24 GMT\0"
+      VALUE "ProductDate", "Wed, 13 Aug 2014 09:27:39 GMT\0"
     END
 
   END
--- a/stx_goodies_smallsense.st	Mon Aug 11 21:30:19 2014 +0100
+++ b/stx_goodies_smallsense.st	Wed Aug 13 10:28:35 2014 +0100
@@ -104,7 +104,8 @@
         #'stx:goodies/refactoryBrowser/helpers'    "BrowserEnvironment - superclass of SmallSense::SmalltalkUnacceptedMethodEnvironment"
         #'stx:goodies/refactoryBrowser/lint'    "RBLintRule - extended"
         #'stx:goodies/regex'    "Regex::RxCharSetParser - superclass of SmallSense::TokenPatternParser::TokenSpecParser"
-        #'stx:libbasic'    "Autoload - superclass of SmallSense::AbstractJavaCompletionEngineTests"
+        #'stx:goodies/sunit'    "TestAsserter - superclass of SmallSense::AbstractJavaCompletionEngineTests"
+        #'stx:libbasic'    "Autoload - superclass of SmallSense::BaseTestClass"
         #'stx:libcomp'    "AbstractSyntaxHighlighter - superclass of SmallSense::SmalltalkParser"
         #'stx:libhtml'    "HTMLDocumentFrame - extended"
         #'stx:libtool'    "AbstractSettingsApplication - superclass of SmallSense::SettingsAppl"
@@ -126,7 +127,7 @@
         #'stx:goodies/refactoryBrowser/parser'    "RBFormatter - referenced by SmallSense::SmalltalkEditSupport>>electricInsertSnippetAfterDoubleColon"
         #'stx:libbasic2'    "BackgroundQueueProcessingJob - referenced by SmallSense::Manager>>initialize"
         #'stx:libbasic3'    "ChangeSet - referenced by RBTransformationRule>>fixes:"
-        #'stx:libjava'    "JavaClass - referenced by SmallSense::CodeNavigationService::Navigator>>navigateToTypeReference:"
+        #'stx:libjava'    "Java - referenced by SmallSense::JavaCompletionEngine>>complete"
         #'stx:libjava/tools'    "GroovyScanner - referenced by SmallSense::GroovyCompletionEngineSimple>>scannerClass"
     )
 !
@@ -166,13 +167,12 @@
 
     ^ #(
         "<className> or (<className> attributes...) in load order"
-        (#'SmallSense::BaseTestClass' autoload)
+        (#'SmallSense::AbstractTestCase' autoload)
         #'SmallSense::CodeHighlightingService'
         #'SmallSense::CodeNavigationService'
         #'SmallSense::CompletionContext'
         #'SmallSense::CompletionController'
         #'SmallSense::CompletionEngine'
-        (#'SmallSense::CompletionEngineTests' autoload)
         #'SmallSense::CompletionResult'
         #'SmallSense::CompletionView'
         #'SmallSense::CriticsWindow'
@@ -197,9 +197,7 @@
         #'SmallSense::SmalltalkQuickFixer'
         #'SmallSense::SmalltalkSyntaxHighlighter'
         #'SmallSense::SmalltalkUnacceptedMethodEnvironment'
-        (#'SmallSense::TestCase' autoload)
         #'SmallSense::TokenPatternMatcher'
-        (#'SmallSense::TokenPatternMatcherTests' autoload)
         #'SmallSense::TokenPatternParser'
         #'SmallSense::TokenPatternToken'
         #'SmallSense::TokenPatternTokenSet'
@@ -208,40 +206,43 @@
         #'SmallSense::TypeHolder'
         #'stx_goodies_smallsense'
         #'SmallSense::AbstractJavaCompletionEngine'
-        (#'SmallSense::AbstractJavaCompletionEngineTests' autoload)
         #'SmallSense::ClassInfo'
         #'SmallSense::ClassPO'
         #'SmallSense::ClassType'
+        (#'SmallSense::CompletionEngineTests' autoload)
         #'SmallSense::ConstantPO'
-        (#'SmallSense::FinderTests' autoload)
         #'SmallSense::GenericEditSupport'
         #'SmallSense::JavaEditSupport'
         #'SmallSense::JavaImportPO'
         #'SmallSense::MethodInfo'
         #'SmallSense::MethodPO'
-        (#'SmallSense::RecognizerTests' autoload)
         #'SmallSense::SmalltalkCompletionEngine'
         #'SmallSense::SmalltalkEditSupport'
         #'SmallSense::SmalltalkInferencer'
         #'SmallSense::SmalltalkParseNodeFinder'
-        (#'SmallSense::SmalltalkParserTests' autoload)
         #'SmallSense::SnippetPO'
         #'SmallSense::UnionType'
         #'SmallSense::UnknownType'
         #'SmallSense::VariablePO'
         #'SmallSense::AbstractJavaCompletionEngineSimple'
-        (#'SmallSense::GroovyCompletionEngineSimpleTests' autoload)
+        (#'SmallSense::AbstractJavaCompletionEngineTests' autoload)
         #'SmallSense::GroovyEditSupport'
         #'SmallSense::JavaCompletionEngine'
-        (#'SmallSense::JavaCompletionEngineTests' autoload)
         #'SmallSense::JavaConstructorPO'
         #'SmallSense::MethodKeywordRestPO'
         #'SmallSense::JavaCompletionEngineSimple'
+        (#'SmallSense::JavaCompletionEngineTests' autoload)
         #'SmallSense::GroovyCompletionEngineSimple'
-        (#'SmallSense::AbstractTestCase' autoload)
+        (#'SmallSense::BaseTestClass' autoload)
         (#'SmallSense::EditSupportTests' autoload)
+        (#'SmallSense::FinderTests' autoload)
+        (#'SmallSense::GroovyCompletionEngineSimpleTests' autoload)
+        (#'SmallSense::RecognizerTests' autoload)
         (#'SmallSense::SmalltalkCompletionEngineTests' autoload)
         (#'SmallSense::SmalltalkEditSupportTests' autoload)
+        (#'SmallSense::SmalltalkParserTests' autoload)
+        (#'SmallSense::TestCase' autoload)
+        (#'SmallSense::TokenPatternMatcherTests' autoload)
     )
 !