WeakArray.st
author Claus Gittinger <cg@exept.de>
Fri, 18 Oct 1996 22:28:54 +0200
changeset 1785 4b18823528b8
parent 1782 76bcca2667a8
child 1825 6f81b866a74a
permissions -rw-r--r--
commentary & change-aspect made ST-80 compatible

"
 COPYRIGHT (c) 1991 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.
"

Array subclass:#WeakArray
	instanceVariableNames:'watcher dependents'
	classVariableNames:'RegistrationFailedSignal AlreadyInitialized'
	poolDictionaries:''
	category:'Collections-Arrayed'
!

!WeakArray class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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
"
    WeakArrays can be used to trace disposal of objects; in contrast to other
    objects, references by WeakArrays will NOT keep an object from being
    garbage collected.
    Instead, whenever an object kept in a WeakArray dies, its entry is zeroed,
    and the WeakArray is informed by the storage manager. The WeakArray itself
    then informs possible dependents via te dependency mechanism.

    WeakArrays are used to track disposal of objects which keep external
    world resources. For example, FileStreams must close their underlying
    file when disposed (otherwise you could run out of OS filedescriptors).
    This can be done by keeping the FileStream objects in a weakArray, and
    keep a parallel array of filedescriptors. Whenever a fileStream is
    freed, search both arrays for an index where the stream is zero, but the
    filedescriptor is non-nil. Then close that file, and nil the filedescriptor
    entry. Notice, that there is a class (Registry) which does exactly this in
    a more programmer friendly way.

    Another application is caching of data: keep it in a weakArray, so the
    data in that cache will not be unreclaimable due to being cached.
    (for example, the ResourcePack class uses a WeakArray to cache recently
     used resource data for a while).

    The way in which weakArrays get informed by the runtime system is via
    an interrupt (DisposeInterrupt) which is first sent to the disposeHandler
    (typically ObjectMemory). ObjectMemory then takes the required steps to
    notify all weakArrays via the #lostPointer message.

    The reason for not sending messages directly from the VM is to make it 
    possible to run the finalization code at lower priority or from another class. 
    Also, as a side effect, it is possible to delay finalization by blocking 
    interrupts.

    Notice, that there are currently two mechanisms by which a weakArray notifies
    its dependents: via normal dependency notfications and/or by sending an
    explicit message to a watcher object, which is found in an instvar of the
    WeakArray.

    Having two mechanisms here (i.e. watcher & dependent) is a historic leftover;
    I dont know, which of the two mechanisms will survive in the long run - 
    I started with the watcher, but now switch to dependencies since they seem 
    to offer more flexibility.
    You should NOT use the watcher mechanism; be prepared, that the watcher 
    mechanism may vanish in the future (i.e. use dependents for your applications).

    NOTICE: 
        WeakArray handling adds some overhead to the VM 
        (each weakarray is scanned after each GC). 
        It is uncertain, if the current mechanism works well
        with (say) ten-thousands of weakArrays.

    As a possible option, we could perform the weakArray scanning only in
    the oldSpace reclamation code - this would remove most of the overhead,
    but will lead to much longer delayed finalization .... we will see.


    [instance variables:]

        watcher                         if non-nil, gets informed via #informDispose
                                        that the weakArray has lost pointers.

        dependents                      get informed via #change notifiction 
                                        that the weakArray has lost pointers.
                                        Having the dependents here is an optimization.


    [class variables:]

        RegistrationFailedSignal        raised if a weakArray cannot be
                                        registered by the VM. This only happens,
                                        if the VM has to resize its shadow tables
                                        and is running out of malloc-memory.

    [author:]
        Claus Gittinger

    [See also:]
        Array WeakIdentitySet WeakIdentityDictionary
"
! !

!WeakArray class methodsFor:'initialization'!

initialize
    "setup the private signal"

    RegistrationFailedSignal isNil ifTrue:[
	RegistrationFailedSignal := ErrorSignal newSignalMayProceed:true.
	RegistrationFailedSignal nameClass:self message:#registrationFailedSignal.
	RegistrationFailedSignal notifierString:'weakArray registration failed'.
    ]
! !

!WeakArray class methodsFor:'instance creation'!

