SmallSense__CompletionEngine.st
author Claus Gittinger
Wed, 26 Feb 2014 19:06:00 +0100
changeset 174 3e08d765d86f
parent 136 a1c1b160f2ca
child 176 df6d3225d1e4
permissions -rw-r--r--
sync from current CVS head; fixed comment highlighting for STXEOLRule

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

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


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

addMethodsStartingWith: prefix
    ^ self addMethodsStartingWith: prefix filter: nil

    "Created: / 24-07-2013 / 13:10:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-10-2013 / 17:59:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addMethodsStartingWith: prefix filter: filterOrNil
    | selectors filter |

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

    Smalltalk allClassesDo:[:class|
        class selectorsAndMethodsDo:[:selector :mthd |             
            ((selector startsWith: prefix) and:[mthd isSynthetic not and:[filter value: mthd]]) 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])).
    ]

    "Created: / 03-10-2013 / 17:56:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-10-2013 / 12:13:32 / 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> $'
! !