Registry.st
author Claus Gittinger <cg@exept.de>
Fri, 17 Jan 1997 16:45:41 +0100
changeset 2189 618dcdc1cee9
parent 2182 78c6e43eb9f5
child 2278 f4b82ee501cc
permissions -rw-r--r--
added #validElementsDo:

"
 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 tally'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support'
!

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

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 a #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 ...)
    Example uses are found in Form, Color, ExternalStream and Font

    [author:]
        Claus Gittinger

    [see also:]
        WeakArray WeakIdentityDictionary WeakIdentitySet
        Font Form Color Cursor ExternalStream
        
"
! !

!Registry methodsFor:'accessing'!

contents
    "return the collection of registered objects.
     Warning: this returns a weak collection."

    ^ registeredObjects

    "Modified: 16.1.1997 / 16:40:46 / cg"
! !

!Registry methodsFor:'dispose handling'!

informDispose:someHandle
    "send a dispose message - this is sent to the phantom,
     since the original is already gone"

    someHandle disposed

    "Modified: 16.1.1997 / 17:23:46 / cg"
!

update:something with:aParameter from:changedObject
    "an instance has been destroyed - look which one it was"

    |phantom
     dstIdx "{ Class: SmallInteger }"
     sz     "{ Class: SmallInteger }"
     newObjects newHandles o wasBlocked
     myHandleArray myRegisteredObjects|

    something == #ElementExpired ifTrue:[
        "/
        "/ use local refs, in case I shrink in an interrupt
        "/

        myHandleArray := handleArray.
        myRegisteredObjects := registeredObjects.

        sz := myHandleArray size.

        1 to:sz do:[:index |

            o := myRegisteredObjects at:index.
            o notNil ifTrue:[
                o == 0 ifTrue:[
                    myRegisteredObjects at:index put:nil.

                    phantom := myHandleArray at:index.
                    phantom notNil ifTrue:[
                        myHandleArray at:index put:nil.
                        tally := tally - 1.
                        self informDispose:phantom.
                    ]
                ]
            ]
        ].

        (sz > 50 and:[tally < (sz // 2)]) ifTrue:[
            "/ shrink
            self resize
        ]
    ] ifFalse:[
        something == #earlyRestart ifTrue:[
            handleArray notNil ifTrue:[
                handleArray atAllPut:nil.
            ]
        ]
    ].

    "Created: 15.6.1996 / 15:24:41 / cg"
    "Modified: 8.1.1997 / 14:05:02 / stefan"
    "Modified: 16.1.1997 / 18:07:41 / cg"
! !

!Registry methodsFor:'enumerating'!

do:aBlock
    "evaluate aBlock for each registered object"

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

!Registry methodsFor:'private'!