new:size
    "return a new weakArray with size slots"

    "This is a kludge: I would like to set WEAK-flag in the classes
     initialize method, but (currently) the order in which the class-initialize
     methods are called is not defined ...
     ... therefore it could happen, that a WeakArray is used by other
     classes initialize method BEFORE this method is evaluated. 
     To avoid this, the WEAK bit in the class is set here, when the very first 
     WeakArray is created."

    AlreadyInitialized isNil ifTrue:[
	self flags:(Behavior flagWeakPointers).
	AlreadyInitialized := true
    ].

    ^ (self basicNew:size) registerAsWeakArray
! !

!WeakArray methodsFor:'GC registration'!

registerAsWeakArray
    "register the receiver in the VM - 
     i.e. tell the VM to nil disposed entries in the receiver
     and notify the disposeInterruptHandler whenever that happened."

    |ok|
%{
    OBJ __addShadowObject();

    ok = __addShadowObject(self, 0);
    if (ok == false) {
	/* 
	 * this happens when too many shadow objects are
	 * already there, collect garbage to get rid of
	 * obsolete ones, and try again.
	 * since a full collect is expensive, we try
	 * a scavenge first, doing a full collect only if 
	 * that does not help.
	 *
	 * THIS MAY OR MAY NOT BE A GOOD IDEA: although it reduces
	 * the number of shadow objects that have to be
	 * processed at GC time, it may create a long delay here,
	 * at shadow object creation time.
	 * Dont know which is better ...
	 */
	__nonTenuringScavenge(__context);
	ok = __addShadowObject(self, 0);
#ifdef OLD
	if (ok == false) {
	    /* 
	     * try more ... 
	     */
	    __scavenge(__context);
	    ok = __addShadowObject(self, 0);
#endif
	    if (ok == false) {
		/* 
		 * hard stuff - need full collect
		 * if this is the very first GC, assume that we are in
		 * the startup phase. Then do no GC.
		 * Heuristics showed, that this GC does not find much ...
		 */
		if ((__garbageCollectCount() != 0)
		 || (__incrementalGCCount() != 0)) {
		    __markAndSweepIfUseful(__context);
		    ok = __addShadowObject(self, 0);
		}
		if (ok == false) {
		    /*
		     * mhmh - it seems that there are really many shadow 
		     * objects around - force creation
		     */
		    ok = __addShadowObject(self, 1);
		    if (ok == false) {
			/* no chance - something must be wrong */
		    }
		}
	    }
#ifdef OLD
	}
#endif
    }
%}.
    ok ifFalse:[
	"
	 the VM was not able to register the new weakArray
	 This can only happen, if the VM has to resize its tables,
	 and a malloc request failed. Usually, this smells like big
	 trouble being on the way (soon running out of memory in
	 other places as well).
	 Configure your OS for more swap space.
	"
	^ RegistrationFailedSignal raiseRequestWith:self
    ]
! !

!WeakArray methodsFor:'accessing'!

at:index
    "return the indexed instance variable with index, anInteger.
     Reimplemented here for IGC readBarrier. You dont have to understand this."

    ^ self basicAt:index
!

basicAt:index
    "return the indexed instance variable with index, anInteger.
     Reimplemented here for IGC readBarrier. You dont have to understand this."

%{  /* NOCONTEXT */

    REGISTER int indx;
    REGISTER unsigned int nIndex;
    OBJ el;

    if (__isSmallInteger(index)) {
	indx = __intVal(index) - 1;
	if (indx >= 0) {
	    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
	    indx += __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
	    if (indx < nIndex) {
		el = __InstPtr(self)->i_instvars[indx];
		if (__isNonNilObject(el)) el = __WEAK_READ__(self, el);
		RETURN (el);
	    }
	}
    }
%}.
    ^ super basicAt:index
!

dependents 
    "return the dependents of the receiver"

    ^ dependents
!

dependents:aCollection
    "set the dependents of the receiver"

    dependents := aCollection
!

watcher
    "return the watcher of the receiver.
     The watcher-stuff is a leftover from an old implementation 
     and will vanish soon"

    ^ watcher
!

watcher:anObject
    "set the watcher of the receiver.
     The watcher-stuff is a leftover from an old implementation 
     and will vanish soon"

    watcher := anObject
! !

!WeakArray methodsFor:'copying'!

postCopy
    "copying alone does not really help - we have to tell
     the VM, that there is a new WeakArray around ...
     Q: who copies weakArrays ?"

    dependents := nil.
    self registerAsWeakArray.
! !

!WeakArray methodsFor:'enumeration'!

