SmallSense__SmalltalkCompletionEngine.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 15 May 2014 14:41:52 +0100
changeset 212 a2caebc602a7
parent 210 1922d415c704
child 233 fb33bd6466a4
permissions -rw-r--r--
Fixes and improvements for Java/Groovy completion (part 1) * Better presentation of constructors. * Better alignment of completion window when completing packages / full class names.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

CompletionEngine subclass:#SmalltalkCompletionEngine
	instanceVariableNames:'inferencer'
	classVariableNames:'Debug'
	poolDictionaries:''
	category:'SmallSense-Smalltalk'
!


!SmalltalkCompletionEngine class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    Debug := false.

    "Modified: / 22-01-2014 / 09:08:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine class methodsFor:'accessing'!

debug
    ^ Debug

    "Created: / 22-01-2014 / 09:08:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

debug: aBoolean
    Debug := aBoolean .
    "
    self debug: true.
    self debug: false.
    "

    "Created: / 22-01-2014 / 09:08:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 22-01-2014 / 19:42:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine class methodsFor:'utilities'!

resultSetFor: mode source: source class: class line: line column: col 
    | inferencer tree |

    mode == #method ifTrue:[
        inferencer := SmalltalkInferencer forClass: class methodSource: source asString.
        inferencer parserClass: SmalltalkParser.
    ] ifFalse:[
        self breakPoint: #jv.
        ^nil.
        inferencer := Parser for: (source asString readStream).
        "JV@2011-06-13: HACK, use polymorphism"
        tree := inferencer
            parseExpressionWithSelf:nil 
            notifying:nil 
            ignoreErrors:false 
            ignoreWarnings:false 
            inNameSpace:nil.
        inferencer tree: tree.
    ].
    ^ self new
        completeAtLine:line
        column:col
        inferencer:inferencer

    "Modified: / 07-04-2011 / 22:55:58 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 17:53:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-05-2014 / 12:29:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-individual'!

addClassVariables
    | class |

    class := inferencer klass theNonMetaclass.
    class classVarNames do:[:nm|
        result add:(VariablePO classVariable: nm in: class).
    ].

    "Created: / 24-07-2013 / 17:00:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-07-2013 / 23:32:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addGlobalsStartingWith: prefix

    | class ns cls environment |
    class := inferencer klass.
    ns := class nameSpace.
    environment := context environment.
    "nameSpace may return private class, sigh"
    [ ns isNameSpace ] whileFalse:[ ns := ns nameSpace ].
    ns keysDo:[:nm|
        (nm startsWith: prefix) ifTrue:[
            cls := ns classNamed: nm.
            (cls notNil and:[cls name = nm]) ifTrue:[
                (JavaPackage isNil or:[cls isJavaPackage not]) ifTrue:[
                    result add:(ClassPO new subject: cls; showPrefix: cls isJavaClass).
                ]
            ] ifFalse:[
                (self isGlobalKeyForClassVariable: nm) ifFalse:[  
                    result add:(VariablePO globalVariable: nm)
                ].
            ].
        ].
    ].
    ns ~~ environment ifTrue:[
        environment keysDo:[:nm|
            (nm startsWith: prefix) ifTrue:[
                cls := environment classNamed: nm.
                (JavaPackage isNil or:[cls isJavaPackage not ]) ifTrue:[
                    cls notNil ifTrue:[
                        cls isBehavior ifTrue:[
                            result add:(ClassPO new subject: cls; showPrefix: cls isJavaClass).
                        ] ifFalse:[
                            (self isGlobalKeyForClassVariable: nm) ifFalse:[  
                                result add:(VariablePO globalVariable: nm).
                            ].
                        ]
                    ]
                ]
            ]
        ].
    ]

    "Created: / 26-11-2011 / 17:29:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-05-2014 / 12:09:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addPools
    | class |

    class := inferencer klass theNonMetaclass.
    class theNonMetaclass sharedPools do:[:pool|
        pool theNonMetaclass classVarNames do:[:nm|
            result add:(VariablePO classVariable: nm in: pool).
        ]
    ].

    "Created: / 24-07-2013 / 16:59:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-07-2013 / 23:32:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addPrivateClasses
    | class |


    class := inferencer klass theNonMetaclass.
    class privateClassesDo:[:pclass|
        | nm |

        nm := pclass fullName copyFrom: class fullName size + 3.
        result add:(ClassPO new subject: pclass; name: nm).
    ]

    "Created: / 06-08-2013 / 12:28:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addVariablesFor: node

    | n klass |

    "Add Instance variables"
    klass := inferencer klass.
    [ klass notNil ] whileTrue:[
        | usedInstVars |

        usedInstVars := inferencer parser usedInstVars. 
        klass instVarNames do:[:nm |
            | po |

            po := VariablePO instanceVariable: nm in: klass.
            "/ Raise relevance if the instvar is already used in the code...
            (usedInstVars includes: nm) ifTrue:[
                po relevance: (po relevance + 10).
            ].

            result add: po.
        ].
        "/ When on class side (i.e., in class method), do not complete
        "/ instance variables of Class / ClassDescription / Behaviour
        "/ as STC won't compile such code.
        klass := (klass isMetaclass and:[klass superclass == Class]) 
                    ifTrue:[nil]
                    ifFalse:[klass superclass].
    ].
    "Add pseudo variables"
    #(self super here thisContext) do:[:nm|
        result add: (VariablePO new name: nm).
    ].
    "Add arguments"
    inferencer parser methodArgs ? #() do:[:nm|
        result add: (VariablePO argument: nm).
    ].
    "Add temporaries"
    inferencer parser methodVars ? #() do:[:nm|
        result add: (VariablePO variable: nm).
    ].
    "Add literals"
    #(#true #false #nil ) do:[:nm|
        result add: (SnippetPO new subject: nm).
    ].


    n := node.
    [ n notNil ] whileTrue:[
        n isBlockNode ifTrue:[
            n arguments ? #() do:[:barg|result add: (VariablePO variable: barg name)].
            n variables ? #() do:[:bvar|result add: (VariablePO variable: bvar name)].
        ].
        n := n parent.
    ]

    "Created: / 31-07-2013 / 00:32:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-01-2014 / 19:42:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-private'!

