Support for completing Java methods (only first level).
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 14 Aug 2014 09:28:16 +0100
changeset 280 100db0f8279b
parent 279 1dcaf8e06968
child 281 200db18cbc2f
Support for completing Java methods (only first level). To simplify things, new PO were introduced to operate directly on JDT's Binding objects. More binding-backed PO's will probably follow (TypeBindingPO for sure)
Make.proto
Make.spec
SmallSense__JavaCompletionEngine.st
SmallSense__JavaCompletionEngineTests.st
SmallSense__MethodBindingPO.st
SmallSense__PO.st
SmallSense__VariableBindingPO.st
abbrev.stc
bc.mak
java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnFieldType.st
java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnQualifiedNameReference.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
java/extensions/org/eclipse/jdt/internal/compiler/lookup/BaseTypeBinding.st
libInit.cc
smallsense.rc
stx_goodies_smallsense.st
--- a/Make.proto	Wed Aug 13 20:40:56 2014 +0100
+++ b/Make.proto	Thu Aug 14 09:28:16 2014 +0100
@@ -203,6 +203,7 @@
 $(OUTDIR)SmallSense__GenericEditSupport.$(O) SmallSense__GenericEditSupport.$(H): SmallSense__GenericEditSupport.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__EditSupport.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__JavaEditSupport.$(O) SmallSense__JavaEditSupport.$(H): SmallSense__JavaEditSupport.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__EditSupport.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__JavaImportPO.$(O) SmallSense__JavaImportPO.$(H): SmallSense__JavaImportPO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__MethodBindingPO.$(O) SmallSense__MethodBindingPO.$(H): SmallSense__MethodBindingPO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__MethodInfo.$(O) SmallSense__MethodInfo.$(H): SmallSense__MethodInfo.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__Info.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__MethodPO.$(O) SmallSense__MethodPO.$(H): SmallSense__MethodPO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__SmalltalkCompletionEngine.$(O) SmallSense__SmalltalkCompletionEngine.$(H): SmallSense__SmalltalkCompletionEngine.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__CompletionEngine.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -212,6 +213,7 @@
 $(OUTDIR)SmallSense__SnippetPO.$(O) SmallSense__SnippetPO.$(H): SmallSense__SnippetPO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__UnionType.$(O) SmallSense__UnionType.$(H): SmallSense__UnionType.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__SmalltalkInferencerParameters.$(H) $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__Type.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__UnknownType.$(O) SmallSense__UnknownType.$(H): SmallSense__UnknownType.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__Type.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__VariableBindingPO.$(O) SmallSense__VariableBindingPO.$(H): SmallSense__VariableBindingPO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__VariablePO.$(O) SmallSense__VariablePO.$(H): SmallSense__VariablePO.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__PO.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__AbstractJavaCompletionEngineSimple.$(O) SmallSense__AbstractJavaCompletionEngineSimple.$(H): SmallSense__AbstractJavaCompletionEngineSimple.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__AbstractJavaCompletionEngine.$(H) $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__CompletionEngine.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__GroovyEditSupport.$(O) SmallSense__GroovyEditSupport.$(H): SmallSense__GroovyEditSupport.st $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__EditSupport.$(H) $(INCLUDE_TOP)/stx/goodies/smallsense/SmallSense__JavaEditSupport.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Wed Aug 13 20:40:56 2014 +0100
+++ b/Make.spec	Thu Aug 14 09:28:16 2014 +0100
@@ -94,6 +94,7 @@
 	SmallSense::GenericEditSupport \
 	SmallSense::JavaEditSupport \
 	SmallSense::JavaImportPO \
+	SmallSense::MethodBindingPO \
 	SmallSense::MethodInfo \
 	SmallSense::MethodPO \
 	SmallSense::SmalltalkCompletionEngine \
@@ -103,6 +104,7 @@
 	SmallSense::SnippetPO \
 	SmallSense::UnionType \
 	SmallSense::UnknownType \
+	SmallSense::VariableBindingPO \
 	SmallSense::VariablePO \
 	SmallSense::AbstractJavaCompletionEngineSimple \
 	SmallSense::GroovyEditSupport \
