SmallSense__Recognizer.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 26 Aug 2013 10:33:23 +0100
changeset 67 020b7461b15e
parent 64 2257d7223898
child 69 1a143dfff51b
permissions -rw-r--r--
Package structure reorganization. SmallSense is no longer Smalltalk-specific but it provides infrastructure to build support for other languages as well. Therefore classes and class categories were renamed to reflect whether it is a reusable *core* thing or Smalltalk-specific code.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#Recognizer
	instanceVariableNames:'resultSet collector'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core'
!


!Recognizer class methodsFor:'utilities'!

old_resultSetFor: mode source: source class: class row: row column: col 

    | parser tree |


    mode == #method ifTrue:[
        parser := Parser new.
        parser 
            parseMethod:source asString
            in: class
            ignoreErrors:false
            ignoreWarnings:false.
    ] ifFalse:[
        parser := Parser for: (source asString readStream).
        "JV@2011-06-13: HACK, use polymorphism"
        tree := parser
            parseExpressionWithSelf:nil 
            notifying:nil 
            ignoreErrors:false 
            ignoreWarnings:false 
            inNameSpace:nil.
        parser tree: tree.
    ].
    ^ self new
        recognize:row
        position:col
        collector:parser

    "Modified: / 07-04-2011 / 22:55:58 / Jakub <zelenja7@fel.cvut.cz>"
    "Created: / 26-11-2011 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

resultSetFor: mode source: source class: class line: line column: col 

    | inferencer tree |


    mode == #method ifTrue:[
        inferencer := Inferencer forClass: class methodSource: source asString.
        inferencer parserClass: Parser.
        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: / 19-08-2013 / 15:12:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Recognizer 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>"
!

