SmallSense__AbstractJavaCompletionSimple.st
changeset 210 1922d415c704
parent 208 0b9ed08a04c0
child 212 a2caebc602a7
--- a/SmallSense__AbstractJavaCompletionSimple.st	Wed May 14 15:23:05 2014 +0100
+++ b/SmallSense__AbstractJavaCompletionSimple.st	Thu May 15 10:40:02 2014 +0100
@@ -9,13 +9,40 @@
 	category:'SmallSense-Java-Abstract'
 !
 
-AbstractJavaCompletionSimple class instanceVariableNames:'patterns'
+AbstractJavaCompletionSimple class instanceVariableNames:'CompletionPatterns AnalysisPatterns'
 
 "
  No other class instance variables are inherited by this class.
 "
 !
 
+!AbstractJavaCompletionSimple class methodsFor:'initialization'!
+
+initializeCompletionPatterns
+    CompletionPatterns isNil ifTrue:[  CompletionPatterns := Dictionary new ].
+
+    #(
+        '[[:import:]] ( [[:Identifier:]](.[[:Identifier:]])*\.? )?'              #completeImport:
+        '[[:new:]] ( [[:Identifier:]](.[[:Identifier:]])*\.?)?'                     #completeNew:
+
+    ) pairWiseDo:[:pattern :action |
+        CompletionPatterns at: (TokenPatternParser parse: pattern) put: action
+    ].
+
+    "Created: / 14-05-2014 / 16:51:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!AbstractJavaCompletionSimple class methodsFor:'accessing'!
+
+completionPatterns
+    CompletionPatterns isNil ifTrue:[ 
+        self initializeCompletionPatterns.
+    ].
+    ^ CompletionPatterns
+
+    "Created: / 14-05-2014 / 16:55:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !AbstractJavaCompletionSimple class methodsFor:'queries'!
 
 isAbstract
@@ -26,6 +53,22 @@
     ^ self == SmallSense::AbstractJavaCompletionSimple.
 ! !
 
+!AbstractJavaCompletionSimple methodsFor:'accessing'!
+
+completionPatterns
+    ^ self class completionPatterns
+
+    "Created: / 14-05-2014 / 17:02:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!AbstractJavaCompletionSimple methodsFor:'accessing-class'!
+
+scannerClass
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+! !
+
 !AbstractJavaCompletionSimple methodsFor:'completion-individual'!
 
 addFieldsStartingWith: prefix
@@ -57,107 +100,174 @@
 !AbstractJavaCompletionSimple methodsFor:'completion-private'!
 
 complete
-    | line col scanner token tokenTypes values startPositions stopPositions maybeReceiverToken |
+    | line col stream tokens anyMatched |
 
     line := codeView listAt: codeView cursorLine.
     col := codeView cursorCol.
     line isNil ifTrue:[ ^ nil ].
     line size < (col - 1) ifTrue:[ ^ nil ].
 
-"/    "/ we need at least three characters in order to reduce
-"/    "/ completions...
-"/    line size < 3 ifTrue:[ ^ nil ]. 
-"/    col - 3 to: col - 1 do:[:i|
-"/        | c |
-"/
-"/        c := line at: i.
-"/        (c isLetterOrDigit or:[c == $_ or:[ c == $$ ] ]) ifFalse:[ ^ nil ] 
-"/    ].
 
