SmallSense__SmalltalkInferencer.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 24 Sep 2013 02:14:28 +0100
changeset 101 a300290bf8fc
parent 95 78bcbdfd9361
child 119 9bb3a9892c2e
permissions -rw-r--r--
Classes renamed to better express theit purpose.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#SmalltalkInferencer
	instanceVariableNames:'class classInfo source parser parserClass tree'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Smalltalk-Types-Inference'
!

SmalltalkParseNodeVisitor subclass:#Phase1
	instanceVariableNames:'classInfo sends types'
	classVariableNames:''
	poolDictionaries:''
	privateIn:SmalltalkInferencer
!

SmalltalkParseNodeVisitor subclass:#Phase2
	instanceVariableNames:'classInfo'
	classVariableNames:''
	poolDictionaries:''
	privateIn:SmalltalkInferencer
!

!SmalltalkInferencer class methodsFor:'documentation'!

documentation
"
    A heart of SmallSense - a type inferencer. For given class
    and method source, instance of inferences walks the parse tree
    and annotate each node with inferred type.
    

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!SmalltalkInferencer class methodsFor:'instance creation'!

forClass: class methodSource: source

    ^self new class: class source: source

    "Created: / 26-11-2011 / 12:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

forClass: class selector: selector

    ^self new class: class selector: selector.

    "Created: / 26-11-2011 / 12:44:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

forMethod: method

    ^self new method: method.

    "Created: / 26-11-2011 / 12:45:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer methodsFor:'accessing'!

klass
    ^ class

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

manager

    ^Manager instance

    "Created: / 27-11-2011 / 16:16:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parser
    ^ parser
!

parserClass
    ^ parserClass
!

parserClass:aClass
    parserClass := aClass.
!

source
    ^ source
!

tree
    ^ tree
! !

!SmalltalkInferencer methodsFor:'initialization'!

class: cls selector: sel

    | m |
    m := cls >> sel.
    m isNil ifTrue:[
        self error: 'No method found'.
    ].
    self method: m.

    "Created: / 26-11-2011 / 12:47:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

class: cls source: src

    class := cls.
    classInfo := self manager infoForClass: class.
    source := src.

    "Created: / 26-11-2011 / 14:46:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

method: method

    self class: method mclass source: method source.

    "Created: / 26-11-2011 / 12:48:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer methodsFor:'private'!

infer


    Phase1 process: tree in: class.

    "
    (SmallSenseParseNodeInspector new node: tree source: source) open
    "

    "Created: / 26-11-2011 / 12:51:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parse

    parserClass isNil ifTrue:[
        parserClass := class parserClass.
    ].
    parser := parserClass 
                parseMethod: source in: class
                ignoreErrors:true 
                ignoreWarnings:true.
    tree := parser tree.

    "Created: / 26-11-2011 / 12:51:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer methodsFor:'processing'!

process

    "Actually infer types. Returns an annotated method tree.
     The tree is also stored in an instance variable, so it
     may be obtained form receiver any time by asking for #tree."

    self parse. 
    tree notNil ifTrue:[
        self infer.
    ].
    ^tree

    "Created: / 26-11-2011 / 12:50:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer::Phase1 methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    sends := Dictionary new.
    types := Dictionary new.

    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 26-11-2011 / 19:31:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer::Phase1 methodsFor:'private'!

rootsUnderstanding: selectors
    "When the set of selectors is not empty, answer a set of the highest possible classes in the system that implement all the selectors.
     When the set of selectors is empty, return the empty set."

    | initialClasses nextClasses traverseStack next |
    selectors isEmpty ifTrue: [^OrderedCollection new].
    nextClasses := OrderedCollection with: Object.
    traverseStack := OrderedCollection new: 1000.
        
    selectors
        do:
            [:selector | 
            initialClasses := nextClasses.
            nextClasses := OrderedCollection new.
            initialClasses
                do:
                    [:initialClass | 
                    "inline canUnderstand: for performance"
                    |cl|
                    cl := initialClass.
                    [(cl == nil) or: [(cl methodDictionary includesKey: selector)]] whileFalse: [cl := cl superclass].
                    (cl == nil)
                        ifFalse: [nextClasses addLast: initialClass]
                        ifTrue:
                            [|size|
                            traverseStack reset.
                            traverseStack addLast: initialClass.
                            size := 1.
                            "(traverseStack isEmpty) removed for performance"
                            [size = 0]
                                whileFalse:
                                    [
                                    "(traverseStack removeFirst) removed for performance"
                                    next := traverseStack removeFirst.
                                    size := size -1.
                                    next
                                        subclassesDo:
                                            [:subcl |
                                            "(subcl includesSelector: selector) removed for performance"
                                            (subcl methodDictionary includesKey: selector)
                                                ifTrue: [nextClasses addLast: subcl]
                                                ifFalse: [traverseStack addLast: subcl. size := size + 1]]]]]].
    ^nextClasses

    "Modified: / 24-11-2010 / 14:39:35 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 26-11-2011 / 14:01:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 18-09-2013 / 01:22:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer::Phase1 methodsFor:'processing'!

