SmallSenseTypeCollector.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 06 Sep 2012 17:38:47 +0100
changeset 28 f516772ba2b8
parent 0 893cc7b0ed1d
child 29 fe650a6e5704
permissions -rw-r--r--
- SmallSenseChecker class definition added: #initialize #new changed: #checkMethodsForClass: - extensions ...

"{ Package: 'stx:libtool/smallsense' }"

TypeCollector subclass:#SmallSenseTypeCollector
	instanceVariableNames:'master'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Roel Typer'
!


!SmallSenseTypeCollector class methodsFor:'instance creation'!

newForPlatform

    ^SmallSenseTypeCollector basicNew

    "Created: / 04-04-2011 / 22:28:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmallSenseTypeCollector methodsFor:'* As yet uncategorized *'!

type

    | extractor |

    extractor := self newExtractor.

    theClass selectorsAndMethodsDo:
        [:sel :method|
        currentExtractedMethod := method.
        extractor
            extractInterfacesFrom:method source
            class: method mclass
            addTo:self.
        ]

    "
        (SmallSenseTypeCollector onClass: SmallSenseTypeCollector) type
    "

    "Created: / 28-04-2011 / 22:10:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmallSenseTypeCollector methodsFor:'accessing'!

master
    ^ master
!

master:aTypeCollector
    master := aTypeCollector.

    self typingResults do:[:myType| | masterType |
        masterType := master typingResults detect:[:r|r ivarName = myType ivarName] ifNone: nil.
        masterType ifNotNil:[myType addLinkedExtractedType: masterType].
    ]

    "Modified: / 29-04-2011 / 08:06:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

subCollector

    ^(self class onClass: theClass) master: self

    "Created: / 28-04-2011 / 22:07:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmallSenseTypeCollector methodsFor:'heuristics'!

assignmentTypeOf: val
	val isBehavior ifTrue: [^val].
	val isVariableBinding
		ifTrue:
			[val key == #instcreation
				ifTrue: [^val value]
				ifFalse: [^val value class]].
	^nil
!

langueSpecificPushSendOf:selector to:rec 
    selector == #blockCopy: ifTrue:[
        ^ #block
    ].
    (#( #'//' #quo: #rem: #'\\' #ceiling #floor #rounded #roundTo: #truncated #truncateTo: #'/' #'+' #'-' #'*' #abs #negated #reciprocal ) 
        includes:selector) 
            ifTrue:[
                ^ self 
                    tryUsing:rec
                    for:selector
                    ifNotUse:Number
            ].
    (selector = #yourself) ifTrue:[
        ^ rec
    ].
    (rec = #self and:[ (theClass methodDict includesKey:selector) ]) ifTrue:[
        ^ #return -> selector
    ].
    ^ nil.

    "Created: / 14-12-2010 / 23:35:55 / Jakub <zelenja7@fel.cvut.cz>"
!

langueSpecificPushSendOf: selector to: rec args: args
        selector == #blockCopy: ifTrue: [^#block].
        (#(#// #quo: #rem: #\\ #ceiling #floor #rounded #roundTo: #truncated #truncateTo: #/ #+ #- #* #abs #negated #reciprocal)
                includes: selector)
                ifTrue:
                        [^self
                                tryUsing: rec
                                for: selector
                                ifNotUse: Number].
        (selector = #yourself) ifTrue: [^rec].
        (rec = #self and: [(theClass methodDict includesKey: selector)]) ifTrue: [^#return->selector].
        ^nil

    "Modified: / 14-12-2010 / 23:56:00 / Jakub <zelenja7@fel.cvut.cz>"
! !

!SmallSenseTypeCollector methodsFor:'private'!

newExtractor
        ^SmallSenseInstvarInterfaceExtractor new

    "Modified: / 03-04-2011 / 22:50:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmallSenseTypeCollector class methodsFor:'documentation'!

version_SVN
    ^ '$Id: SmallSenseTypeCollector.st 7823 2011-11-26 16:55:59Z vranyj1 $'
! !