resize
    |sz          "{ Class: SmallInteger }"
     dstIndex    "{ Class: SmallInteger }"
     realNewSize "{ Class: SmallInteger }"
     newObjects newHandles wasBlocked 
     phantom|

    sz := registeredObjects size.

    (sz > 50 and:[tally < (sz // 2)]) ifTrue:[
        "/ shrink

        realNewSize := tally * 3 // 2.
        newObjects := WeakArray new:realNewSize.
        newHandles := Array new:realNewSize.

        wasBlocked := OperatingSystem blockInterrupts.

        dstIndex := 1.
        1 to:sz do:[:index |
            (phantom := registeredObjects at:index) notNil ifTrue:[
                dstIndex > realNewSize ifTrue:[
                    'Registry [info]: size given is too small in resize' infoPrintCR.
                    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
                    ^ self
                ].
                newObjects at:dstIndex put:phantom.
                newHandles at:dstIndex put:(handleArray at:index).
                dstIndex := dstIndex + 1
            ]
        ].

        registeredObjects removeDependent:self.
        registeredObjects := newObjects.
        newObjects addDependent:self.
        handleArray := newHandles.

        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ]

    "Modified: 16.1.1997 / 18:00:38 / cg"
    "Created: 16.1.1997 / 18:08:00 / cg"
! !

!Registry methodsFor:'registering objects'!

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 wasBlocked|

    wasBlocked := OperatingSystem blockInterrupts.
    registeredObjects size == 0 "isNil" ifTrue:[
        registeredObjects := WeakArray new:10.
        registeredObjects addDependent:self.
        handleArray := Array basicNew:10.
        registeredObjects at:1 put:anObject.
        handleArray at:1 put:aHandle.
        tally := 1.
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
        ObjectMemory addDependent:self.
        ^ self
    ].

    wasBlocked ifFalse:[
        OperatingSystem unblockInterrupts.
        OperatingSystem blockInterrupts.
    ].

    index := registeredObjects identityIndexOf:anObject ifAbsent:0.
    index ~~ 0 ifTrue:[
        "already registered"
        handleArray at:index put:aHandle.
        ('Registry [info]: object (' , (registeredObjects at:index) printString , ' is already registered') infoPrintCR.
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
        ^ self
    ].

    wasBlocked ifFalse:[
        OperatingSystem unblockInterrupts.
        OperatingSystem blockInterrupts.
    ].

    "search for a free slot, on the fly look for leftovers (no longer happens)"
    index := registeredObjects identityIndexOf:nil startingAt:1.
    index ~~ 0 ifTrue:[
        "is there a leftover ?"
        p := handleArray at:index.
        p notNil ifTrue:[
            'Registry [info]: there should be no leftOvers' infoPrintCR.

            "tell the phantom"
            handleArray at:index put:nil.
            tally := tally - 1.
            self informDispose:p.
            p := nil.
        ].
        registeredObjects at:index put:anObject.
        handleArray at:index put:aHandle.
        tally := tally + 1.
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
        ^ 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 addDependent: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.
    tally := tally + 1.

    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].

    "Modified: 7.1.1997 / 16:56:03 / stefan"
    "Modified: 16.1.1997 / 18:05:06 / cg"
!

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

    |index wasBlocked|

    wasBlocked := OperatingSystem blockInterrupts.
    registeredObjects isNil ifTrue:[
        index := 0
    ] ifFalse:[
        index := registeredObjects identityIndexOf:anObject ifAbsent:0.
    ].
    index ~~ 0 ifTrue:[
        handleArray at:index put:anObject shallowCopyForFinalization.
    ] ifFalse:[
        self register:anObject
    ].
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].

    "Modified: 22.6.1996 / 14:27:52 / cg"
!

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

    |index wasBlocked|

    registeredObjects notNil ifTrue:[
        wasBlocked := OperatingSystem blockInterrupts.
        index := registeredObjects identityIndexOf:anObject ifAbsent:0.
        index ~~ 0 ifTrue:[
            handleArray at:index put:nil.
            registeredObjects at:index put:nil.
            tally := tally - 1.
        ].
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].

        self resize
    ]

    "Modified: 16.1.1997 / 18:08:42 / cg"
!

unregisterAllForWhich:aBlock
    "remove registration of all entries, for which the argument block
     evaluates to true.
     should be sent, if we are no more interested in destruction of
     a group of objects (i.e. it no longer holds external resources)."

    |n "{ Class: SmallInteger }"
     obj wasBlocked|

    registeredObjects notNil ifTrue:[
        wasBlocked := OperatingSystem blockInterrupts.
        n := registeredObjects size.
        1 to:n do:[:index |
            obj := registeredObjects at:index.
            (obj notNil and:[obj ~~ 0]) ifTrue:[
                (aBlock value:obj) ifTrue:[
                    handleArray at:index put:nil.
                    registeredObjects at:index put:nil.
                    tally := tally - 1.
                ]
            ]
        ].
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
        self resize
    ]

    "Created: 16.1.1997 / 16:39:18 / cg"
    "Modified: 16.1.1997 / 18:08:47 / cg"
! !

!Registry class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Registry.st,v 1.38 1997-01-17 15:45:41 cg Exp $'
! !