Registry.st
author claus
Tue, 08 Aug 1995 02:49:43 +0200
changeset 375 e5019c22f40e
parent 359 b8df66983eff
child 379 5b5a130ccd09
permissions -rw-r--r--
.

"
 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 handleArray 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.16 1995-08-08 00:48:37 claus Exp $
'!

!Registry class methodsFor:'documentation'!

copyright
"
 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Registry.st,v 1.16 1995-08-08 00:48:37 claus Exp $
"
!

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 (shallow-)copy of the object, and
    watch out for death of the original object. When it dies, the copy will
    be sent the #disposed-message.
    The trick with the shallow copy is especially nice, you can think of it as
    being 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.

    Registries use #shallowCopyForFinalization to aquire the copy of the original,
    this can be redefined in registered classes for faster copying 
    (typically, not all internal state but only some device handles are needed for 
    finalization). I if the to-be-registered object is large, this method may also
    return a stub (placeHolder) object. (i.e. there is no need for the copy to be
    of the same class as the original, as long as it implements disposed and frees
    the relevant OS resources ...)

    See axample uses in Form, Color, ExternalStream and Font
"
! !

!Registry methodsFor:'dispose handling'!

informDispose:someHandle
    someHandle disposed
!

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

    |phantom
     sz "{ Class: SmallInteger }"|

    cleanState ifTrue:[
	sz := handleArray size.
	1 to:sz do:[:index |
	    (registeredObjects at:index) isNil ifTrue:[
		phantom := handleArray at:index.
		phantom notNil ifTrue:[
		    handleArray at:index put:nil.
		    self informDispose:phantom
		]
	    ]
	]
    ]
! !

!Registry methodsFor:'enumerating'!

do:aBlock
    "evaluate aBlock for each registered object"

    registeredObjects notNil ifTrue:[
	registeredObjects nonNilElementsDo:aBlock
    ]
! !

!Registry methodsFor:'accessing'!

contents
    "return the collection of registered objects"

    ^ registeredObjects
!

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

    |index|

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

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

    ^ self register:anObject as:(anObject shallowCopyForFinalization)
!

register:anObject as:aHandle
    "register anObject, so that I later receive informDispose: with aHandle
     (some time in the future)"

    |newColl newPhantoms
     size  "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }"
     p|

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

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

    "search for a free slot, on the fly look for leftovers"
    index := registeredObjects identityIndexOf:nil startingAt:1.
    index ~~ 0 ifTrue:[
	"is there a leftover ?"
	p := handleArray at:index.
	p notNil ifTrue:[
	    "tell the phantom"
	    handleArray at:index put:nil.
	    self informDispose:p.
	    p := nil.
	].
	registeredObjects at:index put:anObject.
	handleArray at:index put:aHandle.
	^ self
    ].

    "no free slot, add at the end"

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

    newPhantoms := Array basicNew:(size * 2).
    newPhantoms replaceFrom:1 to:size with:handleArray.
    handleArray := newPhantoms.
    handleArray at:index put:aHandle.
!

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:[
	handleArray at:index put:nil.
	registeredObjects at:index put:nil
    ]
! !

!Registry methodsFor:'restart handling'!

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