SmallSense__JavaCompletionEngineSimple.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 08 Apr 2014 21:46:51 +0200
changeset 192 f27ce6dac101
parent 157 c71d2e62ece2
child 205 43bee6463c53
child 229 c82a22d2153d
permissions -rw-r--r--
Initial support for completing selector parts. When user types map at: 1 ifA then the completer also offers to complete `ifAbsent:`, `ifAbsentPut:` ... in addition to SmallInteger methods.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

CompletionEngine subclass:#JavaCompletionEngineSimple
	instanceVariableNames:'class classTree method methodTree'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Java'
!


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

completeSimple
    | line col scanner token tokens values startPositions stopPositions maybeReceiverToken |

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

    "/ ok, we got three character prefix, now scan the current line...
    scanner := JavaScanner for: line.
    tokens := OrderedCollection new.
    values := OrderedCollection new.
    startPositions := OrderedCollection new.
    stopPositions := OrderedCollection new.
    [
        [ (token := scanner nextToken) ~~ #EOF and:[ scanner tokenStartPosition < (col - 1) ] ] whileTrue:[
            tokens add: token.
            values add: scanner tokenValue.
            startPositions add: scanner tokenStartPosition.
            stopPositions add: scanner tokenEndPosition. 
        ].
    ] on: Error do:[ 
        ^ nil 
    ].

    tokens isEmpty ifTrue:[ ^ nil ].
    "/ now, simple check for import declaration
    tokens first == #import and:[
        | prefix |

        prefix := String streamContents:[:s|
            | i |

            i := 2.
            [ i <= tokens size ] whileTrue:[
                (tokens at: i) == #Identifier ifTrue:[
                    s nextPutAll: (values at: i).
                ] ifFalse:[
                    ^ nil "/ malformed import
                ].
                (i < tokens size) ifTrue:[
                    (tokens 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.
    (tokens last ~~ #Identifier or:[values last size < 3]) ifTrue:[ ^ nil ].

    "/ Complete after new keyword
    (tokens size > 1 and:[(tokens at: tokens size - 1) == #new]) ifTrue:[
        self addClassesStartingWith: values last.
        ^ result.
    ].


    "/ now check whether the butlast token is dot...
    maybeReceiverToken := nil.
    (tokens size > 1 and:[(tokens at: tokens size - 1) == $.]) ifTrue:[
        "/ if so, it's likely a message send, then complete methods...
        tokens 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: / 20-10-2013 / 01:32:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompletionEngineSimple methodsFor:'completion-helpers'!

javaClassesDo: aBlock
    | loader loaders |

    loaders := Set new.
    loader := (class notNil and:[class isJavaClass]) ifTrue:[class classLoader] ifFalse:[JavaVM systemClassLoader].
    [ loader notNil ] whileTrue:[
        loaders add: loader.
        loader := loader instVarNamed: #parent.
    ].
    loaders add: nil.

    JavaVM registry  classesDo:[:cls|
        (loaders includes: cls classLoader) ifTrue:[
            aBlock value: cls.
        ].
    ].

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

!JavaCompletionEngineSimple methodsFor:'completion-individual'!

addClassesStartingWith: prefix
    self javaClassesDo:[:cls|
        | name i |

        name := cls lastName.
        i := name lastIndexOf: $/.
        ((name size >= (i + prefix size))
            and:[(name at: i + 1) == prefix first
            and:[(name at: i + prefix size) == prefix last
            and:[(2 to: prefix size - 1) allSatisfy:[:o| (name at: i + o) == (prefix at: o)]]]])
            ifTrue:[
                result add: (ClassPO new subject: cls).        
            ].
    ].

    "Created: / 03-10-2013 / 11:16:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-10-2013 / 01:27:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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 ]

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

!JavaCompletionEngineSimple methodsFor:'completion-private'!

complete
    
    | position entry node |

    position := context codeView characterPositionOfCursor.
    codeView syntaxElements notEmptyOrNil ifTrue:[
        entry := codeView syntaxElements atCharacterPosition: position - 1. 
        entry notNil ifTrue:[
            node := entry node
        ].
        codeView syntaxElements tree notNil ifTrue:[
            classTree := (codeView syntaxElements tree types ? #()) detect:[:t | (position - 1) between: t declarationSourceStart and: t declarationSourceEnd ] ifNone:[nil].
            classTree notNil ifTrue:[
                methodTree := (classTree methods ? #()) detect:[:m | (position - 1) between: m declarationSourceStart and: m declarationSourceEnd ] ifNone:[nil].
            ]
        ].
    ].

    context node: node position: position.

    node isNil ifTrue:[
        self completeSimple.
    ] ifFalse:[
        self completeNode: node.
    ].

    ^ result

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

!JavaCompletionEngineSimple class methodsFor:'documentation'!

version_HG

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