Registry.st
author claus
Fri, 25 Feb 1994 14:00:53 +0100
changeset 56 be0ed17e6f85
parent 10 4f1f9a91e406
child 60 0cc690b50dff
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Object subclass:#Registry
       instanceVariableNames:'registeredObjects phantoms cleanState'
       classVariableNames:''
       poolDictionaries:''
       category:'System-Support'
!

Registry comment:'

COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Registry.st,v 1.4 1993-11-08 02:31:48 claus Exp $
written jun 93 by claus
'!

!Registry class methodsFor:'documentation'!

documentation
"
Registries provide an easy interface to using WeakArrays. 
A class, which wants to be informed of instance-death, can put a created object
into a registry. The registry will create a copy of the object, and
watch out for death of the registered object. When it dies, the copy will
be sent the message >>disposed.
The trick with the shallow copy is especially nice, you can think of it as
beeing the original object which died.

All objects, which keep external resources (such as fileDescriptors, fonts, 
colormap-entries etc.) should be registered, so that the underlying resource
can be freed when the object goes away.

Of course, you too can use it to do whatever you need to do in case of the
death of an object.
"
! !

!Registry methodsFor:'dispose handling'!

informDispose
    "an instance has been destroyed - look which one it was"

    |phantom|

    cleanState ifTrue:[
        1 to:phantoms size do:[:index |
            (registeredObjects at:index) isNil ifTrue:[
                phantom := phantoms at:index.
                phantom notNil ifTrue:[
                    phantoms at:index put:nil.
                    phantom disposed
                ]
            ]
        ]
    ]
! !

!Registry methodsFor:'enumeration'!

contentsDo:aBlock
    "evaluate aBlock for each registered object"

    registeredObjects notNil ifTrue:[
        registeredObjects do:[:o |
            o notNil ifTrue:[
                aBlock value:o
            ]
        ]
    ]
! !

!Registry methodsFor:'accessing'!

contents
    "return the collection of registered objects"

    ^ registeredObjects
!

changed:anObject
    "a registered object has changed, create a new phantom"

    |index|

    index := registeredObjects identityIndexOf:anObject ifAbsent:[0].
    index ~~ 0 ifTrue:[
        phantoms at:index put:anObject shallowCopy.
    ]
!

register:anObject
    "register anObject, so that a copy of it gets the disposed message
     when anObject dies (some time in the future)"

    |phantom newColl newPhantoms
     count "{ Class: SmallInteger }"
     p index|

    phantom := anObject shallowCopy.

    registeredObjects isNil ifTrue:[
        registeredObjects := WeakArray new:10.
        registeredObjects watcher:self.
        registeredObjects at:1 put:anObject.
        phantoms := Array new:10.
	phantoms at:1 put:phantom.
	cleanState := true.
	ObjectMemory addDependent:self.
        ^ self
    ].

    index := registeredObjects identityIndexOf:anObject ifAbsent:[0].
    index ~~ 0 ifTrue:[
	"already registered"
	phantoms at:index put:phantom.
	self error:'object is already registered'.
	^ self
    ].

    "search for a free slot, on the fly look for leftovers"
    count := phantoms size.
    1 to:count do:[:index |
        (registeredObjects at:index) isNil ifTrue:[
            "is there a leftover ?"
            p := phantoms at:index.
            p notNil ifTrue:[
                phantoms at:index put:nil.
                p disposed.
		p := nil.
            ].
            registeredObjects at:index put:anObject.
            phantoms at:index put:phantom.
            ^ self
        ]
    ].

    "no free slot, add at the end"

    newColl := WeakArray new:(count * 2).
    newColl replaceFrom:1 to:count with:registeredObjects.
    registeredObjects := newColl.
    registeredObjects watcher:self.
    registeredObjects at:(count + 1) put:anObject.

    newPhantoms := Array new:(count * 2).
    newPhantoms replaceFrom:1 to:count with:phantoms.
    phantoms := newPhantoms.
    phantoms at:(count + 1) put:phantom.
!

unregister:anObject
    "remove registration of anObject, without telling the phantom;
     should be sent, if we are no more interrested in destruction of
     anObject (i.e. it no longer holds external resources)."

    |index|

    index := registeredObjects identityIndexOf:anObject ifAbsent:[0].
    index ~~ 0 ifTrue:[
        phantoms at:index put:nil.
        registeredObjects at:index put:nil
    ]
! !

!Registry methodsFor:'restart handling'!

update:aParameter
    aParameter == #earlyRestart ifTrue:[
	phantoms notNil ifTrue:[
	    phantoms atAllPut:nil
	]
    ].
    aParameter == #returnFromSnapshot ifTrue:[
	cleanState := true
    ]
! !