complete
    "Compute completion for `codeView`, taking all the information
     from it. Returns a CompletionResult with computed completions"

    | class |

    codeView := context codeView.
    class := codeView isCodeView2
                ifTrue: [ codeView klass ]  
                ifFalse: [ codeView editedClass ].
    class isNil ifTrue:[
        class := UndefinedObject.
    ].
    ^ self complete: codeView codeAspect source: codeView contents class: class line: codeView cursorLine column: codeView cursorCol

    "Created: / 02-10-2013 / 13:32:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-01-2014 / 23:20:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

complete: mode source: source class: class line: lineNrArg column: colNrArg 
    | inf lineNr colNr |

    mode == #method ifTrue:[
        lineNr := lineNrArg.
        colNr := colNrArg.
        inf := SmalltalkInferencer forClass: class methodSource: source asString.
    ] ifFalse:[
        | line |

        lineNr := 1.
        colNr := colNrArg.
        line := codeView list at: lineNrArg ifAbsent:[ nil ].
        line isEmptyOrNil ifTrue:[ ^ nil ].
        inf := SmalltalkInferencer forExpression: line.
    ].
    inf parserClass: SmalltalkParser.

    ^ self
        completeAtLine:lineNr
        column:colNr
        inferencer:inf

    "Created: / 02-10-2013 / 13:23:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-05-2014 / 12:29:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeAfter:node
    "return collection of completion items after given node"

    | type |

    type := node inferedType.
    type isUnknownType ifFalse:[
        self addMethodsForType: node inferedType
    ].

    "Created: / 04-03-2011 / 15:45:28 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 10:55:09 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 17:07:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2013 / 02:15:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeAtLine:line column:col inferencer:inferencerArg 
    "find most possible codeCompletion object"

    | nodeToPosition |

    inferencer := inferencerArg.
    inferencer process.
    (inferencer tree isNil or:[inferencer tree == #Error]) ifTrue:[ 
        ^ nil 
    ].
    inferencer environment: context environment.

    nodeToPosition := SmalltalkParseNodeFinder new 
                        findNodeIn: inferencer source tree: inferencer tree comments: inferencer parser commentPositions
                        line: line column: col.
    context node: nodeToPosition key position: nodeToPosition value.

    context isAfterNode ifTrue:[
        self completeAfter:context node.
    ] ifFalse:[
    context isInNode ifTrue:[
        self completeIn:context node.
    ] ifFalse:[
    context isBeforeNode ifTrue:[
        self completeBefore:context node.
    ]]].

    result isEmpty ifTrue:[
        nil "/Only to set breakpoint here
    ].
    ^result.

    "Created: / 13-05-2014 / 12:29:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeBefore:node

    self breakPoint: #jv. "Not yet implemented"

    "Created: / 04-03-2011 / 15:45:28 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 10:55:09 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 17:07:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeIn:node 
    "return collection which can be afterNode"
    
    node isVariableNode ifTrue:[
        self completeInVariableNode:node.
        ^ self.
    ].
    node isMessage ifTrue:[
        self completeInMessageNode:node.
        ^ self
    ].
    self breakPoint:#jv.

    "Created: / 07-03-2011 / 18:59:02 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 09:31:51 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 17:07:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-04-2014 / 20:52:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeInMessageNode:node 
    | parent |


    self addMethodsForType: node receiver inferedType prefix: node selector stripOff: nil.
    parent := node parent.
    parent isMessage ifTrue:[
        self addMethodsForType: parent receiver inferedType prefix: node selector stripOff: parent selector.
    ].

    "Modified (format): / 08-04-2014 / 21:16:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeInVariableNode:node 
    node name first isUppercase ifTrue:[
        self addGlobalsStartingWith:node name.
        self addClassVariables.
        self addPools.
        self addPrivateClasses.
    ] ifFalse:[
        self addVariablesFor:node
    ]
! !

!SmalltalkCompletionEngine methodsFor:'queries'!

isGlobalKeyForClassVariable: aString
    | i |

    i := 0.
    [ 
        i := aString indexOf: $: startingAt: i + 1.
        i ~~ 0 
    ] whileTrue:[ 
        aString size > i ifTrue:[ 
            (aString at: i + 1) ~~ $: ifTrue:[ 
                ^ true
            ].
        ].
        i := i + 1.
    ].
    ^ false

    "
    SmalltalkCompletionEngine new isGlobalKeyForClassVariable: 'AAA'
    SmalltalkCompletionEngine new isGlobalKeyForClassVariable: 'AAA:X'
    SmalltalkCompletionEngine new isGlobalKeyForClassVariable: 'BB::CC::AA'
    SmalltalkCompletionEngine new isGlobalKeyForClassVariable: 'BB::CC::AA:X'
    "

    "Created: / 09-04-2014 / 13:49:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '$Id: SmallSense__SmalltalkCompletionEngine.st,v 1.2 2014/02/12 14:49:29 sr Exp $'
! !


SmalltalkCompletionEngine initialize!