WeakArray.st
author Claus Gittinger <cg@exept.de>
Tue, 21 Jan 1997 13:54:25 +0100
changeset 2216 e4fed6c622de
parent 2199 40b621897c59
child 2220 17ec32355032
permissions -rw-r--r--
*** empty log message ***

"
 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:'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.

    A weakArray notifies its dependents via normal dependency notfications.

    [hint:] 
	WeakArray handling adds small 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.
	We had the system running with >2000 weakArrays, some being quite
	big for a while and had a few percent of added gc time.
	The system as delivered creates between 50 and 100 weakArrays,
	but with many dependents, this number may grow.
	If you need the dependency mechanism on a huge number of objects,
	consider adding a (non-weak) dependents field to your class
	- take the implementation of Model as a guide (or subclass them
	from Model).

										\
    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:]

	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 Registry
	Model
"
! !

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

!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:'enumerating'!

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

%{
    REGISTER int index;
    unsigned int nIndex;
    static struct inlineCache val = _ILC1;

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

    if (__isBlockLike(aBlock)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
	{
	    /*
	     * the most common case: a static compiled block, with home on the stack ...
	     */
	    REGISTER OBJFUNC codeVal;

	    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
#ifdef NEW_BLOCK_CALL
#               define BLOCK_ARG        aBlock
#else
#               define BLOCK_ARG        rHome
		REGISTER OBJ rHome;

		rHome = __BlockInstPtr(aBlock)->b_home;
		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) 
#endif
		{
		    for (; index < nIndex; index++) {
			OBJ element;

			if (InterruptPending != nil) __interruptL(@line);

			element = __InstPtr(self)->i_instvars[index];
			if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			(*codeVal)(BLOCK_ARG, element);
		    }
		    RETURN (self);
		}
	    }
	}

	/*
	 * sorry, must check code-pointer in the loop
	 * it could be recompiled or flushed
	 */
#       undef BLOCK_ARG
#ifdef NEW_BLOCK_CALL
#       define BLOCK_ARG        aBlock
#       define IBLOCK_ARG       nil
#else
#       define BLOCK_ARG        (__BlockInstPtr(aBlock)->b_home)
#       define IBLOCK_ARG       (__BlockInstPtr(aBlock)->b_home)
#endif

	for (; index < nIndex; index++) {
	    REGISTER OBJFUNC codeVal;
	    REGISTER OBJ element;

	    if (InterruptPending != nil) __interruptL(@line);

	    element = __InstPtr(self)->i_instvars[index];
	    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);

	    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
		(*codeVal)(BLOCK_ARG, element);
	    } else {
		if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
		    /*
		     * arg is a compiled block with bytecode -
		     * directly call interpreter without going through Block>>value
		     */
#ifdef PASS_ARG_POINTER
		    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
#else
		    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
#endif
		} else {
		    /*
		     * arg is something else - call it with #value
		     */
		    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
		}
	    }
	} 
	RETURN (self);

#       undef BLOCK_ARG
#       undef IBLOCK_ARG

    }

    /*
     * not a block - send it #value:
     */
    for (; index < nIndex; index++) {
	OBJ element;

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

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"

%{
    REGISTER int index;
    int nIndex;
    static struct inlineCache val = _ILC1;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    if (__isBlockLike(aBlock)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
	{
	    /*
	     * the most common case: a static compiled block, with home on the stack ...
	     */
	    REGISTER OBJFUNC codeVal;

	    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
#ifdef NEW_BLOCK_CALL
#               define BLOCK_ARG        aBlock
#else
#               define BLOCK_ARG        rHome
		REGISTER OBJ rHome;

		rHome = __BlockInstPtr(aBlock)->b_home;
		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) 
#endif
		{
		    for (; index < nIndex; index++) {
			REGISTER OBJ element;

			element = __InstPtr(self)->i_instvars[index];
			if (element) {
			    if (InterruptPending != nil) {
				__interruptL(@line);
				element = __InstPtr(self)->i_instvars[index];
			    }

			    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			    if (element) {
				(*codeVal)(BLOCK_ARG, element);
			    }
			}
		    }
		    RETURN (self);
		}
	    }
	}

	/*
	 * sorry, must check code-pointer in the loop
	 * it could be recompiled or flushed
	 */
#       undef BLOCK_ARG
#ifdef NEW_BLOCK_CALL
#       define BLOCK_ARG        aBlock
#       define IBLOCK_ARG       nil
#else
#       define BLOCK_ARG        (__BlockInstPtr(aBlock)->b_home)
#       define IBLOCK_ARG       (__BlockInstPtr(aBlock)->b_home)
#endif

	for (; index < nIndex; index++) {
	    REGISTER OBJFUNC codeVal;
	    REGISTER OBJ element;

	    element = __InstPtr(self)->i_instvars[index];
	    if (element) {
		if (InterruptPending != nil) {
		    __interruptL(@line);
		    element = __InstPtr(self)->i_instvars[index];
		}
		if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		if (element) {
		    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
			(*codeVal)(BLOCK_ARG, element);
		    } else {
			if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
			    /*
			     * arg is a compiled block with bytecode -
			     * directly call interpreter without going through Block>>value
			     */
#ifdef PASS_ARG_POINTER
			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
#else
			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
#endif
			} else {
			    /*
			     * arg is something else - call it with #value
			     */
			    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
			}
		    }
		}
	    } 
	}
	RETURN (self);