process: tree in: cls

    self process: tree in: cls info: (Manager instance infoForClass: cls)

    "Created: / 26-11-2011 / 13:48:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

process: tree in: cls info: clsInfo

     | i c |

    class := cls.
    classInfo := clsInfo.

    "Fill types with cached data..."

    c := class.
    i := classInfo.
    [ c notNil and:[i notNil] ] whileTrue:[
        c instVarNames do:[:nm|
            types at: nm put: (i infoForInstvar: nm)
        ].
        c := c superclass.
        i := i superclassInfo.
    ].

    self visit: tree.


    "Now, infer variable types based on collected sends"
    sends keysAndValuesDo:[:varName :sentSelectors|
        | classes |

        classes := self rootsUnderstanding: sentSelectors.
        (types at: varName) addClasses: classes.
    ].

    "Created: / 27-11-2011 / 16:22:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer::Phase1 methodsFor:'visiting'!

visitAssignmentNode:anObject
    | type |
    
    self visit: anObject variable.
    self visit: anObject expression.
    type := anObject expression inferedType type.
    type isUnknownType ifFalse:[
         anObject variable inferedType union: type
    ].

    "Created: / 26-11-2011 / 13:53:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-09-2013 / 02:31:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitBlockNode:anObject
    | type |

    super visitBlockNode:anObject.
    type := (Type withClass: BlockClosure).
    type trustfullness: 100.
    anObject inferedType: type.

    "Created: / 26-11-2011 / 14:46:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitConstantNode:anObject
    "Type of a constant is trivially its value class"

    | type |

    super visitConstantNode: anObject.
    type := (Type withClass: anObject value class).
    type trustfullness: 100.
    anObject inferedType: type.

    "Created: / 26-11-2011 / 13:55:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitMessageNode:anObject 

    | rec |

    super visitMessageNode: anObject.

    (rec := anObject receiver) isVariableNode ifTrue:[
        "We don't have to infer types for global/class variables"
        (rec isGlobalVariable or:[rec isClassVariable]) ifFalse:[
            (sends at: rec name ifAbsentPut:[Set new]) add: anObject selector.
        ].
    ].

    "Created: / 26-11-2011 / 13:02:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitSelfNode:anObject
    | type |

    super visitSelfNode:anObject.
    type := Type withClass: class.
    type trustfullness: 100.
    anObject inferedType:type

    "Created: / 26-11-2011 / 14:43:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-09-2013 / 01:25:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitSuperNode:anObject
    | type |

    super visitSuperNode:anObject.
    type := Type withClass: class superclass.
    type trustfullness: 100.
    anObject inferedType:type

    "Created: / 26-11-2011 / 14:44:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-09-2013 / 01:26:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitUnaryNode:anObject 

    | type sel rec |

    super visitUnaryNode:anObject.

    sel := anObject selector.

    sel == #class ifTrue:[
        type := anObject receiver inferedType classSide.
        anObject inferedType: type.
        ^self.
    ].
    (sel == #new or:[sel == #basicNew]) ifTrue:[
        rec := anObject receiver.                        
        (rec isSelf and:[class isMetaclass]) ifTrue:[
            type := Type withClass: class theNonMetaclass.
            type trustfullnessAdd: 50.
            anObject inferedType: type.
            ^self.
        ].

        type := anObject receiver inferedType instanceSide.
        anObject inferedType: type.
        ^self.
    ].

    "Created: / 27-11-2011 / 15:49:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visitVariableNode:anObject

    | t |

    "Following code ensures, that all variable nodes refering same
     variable shares the inferred type"
    t := types at: anObject name ifAbsentPut:[Type unknown].
    anObject inferedType: t.

    anObject isGlobalVariable ifTrue:[
        t addClass: (Smalltalk at: anObject name asSymbol) class.
        t trustfullness: 100.
        ^self.
    ].
    anObject isClassVariable ifTrue:[
        t addClass: (class theNonMetaclass classVarAt: anObject name asSymbol) class.
        t trustfullness: 100.
        ^self.
    ].

    "Created: / 26-11-2011 / 13:31:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 29-08-2013 / 14:00:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer::Phase2 methodsFor:'processing'!

process: tree in: cls

    self process: tree in: cls info: (Manager instance infoForClass: cls)

    "Created: / 26-11-2011 / 13:48:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

process: tree in: cls info: clsInfo

    class := cls.
    classInfo := clsInfo.
    self visit: tree.

    "Created: / 27-11-2011 / 16:22:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkInferencer class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '$Id: SmallSenseInferencer.st 8000 2012-05-17 23:16:11Z vranyj1 $'
! !