SmallSense__SmalltalkCompletionEngine.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 17 Oct 2013 01:41:47 +0100
changeset 132 7c23c51d2cfd
parent 131 ea84eea5a3c4
child 133 bd659b67811c
permissions -rw-r--r--
Completion insertion refactoring. Added language and codeView into CompletionContext. Added context slot into PO so the PO itself know the completion context and can tweak its presentation accordingly. Also, actual text insertion is now delegated to the PO so the PO can insert proper text according to the context (especially - language)

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

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


!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.
        inferencer process.
    ] 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
        collector: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: / 02-09-2013 / 14:43:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 02-10-2013 / 13:09:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine methodsFor:'completion'!

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

    | class |

    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: / 04-10-2013 / 08:18:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-helpers'!

javaClassesDo: aBlock
    | class loader loaders |

    class := collector klass.
    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>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-individual'!

addClassVariables
    | class |

    class := collector 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 |
    class := collector klass.
    ns := class nameSpace.
    "nameSpace may return private class, sigh"
    [ ns isNameSpace ] whileFalse:[ ns := ns nameSpace ].
    ns keysDo:[:nm|
        (nm startsWith: prefix) ifTrue:[
            cls := ns classNamed: nm.
            (JavaPackage isNil or:[cls isJavaPackage not]) ifTrue:[
                cls notNil ifTrue:[
                    cls isBehavior ifTrue:[
                        result add:(ClassPO new subject: cls).
                    ] ifFalse:[
                        result add:(VariablePO globalVariable: cls).
                    ]
                ]
            ]
        ].
    ].
    ns ~~ Smalltalk ifTrue:[
        Smalltalk keysDo:[:nm|
            (nm startsWith: prefix) ifTrue:[
                cls := Smalltalk classNamed: nm.
                (JavaPackage isNil or:[cls isJavaPackage not ]) ifTrue:[
                    cls notNil ifTrue:[
                        cls isBehavior ifTrue:[
                            result add:(ClassPO new subject: cls).
                        ] ifFalse:[
                            result add:(VariablePO globalVariable: cls).
                        ]
                    ]
                ]
            ]
        ].
    ]

    "Created: / 26-11-2011 / 17:29:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 16:36:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addJavaClassesInPackage: prefix
    prefix isEmptyOrNil ifTrue:[
        self javaClassesDo: [:cls |
            result add: (ClassPO new klass: cls; showPrefix: true; yourself)
        ].
    ] ifFalse:[
        self javaClassesDo: [:cls |
            (cls name startsWith: prefix) ifTrue:[
                result add: (ClassPO new klass: cls; showPrefix: true; yourself)
            ].
        ].

    ].

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

addMethodsForType: type 
    | classes seen |

    classes := type classes.
    classes size == 1 ifTrue:[
        classes anElement == JavaPackage class ifTrue:[  
            "/ Special hack for JAVA: for pattern `JAVA java lang reflect`
            "/ complete all Java classes in that package
            | node |

            node := result context node.
            node isUnaryMessage ifTrue:[
                | package |
                "/ Compute package prefix...

                package := node selector.
                node := node receiver.
                [ node isUnaryMessage ] whileTrue:[
                    package := node selector , '/' , package.
                    node := node receiver.
                ].
                self addJavaClassesInPackage: package.
                ^ self.
            ]
        ]
    ].

    seen := Set new.
    type  classesDo: [:each | 
        | class |

        class := each.
        [ class notNil and:[(seen includes: class) not]] whileTrue: [
            seen add: class.
            "/ Now, special care for Java classes, sigh...
            (class isMetaclass and:[class theNonMetaclass isJavaClass]) ifTrue:[
                class theNonMetaclass selectorsAndMethodsDo: [:selector :met | 
                    met isStatic ifTrue:[
                        result add: (MethodPO 
                                    name: selector
                                    class: met mclass).
                    ].
                ].
            ] ifFalse:[
                class selectorsAndMethodsDo: [:selector :met | 
                    result add: (MethodPO 
                                name: selector
                                class: met mclass).
                ].
            ].
            class := class superclass.
        ]
    ].

    "Created: / 26-11-2011 / 17:03:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-10-2013 / 01:04:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addPools
    | class |

    class := collector 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 := collector 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 := collector klass.
    [ klass notNil ] whileTrue:[
         klass instVarNames do:[:nm |
            result add: (VariablePO instanceVariable: nm in: klass).
         ].
         klass := klass superclass.
    ].
    "Add pseudo variables"
    #(self super here thisContext) do:[:nm|
        result add: (VariablePO new name: nm).
    ].
    "Add arguments"
    collector parser methodArgs ? #() do:[:nm|
        result add: (VariablePO argument: nm).
    ].
    "Add temporaries"
    collector parser methodVars ? #() do:[:nm|
        result add: (VariablePO variable: 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: / 18-09-2013 / 00:28:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-private'!

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

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

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

    ^ self
        completeAtLine:lineNr
        column:colNr
        collector:inferencer

    "Created: / 02-10-2013 / 13:23:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-10-2013 / 13:43:33 / 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 collector:coll 
    "find most possible codeCompletion object"
    
    | context |

    collector := coll.
    (collector tree isNil or:[collector tree == #Error]) ifTrue:[ 
        ^ nil 
    ].
    context := SmalltalkParseNodeFinder new 
                    findNodeIn: collector source tree: collector tree 
                    line: line column: col.
    context codeView: codeView.
    context language: SmalltalkLanguage instance.
    result context: context.


    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: / 04-03-2011 / 13:01:14 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 10:52:59 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 17:05:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-10-2013 / 00:34:42 / 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:[
        node name first isUppercase ifTrue:[
            self addGlobalsStartingWith: node name.
            self addClassVariables.
            self addPools.
            self addPrivateClasses.
        ] ifFalse:[
            self addVariablesFor: node
        ].
        ^self.
    ].

    node isMessage ifTrue:[
        | type |

        type := node receiver inferedType.
        type isUnknownType ifFalse:[
            self addMethodsForType: type.
            "/ If the type is union of more than 6 types, then
            "/ assume that the inferencer is likely wrong.
            "/ then, if the prefix is at least 3 chars,
            "/ also add methods with that prefix.
            ((type classes size > 6) and:[node selector size > 2]) ifTrue:[
                self addMethodsStartingWith: node selector.
            ].
        ] ifTrue:[
            self addMethodsStartingWith: node selector.
        ].

        ^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: / 16-10-2013 / 15:53:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkCompletionEngine class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '$Id: SmallSenseRecognizer.st 7826 2011-11-27 09:48:43Z vranyj1 $'
! !