-    "/ Setup some context vars
-    method := codeView editedMethod.
-    class := method notNil ifTrue:[method mclass] ifFalse:[codeView editedClass ].
+    stream := TokenStream on: (self scannerClass for: (line readStream readLimit: col - 1)).
+    anyMatched := false.
+    self completionPatterns keysAndValuesDo:[ :pattern :action |
+        | matcher |
 
-    "/ ok, we got three character prefix, now scan the current line...
-    scanner := self scannerClass for: line.
-    tokenTypes := OrderedCollection new.
-    values := OrderedCollection new.
-    startPositions := OrderedCollection new.
-    stopPositions := OrderedCollection new.
-    [
-        [ (token := scanner nextToken) ~~ #EOF and:[ scanner tokenStartPosition < (col - 1) ] ] whileTrue:[
-            tokenTypes add: token.
-            values add: scanner tokenValue.
-            startPositions add: scanner tokenStartPosition.
-            stopPositions add: scanner tokenEndPosition. 
+        stream position: 0. "/ Reset the position
+        matcher := TokenPatternMatcher for: pattern.
+        matcher matchesOnStream: stream do:[:match | 
+            self perform: action with: match.
+            anyMatched := true.
         ].
-    ] on: Error do:[ 
-        ^ nil 
+    ].
+    anyMatched ifFalse:[ 
+        stream position: 0.
+        tokens := stream contents.
+        (tokens size > 2 and:[tokens last type == $. or:[tokens last type == #Identifier and:[ (tokens at: tokens size - 1) type == $. ]]]) ifTrue:[
+            self completeMethodOrField: tokens.
+        ].                
     ].
 
-    tokenTypes isEmpty ifTrue:[ ^ nil ].
-    "/ now, simple check for import declaration
-    tokenTypes first == #import and:[
-        | prefix |
-
-        prefix := String streamContents:[:s|
-            | i |
-
-            i := 2.
-            [ i <= tokenTypes size ] whileTrue:[
-                (tokenTypes at: i) == #Identifier ifTrue:[
-                    s nextPutAll: (values at: i).
-                ] ifFalse:[
-                    ^ nil "/ malformed import
-                ].
-                (i < tokenTypes size) ifTrue:[
-                    (tokenTypes at: i + 1) == $. ifTrue:[
-                        s nextPut: $.
-                    ] ifFalse:[
-                        ^ nil "/ malformed import
-                    ].
-                ].
-                i := i + 2.
-            ].
-        ].
-        self addImportsStartingWith: prefix.
-        ^ result.
-    ].
-
-    "/ We need at least three characters to complete methods/fields.
-    (tokenTypes last ~~ #Identifier or:[values last size < 3]) ifTrue:[ ^ nil ].
-
-    "/ Complete after new keyword
-    (tokenTypes size > 1 and:[(tokenTypes at: tokenTypes size - 1) == #new]) ifTrue:[
-        self addClassesStartingWith: values last.
-        ^ result.
-    ].
-
-
-    "/ now check whether the butlast token is dot...
-    maybeReceiverToken := nil.
-    (tokenTypes size > 1 and:[(tokenTypes at: tokenTypes size - 1) == $.]) ifTrue:[
-        "/ if so, it's likely a message send, then complete methods...
-        tokenTypes size > 2 ifTrue:[
-            maybeReceiverToken := values at: values size - 2.
-        ].
-    ] ifFalse:[
-        "/ if not, then complete local variables, fields and methods defined in the class itself.
-        maybeReceiverToken := 'this'.
-    ].
-    maybeReceiverToken = 'this' ifTrue:[
-        values last first isUppercase ifTrue:[      
-            self addClassesStartingWith: values last.
-        ] ifFalse:[
-            self addFieldsStartingWith: values last.
-            self addLocalsStartingWith: values last.
-        ].
-    ].
-    self addMethodsForReceiver: maybeReceiverToken startingWith: values last.
 
     ^ result
 
     "Created: / 02-10-2013 / 13:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 13-05-2014 / 17:46:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 15-05-2014 / 07:52:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+completeImport: match
+    | prefix |
+
+    prefix := nil.
+    match size > 1 ifTrue:[ 
+        prefix := String streamContents:[:s | 2 to: match size do:[:i | s nextPutAll: (match at: i) value asString] ].
+    ].
+    self addImportsStartingWith: prefix
+
+    "Created: / 15-05-2014 / 06:57:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+completeMethodOrField: tokens
+    | type dotIndex |
+
+    dotIndex := tokens last type == #Identifier ifTrue:[ tokens size - 1 ] ifFalse:[ tokens size ].  
+    self assert: (tokens at: dotIndex) type == $..
+    type := self guessReceiverTypeFrom: tokens before: dotIndex.
+    type isUnknownType ifFalse:[
+        self addMethodsForType: type.  
+        "/self addFieldsForType: type.
+    ] ifTrue:[ 
+        tokens last type == #Identifier ifTrue:[
+            | prefix |
+
+            prefix := tokens last value.
+            (prefix size >= 3 and:[ prefix ~= 'get' and:[prefix ~= 'set' ]]) ifTrue:[
+                self addMethodsStartingWith: prefix.
+            ].
+        ].
+    ].
+
+    "Created: / 15-05-2014 / 07:44:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-05-2014 / 09:44:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+completeNew: match
+    | prefix |
+
+    prefix := nil.
+    match size > 2 ifTrue:[ 
+        prefix := String streamContents:[:s | 2 to: match size do:[:i | s nextPutAll: (match at: i) value asString] ].
+        self addClassesStartingWith: prefix fullName: true.
+    ] ifFalse:[ 
+        prefix := (match at: 2) value.
+        self addClassesStartingWith: prefix
+    ].
+
+    "Created: / 15-05-2014 / 07:16:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!AbstractJavaCompletionSimple methodsFor:'guesswork'!
+
+guessReceiverTypeFrom: tokens before: end
+    | i type |
+
+    i := end - 1.  
+
+    (tokens at: i) type == $) ifTrue:[ 
+        "/ OK, end of message send, scan for method name...
+        | nparens nargs name |
+
+        nparens := 1.
+
+        i := i - 1.
+        nargs := 0.
+        (tokens at: i) type == $( ifTrue:[ 
+            i := i - 1.
+        ] ifFalse:[
+            nargs := 1.
+            [ i > 0 and:[ nparens ~~ 0 ] ] whileTrue:[ 
+                (tokens at: i) type == $) ifTrue:[ 
+                    nparens := nparens + 1 
+                ] ifFalse:[ 
+                    (tokens at: i) type == $( ifTrue:[ 
+                        nparens := nparens - 1 
+                    ] ifFalse:[ 
+                        (((tokens at: i) type == $,) and:[nparens == 1]) ifTrue:[    
+                            nargs := nargs + 1.
+                        ]
+                    ].
+                ].
+                i := i - 1.
+            ].
+        ].
+        nparens ~~ 0 ifTrue:[ 
+            "/ Malformed input
+            ^ Type unknown
+        ].
+        (tokens at: i) type == #Identifier ifFalse:[ 
+            "/ Malformed input
+            ^ Type unknown
+        ].
+        name := (tokens at: i) value.
+        i > 0 ifTrue:[ 
+            (tokens at: i - 1) type == $. ifTrue:[ 
+                type := self guessReceiverTypeFrom: tokens before: i - 1.
+            ] ifFalse:[ 
+                type := Type withClass: class.
+            ].
+            ^ self guessTypeOfMethod: type of: type numArgs: nargs.
+        ].
+    ].
+
+    ^ Type withClass: (context environment classNamed:#'JAVA::java::lang::Object')
+
+    "Created: / 15-05-2014 / 08:09:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-05-2014 / 09:42:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+guessTypeOfMethod: name of: type numArgs: nargs
+    | methods |
+
+    methods := Set new.
+    type classesDo:[:initialClass | 
+        | class |
+
+        class := initialClass.
+        [ class notNil and:[ class ~~ JavaObject  ] ] whileTrue:[
+            class selectorsAndMethodsDo:[:selector :method |
+                method isJavaMethod ifTrue:[ 
+                    (selector size > name size 
+                        and:[ method numJavaArgs = nargs
+                        and:[ (selector at: name size + 1) == $(
+                        and:[ (selector startsWith: name) ]]])
+                        ifTrue:[ methods add: method ].
+                    ].
+            ].
+        ].
+    ].
+
+    self halt.
+
+    "Created: / 15-05-2014 / 09:39:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+