@@ -160,6 +162,7 @@
     $(OUTDIR_SLASH)SmallSense__GenericEditSupport.$(O) \
     $(OUTDIR_SLASH)SmallSense__JavaEditSupport.$(O) \
     $(OUTDIR_SLASH)SmallSense__JavaImportPO.$(O) \
+    $(OUTDIR_SLASH)SmallSense__MethodBindingPO.$(O) \
     $(OUTDIR_SLASH)SmallSense__MethodInfo.$(O) \
     $(OUTDIR_SLASH)SmallSense__MethodPO.$(O) \
     $(OUTDIR_SLASH)SmallSense__SmalltalkCompletionEngine.$(O) \
@@ -169,6 +172,7 @@
     $(OUTDIR_SLASH)SmallSense__SnippetPO.$(O) \
     $(OUTDIR_SLASH)SmallSense__UnionType.$(O) \
     $(OUTDIR_SLASH)SmallSense__UnknownType.$(O) \
+    $(OUTDIR_SLASH)SmallSense__VariableBindingPO.$(O) \
     $(OUTDIR_SLASH)SmallSense__VariablePO.$(O) \
     $(OUTDIR_SLASH)SmallSense__AbstractJavaCompletionEngineSimple.$(O) \
     $(OUTDIR_SLASH)SmallSense__GroovyEditSupport.$(O) \
--- a/SmallSense__JavaCompletionEngine.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/SmallSense__JavaCompletionEngine.st	Thu Aug 14 09:28:16 2014 +0100
@@ -21,7 +21,7 @@
 "{ NameSpace: SmallSense }"
 
 AbstractJavaCompletionEngine subclass:#JavaCompletionEngine
-	instanceVariableNames:''
+	instanceVariableNames:'completionNode completionScope'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SmallSense-Java'
@@ -52,51 +52,114 @@
 
 !JavaCompletionEngine methodsFor:'completion-individual'!
 
+addFieldsForTypeBinding:binding
+    | current |
+
+    current := binding.        
+    [ current notNil ] whileTrue:[  
+        current fields do:[:fbinding | 
+            result add: (PO forFieldBinding: fbinding )
+        ].  
+        current := current superclass.
+    ].
+
+    "Created: / 13-08-2014 / 21:39:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-08-2014 / 09:06:41 / 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>"
 !
 
+addMethodsForTypeBinding: binding
+    | current seen |
+
+    current := binding.        
+    seen := Set new.
+    [ current notNil ] whileTrue:[  
+        current methods do:[:mbinding |
+            mbinding isConstructor ifFalse:[
+                | selector |
+
+                selector := mbinding selector , mbinding signature.
+                (seen includes: selector) ifFalse:[
+                    result add: (PO forMethodBinding: mbinding).
+                    seen add: selector.
+                ].
+            ].
+        ].  
+        current := current superclass.
+    ].
+
+    "Created: / 13-08-2014 / 21:39:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 22:54:57 / 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) 
+            result add: (PO forLocalVariableBinding: (scope locals at:i) ) 
+        ].
+        self addVariablesInScope: (scope instVarNamed: #parent). "/ !!?!! Why 'scope parent' does not work?
+    ].
+
+    scope kind == JAVA org eclipse jdt internal compiler lookup Scope CLASS_SCOPE ifTrue:[ 
+        | type |
+
+        type := scope referenceType.
+        type notNil ifTrue:[ 
+            self addFieldsForTypeBinding: type binding.  
         ].
     ].
 
     "Created: / 12-08-2014 / 10:41:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-08-2014 / 09:08:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaCompletionEngine methodsFor:'completion-nodes'!
 
-completeOnFieldType: node in: scope
-    node type completeUsingEngine: self in: scope.
+completeOnFieldType: node
+    node type acceptCompletionEngine: self
 
-    "Created: / 13-08-2014 / 01:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 13-08-2014 / 21:04:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-completeOnSingleNameReference: node in: scope
-    self addVariablesInScope: scope.
+completeOnQualifiedNameReference: node
+    | binding |
 