#       undef BLOCK_ARG
#       undef IBLOCK_ARG
    }

    /*
     * not a block - send it #value:
     */
    for (; index < nIndex; index++) {
	REGISTER OBJ element;

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

validElementsDo:aBlock
    "evaluate the argument, aBlock for each non-nil/non-zero element"

%{
    REGISTER int index;
    int nIndex;
    static struct inlineCache val = _ILC1;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    if (__isBlockLike(aBlock)
     && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
	{
	    /*
	     * the most common case: a static compiled block, with home on the stack ...
	     */
	    REGISTER OBJFUNC codeVal;

	    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
#ifdef NEW_BLOCK_CALL
#               define BLOCK_ARG        aBlock
#else
#               define BLOCK_ARG        rHome
		REGISTER OBJ rHome;

		rHome = __BlockInstPtr(aBlock)->b_home;
		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) 
#endif
		{
		    for (; index < nIndex; index++) {
			REGISTER OBJ element;

			element = __InstPtr(self)->i_instvars[index];
			if (element && (element != __MKSMALLINT(0))) {
			    if (InterruptPending != nil) {
				__interruptL(@line);
				element = __InstPtr(self)->i_instvars[index];
			    }

			    if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
			    if (element && (element != __MKSMALLINT(0))) {
				(*codeVal)(BLOCK_ARG, element);
			    }
			}
		    }
		    RETURN (self);
		}
	    }
	}

	/*
	 * sorry, must check code-pointer in the loop
	 * it could be recompiled or flushed
	 */
#       undef BLOCK_ARG
#ifdef NEW_BLOCK_CALL
#       define BLOCK_ARG        aBlock
#       define IBLOCK_ARG       nil
#else
#       define BLOCK_ARG        (__BlockInstPtr(aBlock)->b_home)
#       define IBLOCK_ARG       (__BlockInstPtr(aBlock)->b_home)
#endif

	for (; index < nIndex; index++) {
	    REGISTER OBJFUNC codeVal;
	    REGISTER OBJ element;

	    element = __InstPtr(self)->i_instvars[index];
	    if (element && (element != __MKSMALLINT(0))) {
		if (InterruptPending != nil) {
		    __interruptL(@line);
		    element = __InstPtr(self)->i_instvars[index];
		}
		if (__isNonNilObject(element)) element = __WEAK_READ__(self, element);
		if (element && (element != __MKSMALLINT(0))) {
		    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
			(*codeVal)(BLOCK_ARG, element);
		    } else {
			if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
			    /*
			     * arg is a compiled block with bytecode -
			     * directly call interpreter without going through Block>>value
			     */
#ifdef PASS_ARG_POINTER
			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
#else
			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
#endif
			} else {
			    /*
			     * arg is something else - call it with #value
			     */
			    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
			}
		    }
		}
	    } 
	}
	RETURN (self);

#       undef BLOCK_ARG
#       undef IBLOCK_ARG
    }

    /*
     * not a block - send it #value:
     */
    for (; index < nIndex; index++) {
	REGISTER OBJ element;

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

!WeakArray methodsFor:'notification'!

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

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

    "Modified: 18.10.1996 / 21:28:10 / cg"
    "Modified: 7.1.1997 / 17:22:52 / stefan"
! !

!WeakArray class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/WeakArray.st,v 1.42 1997-01-21 12:54:25 cg Exp $'
! !
WeakArray initialize!