do:aBlock
    "evaluate the argument, aBlock for each element in the collection.
     - reimplemented for IGC readBarrier. You dont have to understand this."

    |home element|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    unsigned int nIndex;
    static struct inlineCache val = _ILC1;
    REGISTER OBJ rHome;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    if (__isBlockLike(aBlock)
     && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
	for (; index < nIndex; index++) {
	    if (InterruptPending != nil) __interruptL(@line);
	    element = __InstPtr(self)->i_instvars[index];
	    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
	    (*codeVal)(aBlock, element);
	} 
#else
	home = __BlockInstPtr(aBlock)->b_home;
	rHome = home;
	if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
	    /*
	     * home will not move - keep in a fast register
	     */
	    for (; index < nIndex; index++) {
		if (InterruptPending != nil) __interruptL(@line);

		element = __InstPtr(self)->i_instvars[index];
	        if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		(*codeVal)(rHome, element);
	    } 
	} else {
	    for (; index < nIndex; index++) {
		if (InterruptPending != nil) __interruptL(@line);

		element = __InstPtr(self)->i_instvars[index];
	        if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		(*codeVal)(home, element);
	    } 
	} 
#endif
    } else {
	for (; index < nIndex; index++) {
	    if (InterruptPending != nil) __interruptL(@line);

	    element = __InstPtr(self)->i_instvars[index];
	    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
	    (*val.ilc_func)(aBlock, 
			    @symbol(value:), 
			    nil, &val, 
			    element);
	} 
    }
%}.
    ^ self
!

forAllDeadIndicesDo:aBlock
    "evaluate the argument, aBlock for all indices where elements have been
     replaced by zero (due to a collected object)."

    self keysAndValuesDo:[:index :element |
	element == 0 ifTrue:[
	     aBlock value:index
	]
    ]
!

forAllDeadIndicesDo:aBlock replacingCorpsesWith:newValue
    "evaluate the argument, aBlock for all indices where elements have been
     replaced by zero (due to a collected object), and replace the element
     with newValue.
     In the current implementation, the block sees the newValue (i.e. it is
     changed before the block is called); this behavior is not guaranteed
     with future versions."

    self keysAndValuesDo:[:index :element |
	element == 0 ifTrue:[
	    self at:index put:newValue.
	    aBlock value:index.
	]
    ]
!

from:start to:stop do:aBlock
    "evaluate the argument, aBlock for the elements starting at index start
     up to (and including) stop in the collection.
     - reimplemented for IGC readBarrier. You dont have to understand this."

    |home element|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    REGISTER OBJ rHome;
    int nIndex, nInsts;
    static struct inlineCache val = _ILC1;
    int indexLow, indexHigh;

    if (__bothSmallInteger(start, stop)) {
	indexLow = __intVal(start);
	if (indexLow > 0) {
	    indexHigh = __intVal(stop);
	    nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
	    indexLow += nInsts;
	    indexHigh += nInsts;
	    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
	    if (indexHigh <= nIndex) {
		indexLow--;
		indexHigh--;
		if (__isBlockLike(aBlock)
		 && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
		 && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
		    for (index=indexLow; index <= indexHigh; index++) {
			if (InterruptPending != nil) __interruptL(@line);
			element = __InstPtr(self)->i_instvars[index];
	    		if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			(*codeVal)(aBlock, element);
		    } 
#else
		    home = __BlockInstPtr(aBlock)->b_home;
		    rHome = home;
		    if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
			index = indexLow;
			for (; index <= indexHigh; index++) {
			    if (InterruptPending != nil) __interruptL(@line);
			    element = __InstPtr(self)->i_instvars[index];
	    		    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			    (*codeVal)(rHome, element);
			} 
		    } else {
			for (index=indexLow; index <= indexHigh; index++) {
			    if (InterruptPending != nil) __interruptL(@line);
			    element = __InstPtr(self)->i_instvars[index];
	    		    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			    (*codeVal)(home, element);
			} 
		    }
#endif
		} else {
		    for (index=indexLow; index <= indexHigh; index++) {
			if (InterruptPending != nil) __interruptL(@line);
			element = __InstPtr(self)->i_instvars[index];
	    		if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			(*val.ilc_func) (aBlock, 
					 @symbol(value:), 
					 nil, &val, 
					 element);
		    } 
		}
	    }
	    RETURN ( self );
	}
    }
%}.
    ^ super from:start to:stop do:aBlock
!