addMethods: type

    type classesDo:[:each|
        | class |

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

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

addMethodsStartingWith: prefix

    Smalltalk allClassesDo:[:class|
        class selectorsAndMethodsDo:[:selector :met | 
            (selector startsWith: prefix) ifTrue:[
                resultSet add:(MethodPO 
                            name:selector
                            description:"met source"nil
                            class:class).
            ]
        ].
    ].

    "Created: / 24-07-2013 / 13:10:51 / 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 |

    "Add Instance variables"
    collector klass allInstVarNames do:[:nm|
        resultSet add: (VariablePO instanceVariable: nm in: collector klass).
    ].
    "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>"
! !

!Recognizer methodsFor:'completion'!

completeAtLine:line column:col collector:coll 
    "find most possible codeCompletion object"
    
    | position |
    resultSet := ResultSet new.
    collector := coll.

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


    position := Finder new 
                    findNodeIn: collector source tree: collector tree 
                    line: line column: col.
    resultSet position: 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 (format): / 24-07-2013 / 16:00:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Recognizer methodsFor:'completion-private'!

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

    self addMethods: 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>"
!

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 addMethods:  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>"
! !

!Recognizer methodsFor:'obsolete'!

addSendsAndMethodFromAssignmentsFromRoelTyperResult:result 
    "we have roelTyperResult for exact node we add all sends and all methods which we can find in assignments"
    
    |retCollection class|

    retCollection := ResultSet new.

    "
    (result interface) do:[:send|
        retCollection add: (SmallSenseMethod name:send description:'Used sender.'). 
    ].
    "
    result assignments do:[:assignment | 
         class := assignment.
        [ class isNil ] whileFalse:[
            class 
                selectorsAndMethodsDo:[:selector :met | 
                    retCollection add:(MethodPO 
                                name:selector
                                description:"met source"nil
                                class:class).
                ].
            class := class superclass.
        ].
    ].
    ^ retCollection.

    "Created: / 07-03-2011 / 18:20:15 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 10:15:20 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 18:51:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

before
    "BasicCollection for allNode which are before "
    
    |retCollection|

    retCollection := ResultSet new.
    retCollection join:(self beforeConstant).
    retCollection join:(self beforeBlock).
    ^ retCollection.

    "Created: / 04-03-2011 / 12:36:56 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 17-03-2011 / 18:32:38 / Jakub <zelenja7@fel.cvut.cz>"
!

before:foundNode collector:collector 
    "BasicCollection for allNode which are before node"
    
    |retCollection helper receiver node helperNode ret|

    "Check nil node"
    retCollection := ResultSet new.
    (foundNode isNil) ifTrue:[
        retCollection join:(self beforeConstant).
        retCollection join:(self beforeBlock).
        retCollection join:(self beforeVariable:collector).
        ^ retCollection.
    ].
    (foundNode node isNil) ifTrue:[
        node := foundNode statement.
    ] ifFalse:[
        node := foundNode node.
    ].
    helperNode := foundNode node.
    (node isErrorNode) ifTrue:[
        helper := foundNode beforeStatement.
        (helper notNil) ifTrue:[
            foundNode node:helper.
            foundNode beforeNode:false.
            foundNode afterNode:true.
            ret := self after:foundNode collector:collector.
            foundNode node:helperNode.
            ^ ret.
        ]
    ].
    node isSelector ifTrue:[
        receiver := self getReceiverinNodeForSelector:node
                    node:foundNode statement.
        (receiver notNil) ifTrue:[
            (receiver isMessage 
                or:[
                    receiver isAssignment 
                        or:[ receiver isErrorNode or:[ receiver isSelector ] ]
                ]) 
                    ifFalse:[
                        foundNode node:receiver.
                        foundNode beforeNode:false.
                        foundNode afterNode:true.
                        ret := self after:foundNode collector:collector.
                        foundNode node:helperNode.
                        ^ ret.
                    ]
        ].
    ].
    retCollection join:(self beforeBlockVariable:foundNode).
    retCollection join:(self beforeConstant).
    retCollection join:(self beforeBlock).
    retCollection join:(self beforeVariable:collector).
    ^ retCollection.

    "Created: / 04-03-2011 / 13:02:42 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 06-04-2011 / 18:48:29 / Jakub <zelenja7@fel.cvut.cz>"
!

beforeBlock
    "There is some basic blocks which can be before node"
    
    |retCollection|

    retCollection := ResultSet new.
    retCollection add:(SnippetPO name:'()ifTrue:[].'
                description:'True block
                     ()ifTrue:[].').
    retCollection add:(SnippetPO name:'()ifFalse:[].'
                description:'False block
                     ()ifFalse:[].').
    retCollection add:(SnippetPO name:'[]whileTrue:[].'
                description:'WhileTrue block
                     ()whileTrue:[].').
    retCollection add:(SnippetPO name:'[]whileFalse:[].'
                description:'WhileFalse block
                     ()whileFalse:[].').
    retCollection 
        add:(SnippetPO name:'[]' description:'Closure to block').
    retCollection add:(SnippetPO name:'()' description:'Brackets').
    ^ retCollection.

    "Created: / 04-03-2011 / 12:46:15 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 17-03-2011 / 17:31:25 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 04-04-2011 / 13:42:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

beforeBlockVariable:foundNode 
    "Add variables from Block Node"
    
    |retCollection|

    retCollection := ResultSet new.
    (foundNode blockVariables notNil) ifTrue:[
        foundNode blockVariables do:[:each | 
            retCollection add:(VariablePO name:each name
                        description:'Variables in the method. Defined in block  [:val| ]').
        ].
    ].
    ^ retCollection

    "Created: / 06-04-2011 / 18:48:29 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 20-05-2011 / 14:36:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

beforeConstant
    "There is some basic constant which can be before node"
    
    |retCollection|
    retCollection := ResultSet new.
    retCollection add:(ConstantPO name:'^'
                description:'Return symbol from method.
For example: ^ nil').
    retCollection 
        add:(ConstantPO name:':=' description:'Assignment to variable').
    retCollection add:(ConstantPO name:'self'
                description:'Reference to self class. 
Access to method from this class. 
For example: self someMethod.').
    retCollection add:(ConstantPO name:'super'
                description:'Reference to super class. 
Access to method from super class. 
For example: super someMethod.').
    retCollection add:(ConstantPO name:'nil'
                description:'Nil. In c# or java null. Something empty').
    retCollection add:(ConstantPO name:'true' description:'True.').
    retCollection add:(ConstantPO name:'false' description:'False').
    retCollection add:(ConstantPO name:'#'
                description:'Symbol reference. 
For example: #Symbol').
    retCollection add:(ConstantPO name:'$'
                description:'Character symbol. 
For example #a').
    ^retCollection.

    "Created: / 04-03-2011 / 12:40:45 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 04-04-2011 / 13:44:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-04-2011 / 23:01:55 / Jakub <zelenja7@fel.cvut.cz>"
!

beforeVariable:collector 
    "There is some variables which can be before node"
    
    |retCollection roelTyper helper class|
    retCollection := ResultSet new.
    (collector isNil) ifTrue:[
        ^ retCollection.
    ].
    (collector methodArgs notNil) ifTrue:[
        collector methodArgs do:[:each | 
            retCollection add:(VariablePO name:each
                        description:'Arguments in the method. Defined in method:val').
        ].
    ].
    roelTyper := self doForSource:collector.
    roelTyper instVars do:[:var | 
        retCollection add:(VariablePO name:var
                    description:'Instance variables. Variables defined in instanceVariableNames')
    ].
    helper := roelTyper localTypingResults 
                at:roelTyper currentExtractedMethod.
    helper do:[:each | 
        (each tempName notNil) ifTrue:[
            retCollection add:(VariablePO name:each tempName
                        description:'Variables in the method. Defined in |val val2|').
        ].
    ].
    class := collector targetClass.
    [ class notNil ] whileTrue:[
        class classVarNames do:[:each | 
            retCollection add:(VariablePO name:each
                        description:'Class variables. Variables defined in classVariableNames').
        ].
        class := class superclass.
    ].
    ^ retCollection.

    "Created: / 04-03-2011 / 13:03:44 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 04-04-2011 / 13:44:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-04-2011 / 22:54:47 / Jakub <zelenja7@fel.cvut.cz>"
!

beforeVariable:collector nodeName:nodeName 
    "There is some variables which can be before node"
    
    |retCollection roelTyper helper class|

    retCollection := ResultSet new.
    (collector isNil) ifTrue:[
        ^ retCollection.
    ].
    (collector methodArgs notNil) ifTrue:[
        collector methodArgs do:[:each | 
            (each asLowercase startsWith:nodeName asLowercase) ifTrue:[
                retCollection add:(VariablePO name:each
                            description:'Arguments in the method. Defined in method:val').
            ].
        ].
    ].
    roelTyper := self doForSource:collector.
    roelTyper instVars do:[:var | 
        (var asLowercase startsWith:nodeName asLowercase) ifTrue:[
            retCollection add:(VariablePO name:var
                        description:'Instance variables. Variables defined in instanceVariableNames')
        ].
    ].
    helper := roelTyper localTypingResults 
                at:roelTyper currentExtractedMethod.
    helper do:[:each | 
        (each tempName notNil) ifTrue:[
            (each tempName asLowercase startsWith:nodeName asLowercase) ifTrue:[
                retCollection add:(VariablePO name:each tempName
                            description:'Variables in the method. Defined in |val val2|').
            ].
        ].
    ].
    class := collector targetClass.
    [ class notNil ] whileTrue:[
        class classVarNames do:[:each | 
            (each asLowercase startsWith:nodeName asLowercase) ifTrue:[
                retCollection add:(VariablePO name:each
                            description:'Class variables. Variables defined in classVariableNames').
            ].
        ].
        class := class superclass.
    ].
    ^ retCollection.

    "Modified: / 04-04-2011 / 13:44:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 06-04-2011 / 16:34:15 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 06-04-2011 / 23:48:55 / Jakub <zelenja7@fel.cvut.cz>"
!

createSelectorFromMessageNode:actualStatement 
    "Creates selector node from selector in messageNode"
    
    |helperNode|

    (actualStatement isNil) ifTrue:[
        helperNode := SelectorNode new.
    ] ifFalse:[
        helperNode := SelectorNode new.
        helperNode receiver: actualStatement receiver.
        helperNode selectors:actualStatement selector.
        helperNode selectorsPosition:actualStatement selectorPosition.
        helperNode lines:actualStatement lines.
    ].
    ^ helperNode.

    "Created: / 07-03-2011 / 17:49:33 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 21:10:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doForSource: compiller
       " | parser|
        parser:=SmallSenseParser new.
        parser sourceText:(compiller sourceStream collection asString) asText.
          parser 
        parseMethod:compiller sourceStream collection asString
        in:compiller targetClass
        ignoreErrors:false
        ignoreWarnings:false."
^self processMethod: compiller sourceStream collection asString class:compiller targetClass parser:compiller.

    "Created: / 04-03-2011 / 12:54:09 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 06-04-2011 / 14:13:15 / Jakub <zelenja7@fel.cvut.cz>"
!

getReceiverinNodeForSelector:selector node:node 
    "Gets receiver for selectorNode in node"
    
    |helperSelector receiver|

    selector receiver ifNotNil:[^selector receiver]. 

    (node isMessage) ifFalse:[
        "no reciver"
        ^ nil.
    ].
    receiver := node receiver.
    helperSelector := self createSelectorFromMessageNode:node.
    ((selector lines) = (helperSelector lines) 
        and:[
            (selector selectors asString) = (helperSelector selectors asString) 
                and:[ (selector selectorsPosition) = (helperSelector selectorsPosition) ]
        ]) 
            ifTrue:[
                ^ receiver.
            ]
            ifFalse:[
                (receiver isMessage) ifTrue:[
                    ^ self getReceiverinNodeForSelector:selector node:node receiver.
                ]
            ].
    ^ nil.

    "Created: / 07-03-2011 / 19:01:44 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 18:35:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inClassName:nodeName 
    "Find all classes which start this Name"
    
    |classes retCollection|

    classes := Smalltalk allClasses 
                select:[:cls | cls name startsWith:nodeName].
    retCollection := ResultSet new.
    classes do:[:cls | 
        retCollection 
            add:(ClassPO subject: cls)
    ].
    ^ retCollection.

    "Created: / 06-04-2011 / 16:21:53 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 18:37:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inNode:foundNode collector:collector 
    "return collection which can be afterNode"
    
    |retCollection receiver node befStatement|

    (foundNode node isNil) ifTrue:[
        node := foundNode statement.
    ] ifFalse:[
        node := foundNode node.
    ].
    retCollection := ResultSet new.
    (node isVariable) ifTrue:[
        retCollection := self beforeVariable:collector nodeName:node name.
        retCollection join:(self beforeBlockVariable:foundNode).
        retCollection join:(self inClassName:node name).
        ^ retCollection.
    ].
    (node isConstant) ifTrue:[
        ^ nil.
    ].
    (node isSelf) ifTrue:[
        retCollection add:(ConstantPO name:'self'
                    description:'Reference to self class. 
Access to method from this class. 
For example: self someMethod.').
        ^ retCollection.
    ].
    (node isSuper) ifTrue:[
        retCollection add:(ConstantPO name:'super'
                    description:'Reference to super class. 
Access to method from super class. 
For example: super someMethod.').
        ^ retCollection.
    ].
    (node isAssignment) ifTrue:[
        ^ self before:foundNode collector:collector.
    ].
    (node isMessage) ifTrue:[
        ^ self before:foundNode collector:collector.
    ].
    (node isBlock) ifTrue:[
        retCollection join:(self before:foundNode collector:collector).
        ^ retCollection.
    ].
    node isSelector ifTrue:[
        receiver := self getReceiverinNodeForSelector:node
                    node:foundNode statement.
        (receiver isNil) ifTrue:[
            "Try to get receiver from cascadeNode"
            befStatement := foundNode beforeStatement.
            [
                befStatement isMessage
            ] whileTrue:[
                receiver := befStatement receiver.
                befStatement := receiver.
            ].
        ].
        (receiver notNil) ifTrue:[
            (receiver isMessage 
                or:[
                    receiver isAssignment 
                        or:[ receiver isErrorNode or:[ receiver isSelector ] ]
                ]) 
                    ifFalse:[
                        foundNode node:receiver.
                        foundNode beforeNode:false.
                        foundNode afterNode:true.
                        ^ self after:foundNode collector:collector.
                    ]
        ].
        ^ retCollection.
    ].
    (foundNode node isErrorNode) ifTrue:[
        ^ self before:foundNode collector:collector.
    ].

    "Created: / 07-03-2011 / 18:59:02 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 09:31:51 / Jakub <zelenja7@fel.cvut.cz>"
!

old_recognize:line position:pos collector:collector 
    "find most possible codeCompletion object"
    
    |node finder position|
    resultSet := ResultSet new.
    (collector tree ~= #Error) ifTrue:[
        finder := Finder new.
        (collector tree isNil) ifTrue:[
            self breakPoint: #jv. ^nil.
        ] ifFalse:[
            position := finder findNodeIn: collector source tree: collector tree 
                                 line: line column: pos.
            position isBeforeNode ifTrue:[
                self before:position node collector:collector.
            ].
            position isAfterNode ifTrue:[
                self after:position node collector:collector.
            ].
            position isInNode ifTrue:[
                self inNode:position node collector:collector.
            ].
        ].
    ] ifFalse:[
        self before.
    ].
    (resultSet objectNameCollection isNil 
        or:[ resultSet objectNameCollection size = 0 ]) 
            ifTrue:[
                resultSet join:(self afterSelfNode:node collector:collector).
                resultSet join:(self before:node collector:collector).
            ].
    resultSet position:position.
    ^ 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 / 16:51:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

processMethod:source class:class parser:parser 
    
    |collector|

    collector := TypeCollector onClass: class.
    collector addMethod:parser.
    TypeCollector new newExtractor   
        extractInterfacesFrom:source
        class:class
        addTo:collector.

    ^ collector

    "Created: / 17-03-2011 / 18:12:26 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 04-04-2011 / 22:29:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-04-2011 / 14:18:50 / Jakub <zelenja7@fel.cvut.cz>"
! !

!Recognizer class methodsFor:'documentation'!

version_HG

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

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