SmallSense__SmalltalkCompletionEngine.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 02 Oct 2013 13:37:01 +0100
changeset 117 441529422c2f
parent 114 SmallSense__SmalltalkCompletion.st@55b3efed5a57
child 120 4fefce92f5bb
permissions -rw-r--r--
Completion support refactored to make it more pluggable/extendable.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

CompletionEngine subclass:#SmalltalkCompletionEngine
	instanceVariableNames:'resultSet 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:'adding'!

addClassVariables
    | class |

    class := collector klass theNonMetaclass.
    class classVarNames do:[:nm|
        resultSet 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.
            cls notNil ifTrue:[
                cls isBehavior ifTrue:[
                    resultSet add:(ClassPO new subject: cls; name: nm).
                ] ifFalse:[
                    resultSet add:(VariablePO globalVariable: cls).
                ]
            ]
        ].
    ].
    ns ~~ Smalltalk ifTrue:[
        Smalltalk keysDo:[:nm|
            (nm startsWith: prefix) ifTrue:[
                cls := Smalltalk classNamed: nm.
                cls notNil ifTrue:[
                    cls isBehavior ifTrue:[
                        resultSet add:(ClassPO new subject: cls; name: nm ).
                    ] ifFalse:[
                        resultSet add:(VariablePO globalVariable: cls).
                    ]
                ]
            ]
        ].
    ]

    "Created: / 26-11-2011 / 17:29:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-07-2013 / 17:00:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsForType: type 
    type 
        classesDo: [:each | 
            | class |

            class := each.
            [ class isNil ] whileFalse: [
                class 
                    selectorsAndMethodsDo: [:selector :met | 
                        resultSet add: (MethodPO 
                                    name: selector
                                    description: nil
                                    class: class).
                    ].
                class := class superclass.
            ].
        ].

    "Created: / 26-11-2011 / 17:03:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix
    | selectors |

    selectors := Dictionary new.


    Smalltalk allClassesDo:[:class|
        class selectorsAndMethodsDo:[:selector :mthd | 
            (selector startsWith: prefix) ifTrue:[
                | class skip |

                class := mthd mclass superclass.
                skip := false.
                [ skip not and:[class notNil] ] whileTrue:[
                    (class methodDictionary includesKey: selector) ifTrue:[
                        skip := true.
                    ].
                    class := class superclass.
                ].
                skip ifFalse:[
                    | classes |

                    classes := selectors at: selector ifAbsentPut:[ Set new ].
                    classes add: mthd mclass.
                ].
            ]
        ].
    ].

    selectors keysAndValuesDo: [:selector :classes|
        resultSet add:(MethodPO 
                name:selector
                description:"met source"nil
                class:(classes size == 1 ifTrue:[classes anElement] ifFalse:[classes])).
    ]

    "Created: / 24-07-2013 / 13:10:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2013 / 02:20:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addPools
    | class |

    class := collector klass theNonMetaclass.
    class theNonMetaclass sharedPools do:[:pool|
        pool theNonMetaclass classVarNames do:[:nm|
            resultSet 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.
        resultSet 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 |
            resultSet add: (VariablePO instanceVariable: nm in: klass).
         ].
         klass := klass superclass.
    ].
    "Add pseudo variables"
    #(self super here thisContext) do:[:nm|
        resultSet add: (VariablePO new name: nm).
    ].
    "Add arguments"
    collector parser methodArgs ? #() do:[:nm|
        resultSet add: (VariablePO argument: nm).
    ].
    "Add temporaries"
    collector parser methodVars ? #() do:[:nm|
        resultSet add: (VariablePO variable: nm).
    ].

    n := node.
    [ n notNil ] whileTrue:[
        n isBlockNode ifTrue:[
            n arguments ? #() do:[:barg|resultSet add: (VariablePO variable: barg name)].
            n variables ? #() do:[:bvar|resultSet 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'!

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 ].
    ^ 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>"
! !

!SmalltalkCompletionEngine methodsFor:'completion-private'!

complete: 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
        completeAtLine:line
        column:col
        collector:inferencer

    "Created: / 02-10-2013 / 13:23:25 / 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"
    
    | position |
    resultSet := CompletionResult new.
    collector := coll.

    (collector tree isNil or:[collector tree == #Error]) ifTrue:[ 
        ^ resultSet 
    ].


    position := SmalltalkParseNodeFinder new 
                    findNodeIn: collector source tree: collector tree 
                    line: line column: col.
    resultSet context: position.


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

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

    "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: / 26-09-2013 / 11:05:26 / 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
        ] 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: / 06-08-2013 / 12:28:48 / 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 $'
! !