keysAndValuesDo:aBlock
    "evaluate the argument, aBlock for each element in the collection.
     Pass both index and element to the block.
     - reimplemented for speed"

    |home element|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    unsigned int nIndex, index0;
    static struct inlineCache val2 = _ILC2;
    REGISTER OBJ rHome;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    index0 = index;
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);

    if (__isBlockLike(aBlock)
     && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(2))) {
#ifdef NEW_BLOCK_CALL
	for (; index < nIndex; index++) {
	    if (InterruptPending != nil) __interruptL(@line);

	    element = __InstPtr(self)->i_instvars[index];
	    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
	    (*codeVal)(aBlock, __MKSMALLINT(index+1-index0), element);
	} 
#else
	home = __BlockInstPtr(aBlock)->b_home;
	rHome = home;
	if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
	    /*
	     * home will not move - keep in a fast register
	     */
	    while (index < nIndex) {
		if (InterruptPending != nil) __interruptL(@line);

		element = __InstPtr(self)->i_instvars[index];
	        if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		index++;
		(*codeVal)(rHome, __MKSMALLINT(index-index0), element);
	    } 
	} else {
	    while (index < nIndex) {
		if (InterruptPending != nil) __interruptL(@line);

		element = __InstPtr(self)->i_instvars[index];
	        if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		index++;
		(*codeVal)(home, __MKSMALLINT(index-index0), element);
	    } 
	} 
#endif
    } else {
	while (index < nIndex) {
	    if (InterruptPending != nil) __interruptL(@line);

	    element = __InstPtr(self)->i_instvars[index];
	    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
	    index++;
	    (*val2.ilc_func)(aBlock, 
			    @symbol(value:value:), 
			    nil, &val2,
			    __MKSMALLINT(index-index0),
			    element);
	} 
    }
%}.
    ^ self
!

nilAllCorpsesAndDo:aBlock
    "evaluate the argument, aBlock for all indices where elements have been
     cleared (due to a collected object), nil the entry."

    self forAllDeadIndicesDo:aBlock replacingCorpsesWith:nil
!

nonNilElementsDo:aBlock
    "evaluate the argument, aBlock for each non-nil element"

    |home element|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    int nIndex;
    static struct inlineCache val = _ILC1;
    REGISTER OBJ rHome;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    if (__isBlockLike(aBlock)
     && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
	for (; index < nIndex; index++) {
	    if (InterruptPending != nil) __interruptL(CONARG);

	    element = __InstPtr(self)->i_instvars[index];
	    if (element != nil) {
		element = __WEAK_READ__(self, element);
		if (element != nil) {
		    (*codeVal)(aBlock, element);
		}
	    }
	} 
#else
	home = __BlockInstPtr(aBlock)->b_home;
	rHome = home;
	if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
	    /*
	     * home will not move - keep in in a register
	     */
	    for (; index < nIndex; index++) {
		if (InterruptPending != nil) __interruptL(CONARG);

		element = __InstPtr(self)->i_instvars[index];
		if (element != nil) {
		    element = __WEAK_READ__(self, element);
		    if (element != nil) {
			(*codeVal)(rHome, element);
		    }
		}
	    } 
	} else {
	    for (; index < nIndex; index++) {
		if (InterruptPending != nil) __interruptL(@line CONARG);

		element = __InstPtr(self)->i_instvars[index];
		if (element != nil) {
		    element = __WEAK_READ__(self, element);
		    if (element != nil) {
			(*codeVal)(home, element);
		    }
		}
	    }
	} 
#endif
    } else {
	for (; index < nIndex; index++) {
	    if (InterruptPending != nil) __interruptL(@line CONARG);

	    element = __InstPtr(self)->i_instvars[index];
	    if (element != nil) {
		element = __WEAK_READ__(self, element);
		if (element != nil) {
		    (*val.ilc_func)(aBlock, 
				    @symbol(value:), 
				    nil, &val, 
				    element);
		}
	    }
	} 
    }
%}.
    ^ self
! !

!WeakArray methodsFor:'notification'!

lostPointer
    "I lost a pointer; tell watcher and/or dependents.
     This is sent from the finalization code in ObjectMemory."

    watcher notNil ifTrue:[
        watcher informDispose
    ].
    dependents notNil ifTrue:[
        self changed:#ElementExpired with:nil.
    ].

    "Modified: 18.10.1996 / 21:28:10 / cg"
! !

!WeakArray class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/WeakArray.st,v 1.34 1996-10-18 20:28:54 cg Exp $'
! !
WeakArray initialize!