-    "Created: / 13-08-2014 / 01:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    binding := node binding.
+    binding notNil ifTrue:[ 
+        binding := binding type.
+        binding notNil ifTrue:[ 
+            self addMethodsForTypeBinding: binding.
+            self addFieldsForTypeBinding: binding.  
+        ].
+    ].
+
+    "Created: / 13-08-2014 / 21:32:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-completeOnSingleTypeReference: node in: scope
-    | prefix |
+completeOnSingleNameReference: node
+    self addVariablesInScope: completionScope.
+    self addClassesStartingWith: node token.
 
-    prefix := node token.
-    self addClassesStartingWith: prefix
+    "Created: / 13-08-2014 / 21:05:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    "Created: / 13-08-2014 / 01:48:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+completeOnSingleTypeReference: node
+    self addClassesStartingWith: node token
+
+    "Created: / 13-08-2014 / 21:05:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaCompletionEngine methodsFor:'completion-private'!
 
 complete
     
-    | position source rslt problemReporter parser tree searcher resolver node scope |
+    | position source rslt problemReporter parser tree searcher resolver  |
 
     position := context codeView characterPositionOfCursor.
 
@@ -130,21 +193,21 @@
     [ 
         resolver resolve: tree.
     ] on: JAVA org eclipse jdt internal codeassist complete CompletionNodeFound do:[:ex |  
-        node := ex astNode.
-        scope := ex scope.
+        completionNode := ex astNode.
+        completionScope := ex scope.
     ].
 
-    context node: node position: position.
+    context node: completionNode position: position.
 
-    (node isNil or:[scope isNil]) ifTrue:[
+    (completionNode isNil or:[completionScope isNil]) ifTrue:[
         result := JavaCompletionEngineSimple new complete: context.
     ] ifFalse:[
-        node completeUsingEngine: self in: scope.
+        completionNode acceptCompletionEngine: self.
     ].
 
     ^ 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>"
+    "Modified: / 13-08-2014 / 21:08:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/SmallSense__JavaCompletionEngineTests.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/SmallSense__JavaCompletionEngineTests.st	Thu Aug 14 09:28:16 2014 +0100
@@ -75,10 +75,11 @@
     }'.
 
     self assert: result notEmpty.
