SmallSense__Manager.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 24 Aug 2013 22:15:09 +0100
changeset 64 2257d7223898
child 67 020b7461b15e
permissions -rw-r--r--
All classes moved to namespace SmallSense.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#Manager
	instanceVariableNames:'classes accessLock updater'
	classVariableNames:'Instance'
	poolDictionaries:''
	category:'SmallSense-Model'
!


!Manager class methodsFor:'instance creation'!

flush
    "flushes the cached singleton"

    Instance := nil

    "
     self flushSingleton
    "

    "Created: / 16-12-2011 / 01:37:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

flushSingleton
    "flushes the cached singleton"

    Instance := nil

    "
     self flushSingleton
    "
!

instance
    "returns a singleton"

    Instance isNil ifTrue:[
        Instance := self basicNew initialize.
    ].
    ^ Instance.

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

new
    "returns a singleton"

    ^ self instance.

    "Modified: / 27-11-2011 / 15:30:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Manager methodsFor:'accessing'!

infoForClass: class

    | info |

    accessLock critical:[
        info := self basicInfoForClass: class.
    ].
    ^info

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

infoForClassOrNil: class

    ^classes at: class name ifAbsent: nil

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

!Manager methodsFor:'accessing-private'!

basicInfoForClass: class

    class isNil ifTrue:[^nil].

    ^classes at: class name ifAbsentPut:[
        ClassInfo new
            setManager: self
            className: class name
    ].

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

!Manager methodsFor:'change & update'!

update:what with:param from:sender
    "Invoked when an object that I depend upon sends a change notification."

    UserPreferences current smallSenseBackgroundTypingEnabled ifFalse:[ ^ self ].

    sender ~~ Smalltalk ifTrue:[
        super update:what with:param from:sender.
        ^self.
    ].

    what == #methodInClass ifTrue:[
        self updateInfoForMethod: (param first >> param second).
        ^self.
    ].
    

"/    Transcript show: 'SmallSense: Smalltalk changed: ', what , ' with: ', param printString.

    "Modified: / 04-02-2012 / 22:30:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Manager methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    classes := Dictionary new.
    accessLock := Semaphore forMutualExclusion.
    updater := BackgroundQueueProcessingJob 
                    named: 'SmallSense background updater' 
                    on: [:classOrMethod|self delayedUpdateInfoForClassOrMethod: classOrMethod].
    updater priority: Processor userBackgroundPriority - 1.

    UserPreferences current smallSenseEnabled ifTrue:[
        Smalltalk addDependent: self.
    ].

    "Modified (format): / 28-11-2011 / 19:31:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Manager methodsFor:'updating'!

updateInfoForClass: class

    | info |

    class programmingLanguage isSmalltalk ifFalse:[ ^ self ].
    info := self infoForClassOrNil: class.
    info isNil ifTrue:[
        updater add: class
    ].

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

updateInfoForMethod: method

    | info |

    method programmingLanguage isSmalltalk ifFalse:[ ^ self ].
    info := self basicInfoForClass: method mclass.
    info isNil ifTrue:[
        updater add: method mclass
    ] ifFalse:[
        updater add: method
    ]

    "Created: / 28-11-2011 / 19:30:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Manager methodsFor:'updating-delayed'!

delayedUpdateInfoForClass: class

    | superclass |

    superclass := class superclass.
    superclass notNil ifTrue:[self updateInfoForClass: superclass].
    class methodsDo:[:mthd|updater add:mthd].

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

delayedUpdateInfoForClassOrMethod: classOrMethod

    classOrMethod isBehavior ifTrue:[
       self delayedUpdateInfoForClass: classOrMethod.
    ].
    classOrMethod isMethod ifTrue:[
       self delayedUpdateInfoForMethod: classOrMethod.
    ]

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

delayedUpdateInfoForMethod: method

    | inferencer |

    method mclass isNil ifTrue:["Obsolete method" ^ self ].
    method mclass programmingLanguage isSmalltalk ifFalse: [ ^ self ].
"/    Transcript showCR: 'SmallSense: updating info for: ', method printString.
    inferencer := Inferencer forMethod: method.
    inferencer process.

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

!Manager class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '$Id: SmallSenseManager.st 7984 2012-04-21 08:36:11Z vranyj1 $'
! !