SmallSense__CompletionEngine.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 }"

Object subclass:#CompletionEngine
	instanceVariableNames:'codeView result context'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core'
!


!CompletionEngine class methodsFor:'accessing'!

exactMatcher
    "Return a match block returning true, if given selector start with given prefix"

    ^ [ :prefix :selector | selector startsWith: prefix ]

    "Created: / 08-04-2014 / 21:31:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inexactMatcher
    "Return a match block returning true, if given prefix matches given selector"

    ^ [ :prefix :selector |
        prefix size < 5 ifTrue:[ 
            selector startsWith: prefix.  
        ] ifFalse:[ 
            | part |

            part := selector copyTo: (prefix size min: selector size).
            (prefix levenshteinTo: part) < 15
        ].
    ].

    "Created: / 08-04-2014 / 21:30:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

matcher
    "Return a match block returning true, if given prefix matches given selector"

    ^ [ :prefix :selector |
        prefix size < 5 ifTrue:[ 
            selector startsWith: prefix.  
        ] ifFalse:[ 
            | part |

            part := selector copyTo: (prefix size min: selector size).
            (prefix levenshteinTo: part) < 15
        ].
    ].

    "Created: / 02-04-2014 / 23:30:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionEngine class methodsFor:'testing'!

isAbstract
    ^ self == CompletionEngine

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

!CompletionEngine methodsFor:'completion'!

complete: aCompletionContext
    "Compute completion for given completion context, taking all the information
     from it. Returns a CompletionResult with computed completions"

    context := aCompletionContext.
    result := CompletionResult new.
    codeView := context codeView.
    result context: context.
    ^ self complete.

    "Created: / 21-01-2014 / 23:07:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completeFor: aCodeView2OrTextEditView
    "Compute completion for given codeView, taking all the information
     from it. Returns a CompletionResult with computed completions"

    codeView := aCodeView2OrTextEditView.
    result := CompletionResult new.

    ^ self complete.

    "Created: / 02-10-2013 / 13:24:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 16:42:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionEngine methodsFor:'completion-individual'!

addClassesInJavaPackage: prefix
    prefix isEmptyOrNil ifTrue:[
        context environment allClassesDo: [:cls |
            cls isJavaClass ifTrue:[
                result add: (ClassPO new klass: cls; showPrefix: true; yourself)
            ].
        ].
    ] ifFalse:[
        context environment allClassesDo: [:cls |
            (cls isJavaClass and:[cls binaryName startsWith: prefix]) ifTrue:[
                result add: (ClassPO new klass: cls; showPrefix: true; yourself)
            ].
        ].

    ].

    "Created: / 15-05-2014 / 11:43:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsForType: type 
    | classes seen |

    classes := type classes.
    "/ Hack for Boolean: ifTrue:iFalse: etc are not defined
    "/ in Boolean ?!!?
    (classes size == 1 and:[classes anElement == Boolean ]) ifTrue:[
        classes := Array with: True with: False.
    ].
    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 addClassesInJavaPackage: package.
                ^ self.
            ]
        ]
    ].

    seen := Set new.
    classes do: [: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 | 
                    "/ Do not offer synthetic methods and Java ctors
                    (met isSynthetic or:[met isJavaMethod and:[met selector startsWith: '<init>']]) ifFalse:[
                        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: / 15-05-2014 / 11:43:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsForType: type prefix: prefix stripOff: stripprefix

    type isUnknownType ifFalse:[
        self addMethodsForType:type stripOff: stripprefix.
        
        "/ 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:[ prefix size > 2 ]) ifTrue:[
            self addMethodsStartingWith:prefix stripOff: stripprefix
        ].
    ] ifTrue:[
        self addMethodsStartingWith:prefix stripOff: stripprefix  
    ].

    "Created: / 08-04-2014 / 21:04:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-04-2014 / 09:31:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsForType: type stripOff: stripprefix     
    | classes seen |

    classes := type classes.
    "/ Hack for Boolean: ifTrue:iFalse: etc are not defined
    "/ in Boolean ?!!?
    (classes size == 1 and:[classes anElement == Boolean ]) ifTrue:[
        classes := Array with: True with: False.
    ].
    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 addClassesInJavaPackage: package.
                ^ self.
            ]
        ]
    ].

    seen := Set new.
    classes do: [: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 | 
                    met isSynthetic ifFalse:[
                        (stripprefix isNil or:[ selector size > stripprefix size and:[selector startsWith: stripprefix]]) ifTrue:[
                            result add: (MethodPO 
                                        name: selector
                                        class: met mclass
                                        stripOff: stripprefix).
                        ].
                    ]
                ].
            ].
            class := class superclass.
        ]
    ].

    "Created: / 08-04-2014 / 21:23:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-05-2014 / 11:43:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix
    ^ self addMethodsStartingWith: prefix stripOff: nil filter: nil

    "Created: / 24-07-2013 / 13:10:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-04-2014 / 21:36:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix stripOff: stripoffPrefix 
    ^ self addMethodsStartingWith: prefix stripOff: stripoffPrefix filter: nil

    "Created: / 08-04-2014 / 21:36:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix stripOff: stripoffPrefix filter: filterOrNil
    | matcher |

    matcher := stripoffPrefix isEmptyOrNil ifTrue:[ CompletionEngine inexactMatcher ] ifFalse:[ CompletionEngine exactMatcher ].
    ^ self addMethodsStartingWith: prefix stripOff: stripoffPrefix filter: filterOrNil matcher: matcher.

    "Created: / 08-04-2014 / 21:35:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix stripOff: stripoffPrefix filter: filterOrNil matcher: matcher
    | matchPrefix selectors filter |

    selectors := Dictionary new.
    matchPrefix := stripoffPrefix isNil ifTrue:[ prefix ] ifFalse:[ stripoffPrefix , prefix ]. 
    filter := filterOrNil  isNil ifTrue:[ [:method | true ] ] ifFalse:[ filterOrNil  ].

    context environment allMethodsWithSelectorDo:[:mthd :selector|
        (mthd isSynthetic not and:[(filter value: mthd) and:[ matcher value: matchPrefix value: selector]]) 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 includes: mthd mclass) ifFalse:[
                    classes add: mthd mclass.
                ].
            ].
        ]
    ].


    selectors keysAndValuesDo: [:selector :classes|
        result add:(MethodPO 
                name:selector
                class:(classes size == 1 ifTrue:[classes anElement] ifFalse:[classes])
                stripOff: stripoffPrefix)
    ]

    "Created: / 08-04-2014 / 21:34:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-05-2014 / 12:30:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionEngine methodsFor:'completion-private'!

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

    ^ self subclassResponsibility

    "Modified (comment): / 02-10-2013 / 13:33:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompletionEngine class methodsFor:'documentation'!

version_HG

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