-    self assert: (result contains:[:each | each isSmallSenseMethodPO
-                                                and:[ each selector == #'hashCode()I' ] ])
+    self assert: (result contains:[:each | each isSmallSenseMethodBindingPO
+                                                and:[ each binding selector = 'hashCode' ] ])
 
     "Created: / 13-08-2014 / 02:05:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-08-2014 / 22:45:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 test_types_01
@@ -119,18 +120,21 @@
     <skip>
 
     self complete:'public class Foo {
+        public int field;
         public int sum(int number1, int number2) {
             return num┃
         }
     }'.
 
-    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' ] ]).
+    self assert: result size == 3.
+    self assert: (result contains:[:each | each isSmallSenseVariableBindingPO
+                                                and:[ each binding name = 'number1' ] ]).
+    self assert: (result contains:[:each | each isSmallSenseVariableBindingPO
+                                                and:[ each binding name = 'number2' ] ]).
+    self assert: (result contains:[:each | each isSmallSenseVariableBindingPO
+                                                and:[ each binding name = 'field' ] ]).
 
     "Created: / 07-08-2014 / 02:00:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 13-08-2014 / 02:03:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-08-2014 / 09:08:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SmallSense__MethodBindingPO.st	Thu Aug 14 09:28:16 2014 +0100
@@ -0,0 +1,110 @@
+"
+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 }"
+
+PO subclass:#MethodBindingPO
+	instanceVariableNames:'binding'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SmallSense-Java-Interface-PO'
+!
+
+!MethodBindingPO 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
+"
+! !
+
+!MethodBindingPO methodsFor:'accessing'!
+
+binding
+    ^ binding
+!
+
+binding:b
+    binding := b.
+!
+
+label
+    "Return a text to be displayed. The label may be cached
+     `label` instvar."
+
+    label isNil ifTrue:[
+        | descriptor |
+
+        descriptor := binding signature.
+        label := JavaMethod specTextFromSignature:descriptor in: nil withName: binding selector isConstructor: binding isConstructor.   
+
+
+"/        | parameters |
+"/
+"/        label := String streamContents: [ :s |
+"/            s nextPutAll: binding selector.
+"/            s nextPut: $(.
+"/            parameters := binding parameters.
+"/            parameters notEmptyOrNil ifTrue:[ 
+"/                s nextPutAll: parameters first displayString.
+"/                parameters size > 1 ifTrue:[ 
+"/                    1 to: parameters size do:[:i |  
+"/                        s nextPutAll: ', '.
+"/                        s nextPutAll: (parameters at: i) displayString.
+"/                    ]
+"/                ].
+"/            ].
+"/            s nextPut: $).
+"/        ]
+    ].
+    ^ label
+
+    "Created: / 13-08-2014 / 22:33:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+stringToCompleteForLanguage:aProgrammingLanguage
+    ^ binding selector , '()'
+
+    "Created: / 13-08-2014 / 22:39:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!MethodBindingPO methodsFor:'testing'!
+
+isSmallSenseMethodBindingPO
+    ^ true
+
+    "Created: / 13-08-2014 / 22:44:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/SmallSense__PO.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/SmallSense__PO.st	Thu Aug 14 09:28:16 2014 +0100
@@ -90,12 +90,30 @@
     "Created: / 20-05-2014 / 10:43:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+forFieldBinding: binding
+    ^ VariableBindingPO new binding: binding
+
+    "Created: / 14-08-2014 / 09:04:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 forGlobalNamed: name
     ^ VariablePO globalVariable: name
 
     "Created: / 24-07-2014 / 16:50:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+forInstanceVariableNamed: nm in: cls
+    ^ VariablePO instanceVariable: nm in: cls.
+
+    "Created: / 13-08-2014 / 21:27:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+forLocalVariableBinding: binding
+    ^ VariableBindingPO new binding: binding
+
+    "Created: / 14-08-2014 / 09:04:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 forLocalVariableNamed: nm
     ^ VariablePO variable: nm
 
@@ -110,6 +128,14 @@
     "Created: / 06-04-2011 / 21:01:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PO class methodsFor:'instance creation-java'!
+
+forMethodBinding: binding
+    ^ MethodBindingPO new binding: binding
+
+    "Created: / 13-08-2014 / 22:24:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !PO methodsFor:'accessing'!
 
 context
@@ -378,6 +404,12 @@
     ^ false
 !
 
+isSmallSenseMethodBindingPO
+    "return false here; to be redefined in subclass(es)"
+
+    ^ false
+!
+
 isSmallSenseMethodPO
     ^ false
 !
@@ -386,6 +418,12 @@
     ^ false
 !
 
+isSmallSenseVariableBindingPO
+    "return false here; to be redefined in subclass(es)"
+
+    ^ false
+!
+
 isSmallSenseVariablePO
     ^ false
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SmallSense__VariableBindingPO.st	Thu Aug 14 09:28:16 2014 +0100
@@ -0,0 +1,87 @@
+"
+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 }"
+
+PO subclass:#VariableBindingPO
+	instanceVariableNames:'binding'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SmallSense-Java-Interface-PO'
+!
+
+!VariableBindingPO 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
+"
+! !
+
+!VariableBindingPO methodsFor:'accessing'!
+
+binding
+    ^ binding
+!
+
+binding:b
+    binding := b.
+!
+
+label
+    "Return a text to be displayed. The label may be cached
+     `label` instvar."
+
+    ^ binding name
+
+    "Created: / 14-08-2014 / 09:02:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+stringToCompleteForLanguage:aProgrammingLanguage
+    "Answers a string to complete"
+
+    ^ binding name
+
+    "Created: / 14-08-2014 / 09:02:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!VariableBindingPO methodsFor:'testing'!
+
+isSmallSenseVariableBindingPO
+    ^ true
+
+    "Created: / 14-08-2014 / 09:01:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/abbrev.stc	Wed Aug 13 20:40:56 2014 +0100
+++ b/abbrev.stc	Thu Aug 14 09:28:16 2014 +0100
@@ -53,6 +53,7 @@
 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::MethodBindingPO SmallSense__MethodBindingPO 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
@@ -64,6 +65,7 @@
 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::VariableBindingPO SmallSense__VariableBindingPO stx:goodies/smallsense 'SmallSense-Java-Interface-PO' 0
 SmallSense::VariablePO SmallSense__VariablePO stx:goodies/smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::AbstractJavaCompletionEngineSimple SmallSense__AbstractJavaCompletionEngineSimple stx:goodies/smallsense 'SmallSense-Java' 2
 SmallSense::AbstractJavaCompletionEngineTests SmallSense__AbstractJavaCompletionEngineTests stx:goodies/smallsense 'SmallSense-Tests' 1
--- a/bc.mak	Wed Aug 13 20:40:56 2014 +0100
+++ b/bc.mak	Thu Aug 14 09:28:16 2014 +0100
@@ -127,6 +127,7 @@
 $(OUTDIR)SmallSense__GenericEditSupport.$(O) SmallSense__GenericEditSupport.$(H): SmallSense__GenericEditSupport.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__EditSupport.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__JavaEditSupport.$(O) SmallSense__JavaEditSupport.$(H): SmallSense__JavaEditSupport.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__EditSupport.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__JavaImportPO.$(O) SmallSense__JavaImportPO.$(H): SmallSense__JavaImportPO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__MethodBindingPO.$(O) SmallSense__MethodBindingPO.$(H): SmallSense__MethodBindingPO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__MethodInfo.$(O) SmallSense__MethodInfo.$(H): SmallSense__MethodInfo.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__Info.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__MethodPO.$(O) SmallSense__MethodPO.$(H): SmallSense__MethodPO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__SmalltalkCompletionEngine.$(O) SmallSense__SmalltalkCompletionEngine.$(H): SmallSense__SmalltalkCompletionEngine.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__CompletionEngine.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -136,6 +137,7 @@
 $(OUTDIR)SmallSense__SnippetPO.$(O) SmallSense__SnippetPO.$(H): SmallSense__SnippetPO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__UnionType.$(O) SmallSense__UnionType.$(H): SmallSense__UnionType.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__SmalltalkInferencerParameters.$(H) $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__Type.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__UnknownType.$(O) SmallSense__UnknownType.$(H): SmallSense__UnknownType.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__Type.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__VariableBindingPO.$(O) SmallSense__VariableBindingPO.$(H): SmallSense__VariableBindingPO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__VariablePO.$(O) SmallSense__VariablePO.$(H): SmallSense__VariablePO.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__PO.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__AbstractJavaCompletionEngineSimple.$(O) SmallSense__AbstractJavaCompletionEngineSimple.$(H): SmallSense__AbstractJavaCompletionEngineSimple.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__AbstractJavaCompletionEngine.$(H) $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__CompletionEngine.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__GroovyEditSupport.$(O) SmallSense__GroovyEditSupport.$(H): SmallSense__GroovyEditSupport.st $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__EditSupport.$(H) $(INCLUDE_TOP)\stx\goodies\smallsense\SmallSense__JavaEditSupport.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnFieldType.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnFieldType.st	Thu Aug 14 09:28:16 2014 +0100
@@ -4,6 +4,6 @@
 
 !(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnFieldType') methodsFor:'* instance *'!
 
-completeUsingEngine: engine in: scope
-    engine completeOnFieldType: self in: scope
+acceptCompletionEngine: engine
+    engine completeOnFieldType: self
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnQualifiedNameReference.st	Thu Aug 14 09:28:16 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnQualifiedNameReference') methodsFor:'* instance *'!
+
+acceptCompletionEngine: engine
+    engine completeOnQualifiedNameReference: self.
+! !
--- a/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleNameReference.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleNameReference.st	Thu Aug 14 09:28:16 2014 +0100
@@ -4,6 +4,6 @@
 
 !(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnSingleNameReference') methodsFor:'* instance *'!
 
-completeUsingEngine: engine in: scope
-    engine completeOnSingleNameReference: self in: scope          
+acceptCompletionEngine: engine
+    engine completeOnSingleNameReference: self
 ! !
--- a/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleTypeReference.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/java/extensions/org/eclipse/jdt/internal/codeassist/complete/CompletionOnSingleTypeReference.st	Thu Aug 14 09:28:16 2014 +0100
@@ -4,6 +4,6 @@
 
 !(Java classForName:'org.eclipse.jdt.internal.codeassist.complete.CompletionOnSingleTypeReference') methodsFor:'* instance *'!
 
-completeUsingEngine: engine in: scope
-    engine completeOnSingleTypeReference: self in: scope          
+acceptCompletionEngine: engine
+    engine completeOnSingleTypeReference: self
 ! !
--- a/java/extensions/org/eclipse/jdt/internal/compiler/ast/ASTNode.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/java/extensions/org/eclipse/jdt/internal/compiler/ast/ASTNode.st	Thu Aug 14 09:28:16 2014 +0100
@@ -4,6 +4,8 @@
 
 !(Java classForName:'org.eclipse.jdt.internal.compiler.ast.ASTNode') methodsFor:'* instance *'!
 
-completeUsingEngine: engine in: scope 
-    Transcript showCR: 'No completion for: ', self class name  
+acceptCompletionEngine: engine
+    (OperatingSystem getLoginName = 'jv') ifTrue:[
+        Transcript showCR: 'No completion for ', self class name  
+    ].
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/java/extensions/org/eclipse/jdt/internal/compiler/lookup/BaseTypeBinding.st	Thu Aug 14 09:28:16 2014 +0100
@@ -0,0 +1,9 @@
+"{ Package: 'stx:goodies/smallsense' }"
+
+!
+
+!(Java classForName:'org.eclipse.jdt.internal.compiler.lookup.BaseTypeBinding') methodsFor:'* instance *'!
+
+displayString
+    ^ simpleName
+! !
--- a/libInit.cc	Wed Aug 13 20:40:56 2014 +0100
+++ b/libInit.cc	Thu Aug 14 09:28:16 2014 +0100
@@ -71,6 +71,7 @@
 _SmallSense__GenericEditSupport_Init(pass,__pRT__,snd);
 _SmallSense__JavaEditSupport_Init(pass,__pRT__,snd);
 _SmallSense__JavaImportPO_Init(pass,__pRT__,snd);
+_SmallSense__MethodBindingPO_Init(pass,__pRT__,snd);
 _SmallSense__MethodInfo_Init(pass,__pRT__,snd);
 _SmallSense__MethodPO_Init(pass,__pRT__,snd);
 _SmallSense__SmalltalkCompletionEngine_Init(pass,__pRT__,snd);
@@ -80,6 +81,7 @@
 _SmallSense__SnippetPO_Init(pass,__pRT__,snd);
 _SmallSense__UnionType_Init(pass,__pRT__,snd);
 _SmallSense__UnknownType_Init(pass,__pRT__,snd);
+_SmallSense__VariableBindingPO_Init(pass,__pRT__,snd);
 _SmallSense__VariablePO_Init(pass,__pRT__,snd);
 _SmallSense__AbstractJavaCompletionEngineSimple_Init(pass,__pRT__,snd);
 _SmallSense__GroovyEditSupport_Init(pass,__pRT__,snd);
--- a/smallsense.rc	Wed Aug 13 20:40:56 2014 +0100
+++ b/smallsense.rc	Thu Aug 14 09:28:16 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", "Wed, 13 Aug 2014 15:03:09 GMT\0"
+      VALUE "ProductDate", "Thu, 14 Aug 2014 08:12:42 GMT\0"
     END
 
   END
--- a/stx_goodies_smallsense.st	Wed Aug 13 20:40:56 2014 +0100
+++ b/stx_goodies_smallsense.st	Thu Aug 14 09:28:16 2014 +0100
@@ -219,6 +219,7 @@
         #'SmallSense::GenericEditSupport'
         #'SmallSense::JavaEditSupport'
         #'SmallSense::JavaImportPO'
+        #'SmallSense::MethodBindingPO'
         #'SmallSense::MethodInfo'
         #'SmallSense::MethodPO'
         (#'SmallSense::RecognizerTests' autoload)
@@ -230,6 +231,7 @@
         #'SmallSense::SnippetPO'
         #'SmallSense::UnionType'
         #'SmallSense::UnknownType'
+        #'SmallSense::VariableBindingPO'
         #'SmallSense::VariablePO'
         #'SmallSense::AbstractJavaCompletionEngineSimple'
         (#'SmallSense::AbstractJavaCompletionEngineTests' autoload)