This is oop.c in view mode; [Download] [Up]
/*********************************************************************** * * Object Table maintenance module. * * $Revision: 1.7 $ * $Date: 1995/09/17 10:49:48 $ * $Author: sbb $ * ***********************************************************************/ /*********************************************************************** * * Copyright (C) 1990, 1991, 1992, 1994, 1995 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 1, or (at your option) any later * version. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. * ***********************************************************************/ /* * Change Log * ============================================================================ * Author Date Change * sbb 10 Sep 95 Added GC torture test. Heh heh heh! * * sbb 7 Sep 95 Added incubator support. * * sbb 30 Aug 95 Merged NT changes back in. Code now contains some * unnecessary casting and unrolled expressions (*= * becomes = *) to shut the Visual C++ compiler's * warnings off. * * sbb 20 Aug 95 Added growMemoryTo(); it's a variant of growTo which * does not involve the garbage collector. * * sbb 20 Aug 95 Fixed alignSize to not double align (we don't * preserve that property during GC anymore anyway, and * the floating point accessing functions in dict.c * which were the initial reason for having it are now * sensitive to whether aligned access to doubles is * required by the hardware or not. * * sbb 23 Jul 95 Fixed #ifdefed out code to not have apostrophes * (OS/2 doesn't understand). * * sbb 9 Jun 95 Began switching to mark & sweep gc. * * sbb 6 Jun 95 Switched to new file naming scheme. * * sbb 30 May 95 Boolean => mst_Boolean. * * sbb 31 Mar 95 Added fflush(stdout) to some debugging funcs * * sbb 2 Oct 94 Made sure to turn off the free bit in moveOOP (no * sense in moving an object that's freed, and moveOOP * will not be called on a truly freed object; this * change "repairs the damage" in cases where there is * an accidental freeing occurring. * * sbb 31 Dec 91 Added registered oops to root set. * * sbb 31 Dec 91 oopTable now allocated from memory instead of being * stored as part of the executable. * * sbb 8 Dec 91 Changed oopValid to only check the FREE bit, instead * of worrying about the even odd flags, which may not * be valid. * * sbb 20 Oct 91 Support for growing now fully operational (and no, it * hasn't taken me over a month to track down the * problems; free time has been nil). Also removed more * vestiges of the incremental GC. * * sbb 15 Sep 91 Added support for loading larger semispaces from * saved images. * * sbb 4 Aug 91 Removed more vestiges of the incremental GC, began * switchover to automatically growing semi-spaces. * * sbb 13 Oct 90 Converted to use bit masks instead of bit fields, * hoping to improve performance somewhat. * * sbyrne 8 Apr 90 Changed oopFree to oopValid to fix the bug with * someInstance losing after GC's due to objects that * have non-free OOP table entries, but point to freed * objects. * * sbyrne 7 Apr 90 Increased mem space size to 4M. This can be * decreased as necessary. * * sbyrne 24 Feb 90 Update to change log: there are no longer any * explicitly allocated OOPs due to the new symbol table * structure; the comment below is now a noop. * * sbyrne 20 Sep 89 Added oop table slot GC'ing. I'm not dealing with * oop table slots that are explictly allocated; I * believe that most OOP slots are not explicitly chosen * and so not running the incremental reclaimer for that * case shouldn't hurt us. * * sbyrne 12 Sep 89 Much of the garbage collector's operation depends on * the fact that only 1 flip will occur between any two * operations (such as a compilation, or a byte-code). * The code would be much more complex if this were not * the case, and I'm not sure that things would even be * possible if this were not the case. Anyway, there is * code in this routine to check for that eventuality * and to halt the system if it occurs. * * sbyrne 6 Sep 89 started implementing the garbage collector (YAY!!!) * * sbyrne 13 Jan 89 Created. * */ #include <stdio.h> #include "gst.h" #include "oop.h" #include "dict.h" #include "save.h" #include "comp.h" #include "callin.h" #include "lex.h" #include "sym.h" #if STDC_HEADERS #include <stdlib.h> #include <string.h> #endif /* STDC_HEADERS */ /* Size of the object semi spaces, in bytes */ #define K 1024 #ifndef atarist /* Min for Kernel = 512K, Kernel+STIX min is 1M */ /* you can increase this value if you need more space, and it won't hurt * performance *if* your machine has enough physical memory (otherwise, you * thrash the pager) */ #define INIT_MEM_SPACE_SIZE /*(512 * K) */ (1 * K * K) #else #define INIT_MEM_SPACE_SIZE (1152 * K) #endif #define CHUNK_SIZE 100 /* SWAG */ #define INIT_NUM_INCUBATOR_OOPS 50 /* SWAG */ #define INCUBATOR_CHUNK_SIZE 20 /* SWAG */ /* Define this flag to turn on debugging code for OOP table management */ /* #define OOP_DEBUGGING */ #define alignSize(size) \ ( ((size) + sizeof(OOP) - 1) & ~(sizeof(OOP) - 1) ) #define objSpace <> <> <> /* a bogus set of tokens to make the compiler screen if seen */ /* XXX #define objSpace(obj) \ ( (((char *)(obj) >= spaces[1].space) \ && ((char *)(obj) < spaces[1].space + spaces[1].totalSize)) \ ? F_SPACE : 0 ) */ /* Returns 1 if space flag represents the ODD space, 0 for the EVEN space */ #define boolSpace <><><> /* a bogus set of tokens to make the compiler screen if seen */ /* XXX #define boolSpace(spaceFlag) \ ((spaceFlag) == F_SPACE) */ /* XXX #define EVEN_ODD_MASK (F_EVEN | F_ODD) */ /* Macros for speed! */ #define makeNewChunk(var, prev) \ (var) = (MarkStackChunk *)malloc(sizeof(MarkStackChunk) \ + (CHUNK_SIZE * sizeof (MarkInProgress))); \ (var)->maxSP = (var)->stack + CHUNK_SIZE; \ (var)->prevChunk = (prev); \ (var)->nextChunk = nil; #define pushCopyStack(sp) \ /* printf("pushing copy stack sp %x max %x curChunk %x %d\n", (sp), currentChunk->maxSP, currentChunk, __LINE__);*/ \ (sp)++; \ if (sp >= currentChunk->maxSP) { \ /* printf("******* growing\n");*/ \ if (currentChunk->nextChunk == nil) { \ MarkStackChunk * chunk; \ /*printf("******* growing & adding\n");*/ \ makeNewChunk(chunk, currentChunk); \ currentChunk->nextChunk = chunk; \ } \ currentChunk = currentChunk->nextChunk; \ (sp) = currentChunk->stack; \ } #define popCopyStack(sp) \ /* printf("popping copy stack sp %x max %x curChunk %x %d\n", (sp), currentChunk->maxSP, currentChunk, __LINE__); */ \ if ((sp) == currentChunk->stack) { \ oldChunk = currentChunk; \ currentChunk = currentChunk->prevChunk; \ (sp) = currentChunk ? currentChunk->maxSP : nil; \ } \ (sp)--; /* Predicate "function". Hides chunk stack implementation from caller. * returns true if the current stack pointer is at the base of the base * chunk. */ #define atStackBase() \ (currentChunk == nil) /* OLD: ((currentChunk->prevChunk == nil) && (copySP == currentChunk->stack)) */ typedef struct CompiledMethodStruct *Method; typedef struct MarkInProgressStruct { /* initial field */ OOP oop; #ifdef BOGUS /* after class -- single object fields */ mst_Object object; OOP objClass; mst_Boolean isPointers; #endif /* BOGUS */ /* loop related fields */ OOP *curOOP; OOP *finalOOP; /* address of 1 OOP past the last valid OOP */ mst_Boolean inLoop; } MarkInProgress; typedef struct MarkStackChunkStruct MarkStackChunk; struct MarkStackChunkStruct { MarkStackChunk *prevChunk; MarkStackChunk *nextChunk; MarkInProgress* maxSP; MarkInProgress stack[1]; }; extern mst_Boolean regressionTesting; /* These are the real OOPS for nil, true, and false */ OOP nilOOP, trueOOP, falseOOP; /* The OOP table. This contains a pointer to the object, and some flag bits indicating which semispace the pointed-to object lives in. Some of the bits indicate the difference between the allocated length (stored in the object itself, and the real length, for things like byte strings that may not be an even multiple of 4 (== sizeof(void *)). */ struct OOPStruct *oopTable; int numFreeOOPs; /* XXX remove these */ /* The indices of which is the current new space (toSpace) and which is the current old space (fromSpace). At GC flip time, these two are interchanged. */ /* XXX unsigned long fromSpace, toSpace; */ mst_Boolean gcFlipped, gcState, gcMessage; int gcFlipCounter; #ifdef GC_TORTURE unsigned long gcWaitFlipCount = 0, allocCounter = 0; unsigned long doTortureCounter = 0; mst_Boolean doGCTorture = false; #endif /* If there is this much space used after a gcFlip, we need to grow the other * semi space by spaceGrowRate next time we gcFlip, so that the storage gets * copied into the new, larger area. */ double growThresholdPercent = 80.0; /* Grow the semi spaces by this percentage when the amount of space used * exceeds growThresholdPercent. */ double spaceGrowRate = 30.0; /* This vector holds the storage for all the Character objects in the system. Since all character objects are unique, we pre-allocate space for 256 of them, and treat them as special built-ins when doing garbage collection.*/ CharObject charObjectTable[NUM_CHAR_OBJECTS]; /* This is "nil" object in the system. That is, the single instance of the UndefinedObject class, which is called "nil". */ struct NilObjectStruct nilObject; /* These represent the two boolean objects in the system, true and false. This is the object storage for those two objects. false == &booleanObjects[0], true == &booleanObjects[1] */ struct BooleanObjectStruct booleanObjects[2]; /* XXX fix the comments here */ struct memorySpaceStruct { char *space; /* base of allocated storage */ char *allocPtr; /* new space ptr, starts hi, goes down */ #ifdef pre_ms_gc /* Sat Jun 24 02:08:35 1995 */ /**/ /**/ char *copyPtr; /* used by GC, points to highest copied space */ /**/ char *scanPtr; /* used by GC, points to highest scanned addr */ #endif /* pre_ms_gc Sat Jun 24 02:08:35 1995 */ char *maxPtr; /* used by GC, points to highest scanned addr */ unsigned long size; /* current remaining size */ unsigned long totalSize; /* current allocated size */ double percentUsed; /* amount used at just after copyReferences */ }; /* This contains the maximum size of a semi space. It is checked before a * semi space gets used at gcflip time; if the space is too small, it is * brought up to spec before being used */ unsigned long maxSpaceSize; /* XXX fix the wording here */ /* These two variables represent information about the semispaces. spaces holds the information for each semispace (basically the pointer to the base of the space, and the pointers into it for allocation, copying, and scanning. curSpace holds the address of one of the two semispace data structures, and is used by the garbage collector */ /* static struct memorySpaceStruct spaces[2]; */ static struct memorySpaceStruct memSpace; static MarkStackChunk* currentChunk; static MarkStackChunk* oldChunk; static MarkInProgress* copySP; /* These variables hold onto the object incubator's state */ OOP *incOOPBasePtr, *incOOPPtr, *incOOPEndPtr; /* XXX remove /* This contains the bit mask of the current toSpace: it's F_EVEN when toSpace is 0, and F_ODD when toSpace is not zero * / static unsigned long evenOddFlag; */ #ifdef preserved /* Sat Aug 3 18:47:58 1991 */ /**/static double copyRate; /**/static double copyRateAdjustment = 1.50; /* copy 50% more than last time */ #endif /* preserved Sat Aug 3 18:47:58 1991 */ static long oopTableIndex; /* static mst_Object moveObject(); */ static mst_Boolean isOOPAddr(), isObjAddr(), growMemory(); static void initCharObject(), /* moveRootOOPs(), */ initSpace(), markBuiltinOOPs(), unmarkBuiltinOOPs(), /* copyReferencedObjects(),*/ /* XXX clearOldOOPs(), */ displayOOP(), displayObject(), markOOPs(), sweepOOPs(), markAnOOPInternal(), markGlobalOOPs(), reverseOOPPointers(), markIncubatorOOPs(); /* * void initOOPTable() * * Description * * Initialize the OOP table. Initially, all the OOPs are on the OOP free * list so that's just how we initialize them. We do as much * initialization as we can, but we're called before classses are * defined, so things that have definite classes must wait until * the classes are defined. * */ void initOOPTable() { int i; allocOOPTable(); numFreeOOPs = OOP_TABLE_SIZE; for (i = 0; i < OOP_TABLE_SIZE; i++) { oopTable[i].flags = F_FREE; } nilOOP = &oopTable[nilOOPIndex]; trueOOP = &oopTable[trueOOPIndex]; falseOOP = &oopTable[falseOOPIndex]; nilOOP->flags = trueOOP->flags = falseOOP->flags = 0; nilOOP->object = (mst_Object)&nilObject; nilObject.objSize = ROUNDED_WORDS(sizeof(struct NilObjectStruct)); trueOOP->object = (mst_Object)&booleanObjects[0]; falseOOP->object = (mst_Object)&booleanObjects[1]; booleanObjects[0].objSize = ROUNDED_WORDS(sizeof(struct BooleanObjectStruct)); booleanObjects[1].objSize = ROUNDED_WORDS(sizeof(struct BooleanObjectStruct)); booleanObjects[0].booleanValue= trueOOP; booleanObjects[1].booleanValue= falseOOP; dictInit(); /* ### TEMP HACK ### */ } void allocOOPTable() { oopTable = (struct OOPStruct *)malloc(sizeof(struct OOPStruct) *TOTAL_OOP_TABLE_SLOTS); if (oopTable == NULL) { errorf("Failed to allocate oopTable!!!"); exit(1); } } /* * void initNil() * * Description * * Initialize the "nil" object. * */ void initNil() { nilObject.objClass = undefinedObjectClass; } /* * void initBooleans() * * Description * * Initialize the two boolean objects, after their respective classes have * been created. * */ void initBooleans() { booleanObjects[0].objClass = trueClass; booleanObjects[1].objClass = falseClass; } /* * void initCharTable() * * Description * * Initialize the instances of the class Character, after that class has * been created. * */ void initCharTable() { int i; for (i = 0; i < NUM_CHAR_OBJECTS; i++) { initCharObject(i); oopTable[i + CHAR_OBJECT_BASE].object = (mst_Object)&charObjectTable[i]; oopTable[i + CHAR_OBJECT_BASE].flags = 0; } } /* * static void initCharObject(i) * * Description * * Initialize a single character object. * * Inputs * * i : The index of the character object, in the range 0..255. * */ static void initCharObject(i) int i; { charObjectTable[i].objSize = ROUNDED_WORDS(sizeof(CharObject)); charObjectTable[i].objClass = charClass; charObjectTable[i].charVal = i; } /* * void fixupMetaclassObjects() * * Description * * Called after the fundamental class hierarchy has been defined, this * function goes through and fixes up all the objects in the oop table * that don't have a objClass (objClass == nilOOP). It's a * chicken-and-egg problem: the metaclassClass doesn't yet exist when the * hierarchy is put together, so after it's created, we have to go back * and fix all the metaclasses that we created. * */ void fixupMetaclassObjects() { int i; for (i = 0; i < OOP_TABLE_SIZE; i++) { if (!(oopTable[i].flags & F_FREE) && isNil(oopTable[i].object->objClass)) { oopTable[i].object->objClass = metaclassClass; } } } /* * OOP findAnInstance(classOOP) * * Description * * Finds and returns an instance of the class CLASSOOP. Returns "nil" if * there are no instances present. * * Inputs * * classOOP: * OOP for a class for which to find an instance * * Outputs * * The first instance of the given class in the OOP table. */ OOP findAnInstance(classOOP) OOP classOOP; { register OOP oop; for (oop = oopTable; oop < &oopTable[OOP_TABLE_SIZE]; oop++) { if (!(oop->flags & F_FREE) && oop->object->objClass == classOOP) { return (oop); } } return (nilOOP); } #ifndef INLINE_MACROS /* * long oopIndex(oop) * * Description * * Returns the index within the OOP table of the given OOP. * * Inputs * * oop : OOP to return index of * * Outputs * * Returned index in the OOP table, in range 0..TOTAL_OOP_TABLE_SLOTS. */ long oopIndex(oop) OOP oop; { return (oopIndexMac(oop)); } #endif /* INLINE_MACROS */ /* * mst_Boolean oopIndexValid(index) * * Description * * Checks to see if index represents a valid OOP. * * Inputs * * index : a long index into the OOP table, apparently 1 based due to * being called from Smalltalk via a primitive. * * Outputs * * True if the index represents a valid OOP table element, false * otherwise. */ mst_Boolean oopIndexValid(index) long index; { return (index >= 1 && index <= TOTAL_OOP_TABLE_SLOTS); } #ifndef INLINE_MACROS OOP oopAt(index) long index; { return (oopAtMac(index)); } void prepareToStore(destOOP, srcOOP) OOP destOOP, srcOOP; { prepareToStoreMac(destOOP, srcOOP); } #endif /* INLINE_MACROS */ void swapObjects(oop1, oop2) OOP oop1, oop2; { struct OOPStruct tempOOP; tempOOP = *oop2; /* note structure assignment going on here */ *oop2 = *oop1; *oop1 = tempOOP; } OOP charOOPAt(c) Byte c; { return (&oopTable[c + CHAR_OBJECT_BASE]); } Byte charOOPValue(charOOP) OOP charOOP; { return (charOOP - &oopTable[CHAR_OBJECT_BASE]); } void printObject(oop) OOP oop; { if (isInt(oop)) { printf("%d", toInt(oop)); } else if (isNil(oop)) { printf("nil"); } else if (oop == trueOOP) { printf("true"); } else if (oop == falseOOP) { printf("false"); } else if (oopClass(oop) == charClass) { printf("$%c", charOOPValue(oop)); } else if (oopClass(oop) == floatClass) { printf("%#g", floatOOPValue(oop)); } else if (oopClass(oop) == symbolClass) { printf("#"); printSymbol(oop); } else if (oopClass(oop) == stringClass) { /* ### have to quote embedded quote chars */ printf("'"); printString(oop); printf("'"); } else { printOOPConstructor(oop); } fflush(stdout); } void classifyAddr(addr) void *addr; { if (isOOPAddr(addr)) { displayOOP(addr); } else if (isObjAddr(addr)) { displayObject(addr); } else if isInt(addr) { printf("Smalltalk Integer %d\n", toInt(addr)); } else { printf("Address %#x is not a Smalltalk entity\n", addr); } fflush(stdout); } static mst_Boolean isOOPAddr(addr) OOP addr; { if (addr >= oopTable && addr < &oopTable[TOTAL_OOP_TABLE_SLOTS]) { if ((long)addr % 4 == 0) { return (true); } } return (false); } static mst_Boolean isObjAddr(addr) char *addr; { /* XXX if ((addr >= spaces[0].space && addr < spaces[0].space + spaces[0].totalSize) || (addr >= spaces[1].space && addr < spaces[1].space + spaces[1].totalSize)) { */ if ((addr >= memSpace.space) && (addr < memSpace.space + memSpace.totalSize)) { if ((long)addr % 4 == 0) { return (true); } } return (false); } static void displayOOP(oop) OOP oop; { mst_Boolean isBuiltin; if (!isOOPAddr(oop)) { printf("Parameter %#x does not appear to be an OOP!\n", oop); return; } isBuiltin = (oop >= &oopTable[OOP_TABLE_SIZE]) ? true : false; if (!isBuiltin) { printf ("OOP %#x [%d]\n", oop, oop - oopTable); } if (oop->flags & F_FREE) { printf("Free "); } if (oop->flags & F_REACHABLE) { printf("Reachable "); } #ifdef pre_ms_gc /* Fri Jun 9 23:01:00 1995 */ /**/ /**/ printf("Space=%d ", (oop->flags & F_SPACE) ? 1 : 0); /**/ if (oop->flags & F_EVEN) { /**/ printf("Even "); /**/ } /**/ if (oop->flags & F_ODD) { /**/ printf("Odd "); /**/ } /**/ if (oop->flags & F_FAKE) { /**/ printf("Fake "); /**/ } #endif /* pre_ms_gc Fri Jun 9 23:01:00 1995 */ printf(" Empty bytes = %d\n", (oop->flags & EMPTY_BYTES)); if (!(oop->flags & F_FREE)) { printObject(oop); } printf("\n"); } static void displayObject(obj) mst_Object obj; { if (!isObjAddr(obj)) { printf("Parameter %#x does not appear to be an object!\n", obj); return; } printf("Object at %#x, ", obj); if ((char *)obj >= memSpace.allocPtr) { /* XXX NOT ACCURATE RIGHT NOW */ printf("allocated this GC pass\n"); #ifdef pre_ms_gc /* Sat Jun 24 02:10:09 1995 */ /**/ } else if ((char *)obj >= memSpace.scanPtr) { /**/ printf("copied in this GC pass, not scanned\n"); /**/ } else { /**/ printf("copied in this GC pass, scanned\n"); #endif /* pre_ms_gc Sat Jun 24 02:10:09 1995 */ } #ifdef pre_ms_gc /* Fri Jun 9 23:01:44 1995 */ /**/ space = objSpace(obj) != 0; /**/ printf("Object at %#x, in space %d (curSpace is %d), ", obj, space, /**/ curSpace == &spaces[1]); /**/ if ((char *)obj >= spaces[space].allocPtr) { /**/ printf("allocated this GC pass\n"); /**/ } else if ((char *)obj >= spaces[space].scanPtr) { /**/ printf("copied in this GC pass, not scanned\n"); /**/ } else { /**/ printf("copied in this GC pass, scanned\n"); /**/ } /**/ #endif /* pre_ms_gc Fri Jun 9 23:01:44 1995 */ printf("Size %d\n", numOOPs(obj)); printf("Class "); printObject(obj->objClass); printf("\n"); } mst_Boolean oopValid(oop) OOP oop; { /* In the non-incremental GC world, being FREE is all that matters for * validity. */ return (!(oop->flags & F_FREE)); } #ifndef INLINE_MACROS mst_Boolean oopAvailable(index) long index; { return (oopAvailableMac(index)); } #endif /* INLINE_MACROS */ /* * OOP allocOOP(obj) * * Description * * Given an object OBJ, this routine allocates an OOP table slot for it * and returns it. It marks the OOP so that it indicates the object is in * new space, and that the oop has been referenced on this pass (to keep * the OOP table reaper from reclaiming this OOP). * * Inputs * * obj : Object that the new OOP should point to. * * Outputs * * An OOP, which is the address of an element in the OOP table. */ OOP allocOOP(obj) mst_Object obj; { register OOP oop; for (oop = &oopTable[oopTableIndex]; oop < &oopTable[OOP_TABLE_SIZE]; oop++) { if (oop->flags & F_FREE) { oopTableIndex = oop - oopTable + 1; numFreeOOPs--; #ifdef pre_sc_gc /* Sun Jun 18 15:25:31 1995 */ /**/ /* !!! not sure if this is needed */ /**/ if (objSpace(obj) != toSpace) { /**//* dprintf("doing move for oldspace object in allocOOP\n"); */ /**/ obj = moveObject(obj); /**/ } #endif /* pre_sc_gc Sun Jun 18 15:25:31 1995 */ oop->object = obj; oop->flags = 0; /* no flags on this one */ #ifdef pre_ms_gc /* Fri Jun 9 23:03:32 1995 */ /**/ oop->flags = toSpace | evenOddFlag; #endif /* pre_ms_gc Fri Jun 9 23:03:32 1995 */ return (oop); } } errorf("Ran out of OOP Table slots!!!"); exit(1); } #ifdef preserved /* Sat Jul 27 16:48:12 1991 */ /**/OOP allocOOP(obj) /**/Object obj; /**/{ /**/#ifndef NORMAL_ALLOC_OOP /**/ register OOP oop; /**/ register int i; /**/ /**/ for (i = 0, oop = &oopTable[oopTableIndex]; /**/ i < oopReclaimFactor && oop < &oopTable[OOP_TABLE_SIZE]; i++, oop++) { /**/ if (!(oop->flags & F_FREE)) { /**/ if (!(oop->flags & (F_EVEN|F_ODD))) { /**/ /* we've found a dead one...add it to the free list */ /**/ numFreeOOPs++; /**/ oop->object = (Object)freeOOPs; /**/ freeOOPs = oop; /**/ freeOOPs->flags |= F_FREE; /**/ } else { /**/ /* turn off the bit for the space we're not in */ /**/ oop->flags &= ~(evenOddFlag ^ EVEN_ODD_MASK); /**/ } /**/ } /**/ } /**/ /**/ oopTableIndex = oop - oopTable; /**/ /**/#else /**/ OOP oop; /**/ register int i; /**/ /**/ for (i = 0; i < oopReclaimFactor; i++) { /**/ if (oopTableIndex >= OOP_TABLE_SIZE) { /**/ break; /**/ } /**/ oop = &oopTable[oopTableIndex++]; /**/ if (!oop->isFree) { /**/ if (!oop->evenMark && !oop->oddMark) { /**/ /* we've found a dead one...add it to the free list */ /**/ numFreeOOPs++; /**/ oop->object = (Object)freeOOPs; /**/ freeOOPs = oop; /**/ freeOOPs->isFree = true; /**/ } else if (toSpace) { /**/ oop->evenMark = 0; /**/ } else { /**/ oop->oddMark = 0; /**/ } /**/ } /**/ } /**/#endif /**/ /**/ oop = freeOOPs; /**/ /**/ numFreeOOPs--; /**/ /**/ if (oop == nil) { /**/ errorf("Ran out of OOP Table slots!!!"); /**/ exit(1); /**/ /* ### this needs to be fixed */ /**/ } /**/ /**/ if (!(oop->flags & F_FREE)) { /**/ errorf("Allocating allocated OOP!!!"); /**/ exit(0); /**/ } /**/ /**/ freeOOPs = (OOP)oop->object; /**/ /**/ if (objSpace(obj) != toSpace) { /**/ obj = moveObject(obj); /**/ } /**/ /**/ /**/ oop->object = obj; /**/ oop->flags = toSpace | evenOddFlag; /**/ /**/ return (oop); /**/} #endif /* preserved Sat Jul 27 16:48:12 1991 */ /* * void setOOPObject(oop, object) * * Description * * Sets the object of OOP to be OBJECT. * * Inputs * * oop : an OOP table entry to be assigned into * object: an object that the OOP should point to. * */ void setOOPObject(oop, object) OOP oop; mst_Object object; { #ifndef OPTIMIZE if (isFake(oop)) { printf("found a fake oop %x\n", oop); debug(); } #endif /* !OPTIMIZE */ #ifdef pre_ms_gc /* Fri Jun 9 23:04:32 1995 */ /**/ if (objSpace(object) != toSpace) { /**//* dprintf("doing move for oldspace object in setOOPObject\n"); */ /**/ object = moveObject(object); /**/ } #endif /* pre_ms_gc Fri Jun 9 23:04:32 1995 */ oop->object = object; #ifdef pre_ms_gc /* Fri Jun 9 23:04:51 1995 */ /**/ oop->flags = (oop->flags & ~F_SPACE) | toSpace; #endif /* pre_ms_gc Fri Jun 9 23:04:51 1995 */ } /* * void initMem() * * Description * * Initialize the memory allocator. Both semispaces are allocated, and * the various garbage collection flags are set to their initial values. * */ void initMem() { /* int i; */ maxSpaceSize = INIT_MEM_SPACE_SIZE; memSpace.space = (char *)malloc(maxSpaceSize); memSpace.totalSize = maxSpaceSize; memSpace.percentUsed = 0.0; if (memSpace.space == NULL) { printf("\n\n[Memory allocation failure]\nCan't allocate enough memory to continue.\n"); exit(1); } initSpace(&memSpace); #ifdef pre_ms_gc /* Fri Jun 9 23:05:27 1995 */ /**/ for (i = 0; i < 2; i++) { /**/ spaces[i].space = (char *)malloc(maxSpaceSize); /**/ spaces[i].totalSize = maxSpaceSize; /**/ spaces[i].percentUsed = 0.0; /**/ if (spaces[i].space == NULL) { /**/ printf("Malloc failure; you're out of paging/swapping space\n"); /**/ exit(1); /**/ } /**/ initSpace(&spaces[i]); /**/ } /**/ /**/ curSpace = &spaces[0]; /**/ toSpace = 0; /**/#ifdef bogus_old_code /* Sat Oct 13 15:37:50 1990 */ /**//**/ fromSpace = !toSpace; /**/#endif /* bogus_old_code Sat Oct 13 15:37:50 1990 */ /**/ fromSpace = F_SPACE; /**/ evenOddFlag = F_EVEN; #endif /* pre_ms_gc Fri Jun 9 23:05:27 1995 */ gcFlipped = false; gcState = false; gcMessage = true; #ifdef preserved /* Sat Aug 3 18:48:45 1991 */ /**/ copyRate = 0.0; /* don't copy anything until first flip */ /**/ copyQuota = 0; #endif /* preserved Sat Aug 3 18:48:45 1991 */ oopTableIndex = 0; #ifdef testing_out /* Sat Feb 29 10:55:51 1992 */ /**/ markBuiltinOOPs(); #endif /* testing_out Sat Feb 29 10:55:51 1992 */ clearGCFlipFlags(); incInitRegistry(); } mst_Object curSpaceAddr() { return ((mst_Object)memSpace.space); #ifdef pre_ms_gc /* Fri Jun 9 23:08:17 1995 */ /**/ return ((mst_Object)curSpace->space); #endif /* pre_ms_gc Fri Jun 9 23:08:17 1995 */ } void setSpaceInfo(size) long size; { memSpace.allocPtr = memSpace.space + size; #ifdef pre_ms_gc /* Sat Jun 24 02:10:47 1995 */ /**/ memSpace.copyPtr = memSpace.scanPtr = memSpace.space + size; /**/ memSpace.size -= size; #endif /* pre_ms_gc Sat Jun 24 02:10:47 1995 */ } #ifndef INLINE_MACROS void clearGCFlipFlags() { clearGCFlipFlagsMac(); } #endif /* INLINE_MACROS */ /* * Object allocObj(size) * * Description * * Allocate and return space for an object of SIZE bytes. This basically * means moving the allocation pointer for the current space down by SIZE * bytes, and, if there isn't enough space left, flipping the garbage * collector to switch semispaces. The space is merely allocated; it is * not initialized. * * Inputs * * size : size in bytes of the object to allocate. This will be rounded * by this routine up to a suitable boundary, typically to a 4 * byte boundary. * * Outputs * * Address of the newly allocated object. */ mst_Object allocObj(size) unsigned long size; { char *newAllocPtr; #ifdef GC_TORTURE if (gcState && doGCTorture || (gcWaitFlipCount != 0 && allocCounter++ >= gcWaitFlipCount)) { gcFlip(); } #endif size = alignSize(size); if (size >= maxSpaceSize) { unsigned long spaceAvail; unsigned long spaceNeeded; /* If we've been asked for a huge amount of space, go ahead an make room * for it. First flip to see what we have to work with */ gcFlip(); spaceAvail = memSpace.maxPtr - memSpace.allocPtr; spaceNeeded = size - spaceAvail; spaceNeeded = (unsigned long)(spaceNeeded * (1.0 + spaceGrowRate/100.0)); /* allow breathing room */ growMemoryTo(spaceNeeded); } #ifdef preserved /* Sat Jul 27 16:43:00 1991 */ /**/ copyReferencedObjects((long)(size * copyRate)); #endif /* preserved Sat Jul 27 16:43:00 1991 */ /* We don't want to have allocPtr pointing to the wrong thing during GC, so * we use a local var to hold its new value */ newAllocPtr = memSpace.allocPtr + size; while (newAllocPtr >= memSpace.maxPtr) { gcFlip(); newAllocPtr = memSpace.allocPtr + size; } memSpace.allocPtr = newAllocPtr; #ifdef preserved /* Fri Oct 18 21:46:22 1991 */ /**/ if (curSpace->allocPtr <= curSpace->copyPtr) { /**/ gcFlip(); /**/ curSpace->allocPtr -= size; /**/ } #endif /* preserved Fri Oct 18 21:46:22 1991 */ return ((mst_Object)(memSpace.allocPtr - size)); } #ifdef pre_sc_gc /* Sun Jun 18 15:26:37 1995 */ /**//* /**/ * static void copyReferencedObjects() /**/ * /**/ * Description /**/ * /**/ * This is the heart of the garbage collector. It fully scans all objects /**/ * in new space, copying object that it finds that are still in old space /**/ * to new space and adding them to the set of objects to be scanned. /**/ * It has to special case /**/ * CompiledMethod objects due to their unusual structure. /**/ * /**/ */ /**/static void copyReferencedObjects() /**/{ /**/ mst_Object object; /**/ register OOP curClass, *oop; /**/ int stepSize, count; /**/ Method method; /**/ register int i; /**/ /**/ while (curSpace->scanPtr < curSpace->copyPtr) { /* there's more to scan */ /**/ /* if there is no current object, start off with the object's class */ /**/ object = (mst_Object)curSpace->scanPtr; /**/ curClass = object->objClass; /**/ /**/#ifdef debugging /* Mon Oct 28 12:29:31 1991 */ /**//**/ if (curClass == stringClass) { /**//**/ fwrite(object->data, sizeof(Byte), numOOPs(object) * sizeof(OOP), stdout); /**//**/ fflush(stdout); /**//**/ printf("\n----------------------------------------\n"); /**//**/ } /**/#endif /* debugging Mon Oct 28 12:29:31 1991 */ /**/ /**/ /**//* { extern mst_Boolean gcDebug; /**/ if (gcDebug) { /**/ dprintf("copying at %#8x, size %d\n", curSpace->scanPtr, object->objSize); /**/ } /**/ } /**/*/ /**/ /**/ /* Ensure that our class is also present in new space */ /**/ /* don't need to do the isInt test for this case */ /**/ localMaybeMoveOOP(curClass); /**/ /**/ stepSize = object->objSize * sizeof(OOP); /**/ if (curClass == compiledMethodClass) { /**/ /* Compiled methods have to be dealt with specially since they /**/ * have a structure thats unlike a regular Smalltalk object: /**/ * it has two fixed instance variables (description and /**/ * methodHeader), a variable number of literals, and then /**/ * a bunch of bytecodes, which must be skipped over */ /**/ method = (Method)object; /**/ localMaybeMoveOOP(method->descriptor); /**/ if (method->header.headerFlag == 0 || method->header.headerFlag == 3) { /**/ count = method->header.numLiterals; /**/ for (i = 0; i < count; i++) { /**/ localMaybeMoveOOP(method->literals[i]); /**/ } /**/ } /**/ /**/ } else if (!classIsPointers(curClass)) { /**/ /* nothing to scan, just skip over it */ /**/ } else { /**/ /* we've got an object with sub structure, so we set the object /**/ * size pointer to 2 words less than the object size (ignore /**/ * the header; weve already copied the class) and set the /**/ * scan pointer to the first word of the object. We then continue /**/ * to go through the normal scanning procedure (fall out the /**/ * bottom of the if and go back to the top of the loop again) /**/ */ /**/ count = numOOPs(object); /**/ for (i = 0, oop = object->data; i < count; i++, oop++) { /**/ localMaybeMoveOOP(*oop); /**/ } /**/ /**/ } /**/ curSpace->scanPtr += stepSize; /**/ } /**/} #endif /* pre_sc_gc Sun Jun 18 15:26:37 1995 */ #ifdef preserved /* Sat Jul 27 17:06:09 1991 */ /**/static void copyReferencedObjects(numBytes) /**/long numBytes; /**/{ /**/ Object object; /**/ OOP curClass; /**/ int stepSize, i; /**/ Method method; /**/ /**/ copyQuota += numBytes; /**/ while (curSpace->scanPtr < curSpace->copyPtr /**/ && copyQuota > 0) { /* there's more to scan */ /**/ if (curObject == nil) { /**/ /* if there is no current object, start off with the object's class */ /**/ object = (Object)curSpace->scanPtr; /**/ curClass = object->objClass; /**/ maybeMoveOOP(curClass); /**/ /**/ if (curClass == compiledMethodClass) { /**/ /* Compiled methods have to be dealt with specially since they /**/ * have a structure that''s unlike a regular Smalltalk object: /**/ * it has two fixed instance variables (description and /**/ * methodHeader), a variable number of literals, and then /**/ * a bunch of bytecodes, which must be skipped over */ /**/ stepSize = object->objSize * sizeof(OOP); /**/ method = (Method)object; /**/ maybeMoveOOP(method->descriptor); /**/ if (method->header.headerFlag == 0 || method->header.headerFlag == 3) { /**/ for (i = 0; i < method->header.numLiterals; i++) { /**/ maybeMoveOOP(method->literals[i]); /**/ } /**/ } /**/ /**/ curSpace->scanPtr += stepSize; /**/ copyQuota -= stepSize; /**/ } else if (!classIsPointers(curClass)) { /**/ /* nothing to scan, just skip over it */ /**/ stepSize = object->objSize * sizeof(OOP); /**/ curSpace->scanPtr += stepSize; /**/ copyQuota -= stepSize; /**/ } else { /**/ /* we've got an object with sub structure, so we set the object /**/ * size pointer to 2 words less than the object size (ignore /**/ * the header; we''ve already copied the class) and set the /**/ * scan pointer to the first word of the object. We then continue /**/ * to go through the normal scanning procedure (fall out the /**/ * bottom of the if and go back to the top of the loop again) /**/ */ /**/ curObject = object; /**/ curObjectSize = numOOPs(curObject) * sizeof(OOP); /**/ curSpace->scanPtr = (char *)curObject->data; /**/ } /**/ /**/ } else { /**/ /* we're part way through scanning an object, continue to scan... */ /**/ if (curObjectSize <= 0) { /**/ curObject = nil; /**/ } else { /**/ maybeMoveOOP(*(OOP *)curSpace->scanPtr); /**/ stepSize = sizeof(OOP); /**/ curSpace->scanPtr += stepSize; /**/ curObjectSize -= stepSize; /**/ copyQuota -= stepSize; /**/ } /**/ } /**/ } /**/ /**/ if (copyQuota < 0) { /**/ copyQuota = 0; /**/ } /**/} /**/ #endif /* preserved Sat Jul 27 17:06:09 1991 */ /* * mst_Boolean gcOff() * * Description * * Turns off the garbage collector. Returns the previous on/off state. * * Outputs * * Previous state of the garbage collector (on or off). */ mst_Boolean gcOff() { mst_Boolean oldGCState; oldGCState = gcState; gcState = false; return (oldGCState); } /* * void gcOn() * * Description * * Turns on the garbage collector. * */ void gcOn() { gcState = true; } /* * void setGCState(state) * * Description * * Set the garbage collector flag to the specified state (either on or * off). * * Inputs * * state : mst_Boolean, true => gc on. * */ void setGCState(state) mst_Boolean state; { gcState = state; } #ifdef pre_ms_gc /* Fri Jun 9 23:12:28 1995 */ /**//* /**/ * static void clearOldOOPs() /**/ * /**/ * Description /**/ * /**/ * Scans through the OOP table, removing OOPS that have died. Only /**/ * called at the end of a full GC to remove any stragglers. /**/ * /**/ */ /**/static void clearOldOOPs() /**/{ /**/ register OOP oop; /**/ /**/ for (oop = oopTable; oop<&oopTable[OOP_TABLE_SIZE]; oop++) { /**/ if (!(oop->flags & F_FREE)) { /**/ if (!(oop->flags & evenOddFlag)) { /**/ /* we've found a dead one...add it to the free list */ /**/ /* !!! Check for finalize here!! */ /**/ numFreeOOPs++; /**/ /* Here's why I am not using the |= FREE -- Speed. I think that every /**/ * case where I would need to have this (basically to rescue a /**/ * mistakenly GCed object) can be worked around by not allocating /**/ * the OOP until the last possible moment (after all the object /**/ * allocations have occurred. Allocating the OOP will move the object /**/ * into toSpace if need be */ /**/ oop->flags = F_FREE; /**/ /* oop->flags |= F_FREE; /* keep the other bits in case we mistakenly freed */ /**/ } else { /**/ /* !!! may not want to clear completey to 0? */ /**/ oop->flags &= ~EVEN_ODD_MASK; /**/ } /**/ } /**/ /**/#ifdef pre_sc_gc /* Sat Jul 27 17:33:01 1991 */ /**//**/ for (oop = &oopTable[oopTableIndex]; oop<&oopTable[OOP_TABLE_SIZE]; oop++) { /**//**/ if (!(oop->flags & F_FREE)) { /**//**/ if (!(oop->flags & evenOddFlag)) { /**//**/ /* we've found a dead one...add it to the free list */ /**//**/ numFreeOOPs++; /**//**/ oop->object = (Object)freeOOPs; /**//**/ freeOOPs = oop; /**//**/ freeOOPs->flags |= F_FREE; /**//**/ } else { /**//**/ /* turn off the bit for the space we're not in */ /**//**/ oop->flags &= ~(evenOddFlag ^ EVEN_ODD_MASK); /**//**/ } /**//**/ } /**//**/ /**/#endif /* pre_sc_gc Sat Jul 27 17:33:01 1991 */ /**/ } /**/} #endif /* pre_ms_gc Fri Jun 9 23:12:28 1995 */ /* * mst_Boolean growTo(semiSpaceSize) * * Description * * Grows the allocated memory to the given size in bytes, if it's not * there already. In the future, the gc should give some indication that * it was not able to acquire the required number of bytes, and this * function will return false, causing the system primitive to fail. * * Inputs * * semiSpaceSize: * Size in bytes to grow the semispaces to. * * Outputs * * True if the operation was successful, False if the memory could not be * allocated (this is not currently implemented). */ mst_Boolean growTo(semiSpaceSize) unsigned long semiSpaceSize; { if (semiSpaceSize > maxSpaceSize) { maxSpaceSize = semiSpaceSize; gcFlip(); } return true; } /* * void gcFlip() * * Description * * Switches the garbage collector's notion of which space is "new" space * and which is "old" space. Readjusts the garbage collection parameters * based on things like the allocation to copying ratio. Copies the root * set to new space. * */ int oldOopTableIndex; void gcFlip() { #ifdef pre_ms_gc /* Sun Jul 9 00:23:42 1995 */ /**/ long oldCopySize, oldNewSize; #endif /* pre_ms_gc Sun Jul 9 00:23:42 1995 */ double lastPercent; { extern mst_Boolean okToCheck; if (okToCheck) { debug(); } } if (!gcState) { errorf("Attempted to do a gcFlip with garbage collector off!"); exit(1); } #ifndef OPTIMIZE if (gcFlipCounter >= 1) { errorf("Attempted to do a gcFlip too soon after a gcFlip!"); exit(1); } #endif #ifdef OOP_DEBUGGING printf("%d free oops = %.2f%%, scanner was at %d/%d\n", numFreeOOPs, 100.0 * numFreeOOPs / OOP_TABLE_SIZE, oopTableIndex, OOP_TABLE_SIZE); #endif if (gcMessage && !regressionTesting) { /* print the first part of this message before we finish scanning * oop table for live ones, so that the delay caused by this scanning * is apparent. */ printf("\"GC flipping "); fflush(stdout); } #ifdef pre_ms_gc /* Sat Jun 24 01:55:53 1995 */ /**/ oldCopySize = curSpace->copyPtr - curSpace->space; /**/ oldNewSize = curSpace->space + curSpace->totalSize - curSpace->allocPtr; /**/ /**/ if (oldCopySize == 0) { /* ### Experimental */ /**/ oldCopySize = oldNewSize; /**/ } #endif /* pre_ms_gc Sat Jun 24 01:55:53 1995 */ #ifdef preserved /* Sat Jul 27 17:30:33 1991 */ /**/ copyRate = ((double)oldCopySize) / oldNewSize; /**/ copyRate *= copyRateAdjustment; #endif /* preserved Sat Jul 27 17:30:33 1991 */ #ifdef pre_ms_gc /* Fri Jun 9 23:13:52 1995 */ /**/ toSpace ^= F_SPACE; /**/ fromSpace ^= F_SPACE; /**/ evenOddFlag ^= EVEN_ODD_MASK; /* switch which bit is in use */ /**/ curSpace = &spaces[boolSpace(toSpace)]; #endif /* pre_ms_gc Fri Jun 9 23:13:52 1995 */ #ifdef pre_full_gc /* Sun Aug 4 19:24:21 1991 */ /**/ curObject = nil; #endif /* pre_full_gc Sun Aug 4 19:24:21 1991 */ #ifdef preserved /* Sat Aug 3 18:49:00 1991 */ /**/ copyQuota = 0; #endif /* preserved Sat Aug 3 18:49:00 1991 */ oldOopTableIndex = oopTableIndex; oopTableIndex = 0; markOOPs(); sweepOOPs(); #ifdef GC_DEBUGGING /* Sun Aug 20 15:32:50 1995 */ /**/{ /**/ char *ptr; /**/ mst_Object object; /**/ /**/ ptr = memSpace.space; /**/ /**/ while (ptr < memSpace.allocPtr) { /**/ object = (mst_Object)ptr; /**/ /**/ displayObject(object); /**/ if (object->objClass == stringClass) { /**/ printf("--- String: '"); /**/ fwrite(object->data, sizeof(Byte), size2Bytes(object->objSize), stdout); /**/ printf("'\n"); /**/ } /**/ /**/ ptr += size2Bytes(object->objSize); /**/ } /**/} #endif /* GC_DEBUGGING Sun Aug 20 15:32:50 1995 */ /* At this point, storage in memory is compacted and contiguous, so we can * examine how much memory we have left, and decide if we need to increase * memory some more. */ lastPercent = (memSpace.allocPtr - memSpace.space) * 100.0 / memSpace.totalSize; if (lastPercent > growThresholdPercent) { /* XXX not quite right -- with bad values for grow rate, can undergrow. */ maxSpaceSize = (unsigned long)(maxSpaceSize * (1.0 + spaceGrowRate/100.0)); maxSpaceSize &= ~(sizeof(long)-1); /* round to word boundary */ } if (maxSpaceSize > memSpace.totalSize) { growMemory(); } /* Since things have moved around, any pointers directly at or into * objects need to be adjusted. Things which reference objects via OOPs do * not need adjustment, since the OOPs don't move. */ restoreObjectPointers(); #ifdef pre_ms_gc /* Sat Jun 10 17:55:00 1995 */ /**/ /**/ moveRootOOPs(); /**/ copyReferencedObjects(); /* copy what we can */ /**/ clearOldOOPs(); #endif /* pre_ms_gc Sat Jun 10 17:55:00 1995 */ #ifdef pre_ms_gc /* Sat Jun 24 00:17:37 1995 */ /**/ curSpace->percentUsed = (curSpace->scanPtr - curSpace->space) * 100.0 /**/ / curSpace->totalSize; #endif /* pre_ms_gc Sat Jun 24 00:17:37 1995 */ /* if oldCopySize / size of space > threshold allocate new old space */ /* note the use of quotation marks around the printed message. The idea here was to make them appear as Smalltalk comments, so that generated output could be fed to another Smalltalk without harm. */ if (gcMessage && !regressionTesting) { #ifdef pre_ms_gc /* Sun Jun 18 15:32:13 1995 */ /**/ printf("to space %d...", boolSpace(toSpace)); fflush(stdout); #endif /* pre_ms_gc Sun Jun 18 15:32:13 1995 */ printf("copied space = %.1f%%...", lastPercent); #ifdef pre_full_gc /* Sun Aug 4 20:09:15 1991 */ /**/ printf("copied space = %.1f%%...", oldCopySize * 100.0 / MEM_SPACE_SIZE); #endif /* pre_full_gc Sun Aug 4 20:09:15 1991 */ } if (gcMessage && !regressionTesting) { printf("done\"\n"); } gcFlipped = true; } /* * mst_Boolean growMemoryTo(spaceSize) * * Description * * Grows the memory segment to sapceSize. Shoudl be called after the * sweep has occurred so that things are contiguous. Ensures that the OOP * table pointers are fixed up to point to the new objects. * * Inputs * * spaceSize: * The size of memory to grow to. If it's not larger than the * current allocation, nothing happens. * * Outputs * * True if the operation succeeded, false of the memory could not be * grown. */ mst_Boolean growMemoryTo(spaceSize) unsigned long spaceSize; { if (spaceSize > maxSpaceSize) { maxSpaceSize = spaceSize; return growMemory(); } return true; } /* * static mst_Boolean growMemory() * * Description * * Grows the memory segment to maxSpaceSize. Should be called after the * sweep has occurred so that things are contiguous. Ensures that the OOP * table pointers (the live ones) are fixed up to point to the new * objects. * */ static mst_Boolean growMemory() { unsigned long spaceDelta; char *oldSpacePtr; OOP oop; oldSpacePtr = memSpace.space; memSpace.space = (char *)realloc(memSpace.space, maxSpaceSize); if (memSpace.space == NULL) { /* !!! check to see if realloc frees existing memory if it cannot * allocate more */ printf("\n\n[Memory allocation failure]\nCan't allocate enough memory to continue.\n"); /* try to recover */ maxSpaceSize = memSpace.totalSize; memSpace.space = oldSpacePtr; return false; } spaceDelta = memSpace.space - oldSpacePtr; memSpace.totalSize = maxSpaceSize; memSpace.allocPtr += spaceDelta; memSpace.maxPtr = memSpace.space + memSpace.totalSize; if (oopTable) { /* Fix up the OOP table pointers to objects */ for (oop = oopTable; oop < &oopTable[OOP_TABLE_SIZE]; oop++) { if (!(oop->flags & F_FREE)) { oop->object = (mst_Object)(((char *)oop->object) + spaceDelta); } } } return true; } #ifdef preserved /* Sat Jul 27 16:37:34 1991 */ /**/void gcFlip() /**/{ /**/ long oldCopySize, oldNewSize; /**/ /**/ if (!gcState) { /**/ errorf("Attempted to do a gcFlip with garbage collector off!"); /**/ exit(1); /**/ } /**/ /**/ if (gcFlipCounter >= 1) { /**/ errorf("Attempted to do a gcFlip too soon after a gcFlip!"); /**/ exit(1); /**/ } /**/ /**/ /**/#ifdef OOP_DEBUGGING /**/ printf("%d free oops = %.2f%%, scanner was at %d/%d\n", numFreeOOPs, /**/ 100.0 * numFreeOOPs / OOP_TABLE_SIZE, oopTableIndex, OOP_TABLE_SIZE); /**/#endif /**/ /**/ if (gcMessage && !regressionTesting) { /**/ /* print the first part of this message before we finish scanning /**/ * oop table for live ones, so that the delay caused by this scanning /**/ * is apparent. /**/ */ /**/ printf("\"GC flipping "); fflush(stdout); /**/ } /**/ /**/ finishOOPScan(); /* make sure we're done */ /**/ /**/ oldCopySize = curSpace->copyPtr - curSpace->space; /**/ oldNewSize = curSpace->space + MEM_SPACE_SIZE - curSpace->allocPtr; /**/ /**/if (oldCopySize == 0) { /* ### Experimental */ /**/ oldCopySize = oldNewSize; /**/} /**/ /**/ /**/ copyRate = ((double)oldCopySize) / oldNewSize; /**/ copyRate *= copyRateAdjustment; /**/ /**/ toSpace ^= F_SPACE; /**/ fromSpace ^= F_SPACE; /**/ evenOddFlag ^= EVEN_ODD_MASK; /* switch which bit is in use */ /**/#ifdef bogus /* Sat Oct 13 15:38:55 1990 */ /**//**/ toSpace = !toSpace; /**//**/ fromSpace = !fromSpace; /**/#endif /* bogus Sat Oct 13 15:38:55 1990 */ /**/ curSpace = &spaces[boolSpace(toSpace)]; /**/ curObject = nil; /**/ copyQuota = 0; /**/ oopTableIndex = 0; /**/ initSpace(curSpace); /**/ /**/#ifdef remove_soon /* Mon May 14 23:41:55 1990 */ /**//**/zeroMarks(); /**/#endif /* remove_soon Mon May 14 23:41:55 1990 */ /**/ /**/ /* note the use of quotation marks around the printed message. The /**/ idea here was to make them appear as Smalltalk comments, so that /**/ generated output could be fed to another Smalltalk without harm. */ /**/ if (gcMessage && !regressionTesting) { /**/ printf("to space %d...", boolSpace(toSpace)); fflush(stdout); /**/ printf("copied space = %.1f%%...", oldCopySize * 100.0 / MEM_SPACE_SIZE); /**/ } /**/ moveRootOOPs(); /**/ if (gcMessage && !regressionTesting) { /**/ printf("done\"\n"); /**/ } /**/ gcFlipped = true; /**/} #endif /* preserved Sat Jul 27 16:37:34 1991 */ static void initMarkingSystem() { makeNewChunk(oldChunk, nil); copySP = oldChunk->stack; } static void finalizeMarkingSystem() { MarkStackChunk *chunk, *deadChunk; for (chunk = oldChunk; chunk; ) { deadChunk = chunk; chunk = chunk->nextChunk; free(deadChunk); } } static void markOOPs() { initMarkingSystem(); markBuiltinOOPs(); markGlobalOOPs(); markProcessorRegisters(); markRegisteredOOPs(); markCompileContext(); markIncubatorOOPs(); finalizeMarkingSystem(); #ifdef DEBUG_FREED /* Mon Jul 3 00:38:46 1995 */ /**/ { /**/ OOP oop; int i; /**/ for (i = 0, oop = oopTable; oop < &oopTable[oldOopTableIndex]; oop++, i++) { /**/ if (!(oop->flags & F_REACHABLE)) { /**/ printf("[%4d]: "); fflush(stdout); /**/ printObject(oop); /**/ printf("\n"); /**/ fflush(stdout); /**/ } /**/ } /**/ } #endif /* DEBUG_FREED Mon Jul 3 00:38:46 1995 */ reverseOOPPointers(); } #ifdef comments the class must be copied if the object is bytes or words, done. if the object is a compiled method, queue compiled method copies else queue copies for each oop slot. but -- queuing costs -- we can either trade stack depth for queuing -- queue bunches of objects at the same level, then do those, etc -- the queue grows as the number of objects at this level of access, but for each of those it grows one more level, etc. The queue eventually copies all of memory. * a choice would be to have a disciplined copy -- copy only pointers to those things referenced by the current object. then for each of those, do the same -- more copying because things arent marked yet (unless we mark em) still -- grows as fanout grows. for 4 levels of 5 object each, the series is 1, 5, 25, 125, 625 -- 5^n. the stack approach grows as the depth of reference. stops immediately when it sees a marked one. equivalent to a series of nested for loops & function calls, but cheaper performance. * stack needs to record the current object pointer, and the end condition (and which case it was in -- normal pointer, or compiled method (though, it could fake it so that the count etc seemed to the busy loop like normal and the special casing was only discovered after the busy loop has finished)) while (stack has stuff on it) { if (!isMarked(csp->object->objClass)) { object = csp->object; /* copy stack pointer == csp */ csp++; csp->object = object->objClass; continue; /* the main loop */ } /* here if we are into the main body of the object */ /* !!! need to see if we are still processing some other object or not. */ object = csp->object; curClass = object->objClass; if (curClass == compiledMethodClass) { /* Compiled methods have to be dealt with specially since they * have a structure that's unlike a regular Smalltalk object: * it has two fixed instance variables (description and * methodHeader), a variable number of literals, and then * a bunch of bytecodes, which must be skipped over */ method = (Method)object; localMaybeMoveOOP(method->descriptor); if (method->header.headerFlag == 0 || method->header.headerFlag == 3) { count = method->header.numLiterals; for (i = 0; i < count; i++) { localMaybeMoveOOP(method->literals[i]); } } } else if (!classIsPointers(curClass)) { /* we are done with this guy, pop the stack & continue */ csp--; /* more complicated, probably -- objstacks*/ continue; } else { /* we've got an object with sub structure, so we set the object * size pointer to 2 words less than the object size (ignore * the header; we've already copied the class) and set the * scan pointer to the first word of the object. We then continue * to go through the normal scanning procedure (fall out the * bottom of the if and go back to the top of the loop again) */ count = numOOPs(object); for (i = 0, oop = object->data; i < count; i++, oop++) { localMaybeMoveOOP(*oop); } } stack record { object (not oop); int index; int maxindex; state (in prog -- at start) classification (?) pointers, compiled method } the recursive form markAnObject class = object->objClass; markTheCurrentObject; if (unMarked(class) state1 ======> in the setup case. markAnObject(class) if (obj compiledMethod) { if (hasLiterals) { foreach literal state2 ======> curliteral, termination count, in the literal case markAnObject(literal); } } else if (hasPointers) { foreach pointer state3 ======> curpointer, term count, markAnObject(pointer); } #endif #ifdef USE_REAL_CODE static void initCopyStack() { makeNewChunk(currentChunk, nil); copySP = currentChunk->stack; } #else #define initCopyStack() \ currentChunk = oldChunk; \ copySP = currentChunk->stack; #endif #ifdef USE_REAL_CODE /* Free whatever we've allocated. The invariant is that the current chunk * at most only has a next chunk which has nil for its own next pointer. * The value of currentChunk should be a chunk where prevChunk is nil */ static void finishCopyStack() { if (oldChunk->nextChunk != nil) { free(oldChunk->nextChunk); } free(oldChunk); } #else #define finishCopyStack() #endif void markAnOOP(oop) OOP oop; { /* mst_Boolean inLoop = false; OOP *curOOP, *finalOOP; */ /* pro tem -- get away from local varialbes -- do everything on copy stack, then once algorithm is coded,switch to local vars */ initCopyStack(); copySP->oop = oop; copySP->inLoop = false; /* the others don't matter if inLoop isfalse*/ markAnOOPInternal(); finishCopyStack(); } void markOOPRange(startOOP, endOOP) OOP *startOOP, *endOOP; { initCopyStack(); copySP->inLoop = true; copySP->curOOP = startOOP; copySP->finalOOP = endOOP; markAnOOPInternal(); finishCopyStack(); } static void markAnOOPInternal() { OOP oop; do { if (!copySP->inLoop) { /* just starting with this oop */ OOP objClass; mst_Object object; oop = copySP->oop; if (!isOOPMarked(oop)) { objClass = oopToObj(oop)->objClass; oop->flags |= F_REACHABLE; if (!isOOPMarked(objClass)) { pushCopyStack(copySP); copySP->oop = objClass; copySP->inLoop = false; continue; /* this class is reachable too! so tail * recurse! */ } } /* see if the object has pointers, set up to copy them if so */ object = oopToObj(copySP->oop); objClass = object->objClass; if (objClass == compiledMethodClass) { /* set up the iteration slightly differently */ Method method; method = (Method)object; /* printf("!!! in compiled method marked %d\n", !isOOPMarked(method->descriptor)); */ /* yeah, it's not completely optimal, but it's ok. */ if (!isOOPMarked(method->descriptor)) { pushCopyStack(copySP); copySP->oop = method->descriptor; copySP->inLoop = false; continue; /* tail recurse!!! */ } /* printf("!!! testing header flag %d\n", method->header.headerFlag); */ if ((method->header.headerFlag == 0) || (method->header.headerFlag == 3)) { /* printf("setting up for loop on literals"); */ /* pushCopyStack(copySP); */ copySP->inLoop = true; copySP->curOOP = method->literals; copySP->finalOOP = method->literals + method->header.numLiterals; continue; /* tail recurse! */ } } else if (classIsPointers(objClass)) { /* printf(">>>> Setting up iteration, stack %x\n", copySP); */ /* pushCopyStack(copySP); */ copySP->inLoop = true; copySP->curOOP = object->data; copySP->finalOOP = object->data + numOOPs(object); continue; /* tail recurse! */ } /* we're here if we don't have any other objects to /* pop a level and/or return */ popCopyStack(copySP); continue; } else { /* we are in the loop! */ iterationLoop: /* XXX the name finalOOP is bad -- it's justone past thefinal */ /* in a loop, do next iteration */ if (copySP->curOOP >= copySP->finalOOP) { /* we're done with this iteration. */ popCopyStack(copySP); continue; } oop = *copySP->curOOP; copySP->curOOP++; if (!isInt(oop) && !isOOPMarked(oop)) { /* printf("curoop %x final %x\n", copySP->curOOP, copySP->finalOOP); */ /* set up for tail recursion */ pushCopyStack(copySP); copySP->oop = oop; copySP->inLoop = false; continue; /* tail recurse!!! */ } /* with a goto here, or with a more powerful continue construct above * this code could be faster -- we are already in the loop case, so * all we need to do is to goto the next label. Since speed is a * requirement here, I'm doing it. */ goto iterationLoop; } #ifdef looks_like_not_needed /* Sun Jun 11 19:13:30 1995 */ /**/ /**/ if (!isMarked(oopToObj(*curOOP))) { /**/ /* save current state, loop around to mark the oop */ /**/ pushCopyStack(copySP); /**/ /* XXX not sure about does SP point at current or next */ /**/ copySP->curOOP = curOOP; /**/ copySP->finalOOP = finalOOP; /**/ copySP->inLoop = inLoop; /* it has to be TRUE here, but... */ /**/ /**/ /* "recursively call" (loop around) marking the refereced object */ /**/ inLoop = false; /**/ oop = *curOOP; /**/ } else { /* already marked, so continue */ /**/ /**/ curOOP++; /**/ if (curOOP >= finalOOP) { /* finished with this object */ /**/ popCopyStack(copySP); /**/ curOOP = copySP->curOOP; /**/ finalOOP = copySP->finalOOP; /**/ inLoop = copySP->inLoop; /**/ } /**/ } #endif /* looks_like_not_needed Sun Jun 11 19:13:30 1995 */ } while (!atStackBase()); } /* * static void reverseOOPPointers() * * Description * * Iterate through the OOP table. On non-free OOPS that are marked, * interchange the pointer to the object with the pointer to the object's * class. * */ static void reverseOOPPointers() { OOP oop; mst_Object object; for (oop = oopTable; oop < &oopTable[OOP_TABLE_SIZE]; oop++) { if ((oop->flags & (F_FREE | F_REACHABLE)) == F_REACHABLE) { object = oopToObj(oop); oop->object = (mst_Object)object->objClass; object->objClass = markObject(oop); oop->flags &= ~F_REACHABLE; /* moved here from the unconditonal part as an experiment */ } else { oop->flags = F_FREE; /* was |= */ oop->object = NULL; /* helps with debugging */ } } } /* #define SWEEP_DEBUG */ static void sweepOOPs() { char *from, *fromStart, *to; unsigned long chunkSize; /* Algorithm: * Start at beginning of allocated space. * Skip over the initial contiguous range of marked object, unmarking as you go. loop: * skip over the contiguous range of unmarked objects, leaving "to" where it is and advancing "from". * if "to" passes the end of allocated storage, we are done. * set "fromStart" to "from", and skip over the next contiguous range of marked objects, advancing "from". * copy the range ["fromStart".."from") to "to". advance "to" to right after the newly copied area. * goto loop */ mst_Object object; register OOP curClass, oop; from = to = memSpace.space; while (to < memSpace.allocPtr) { object = (mst_Object)to; if (!isMarked(object)) { /* found the end of the contiguous range */ break; } /* unmark this dude */ oop = unmarkObject(object->objClass); curClass = (OOP)oop->object; oop->object = object; object->objClass = curClass; to += size2Bytes(object->objSize); } #ifdef SWEEP_DEBUG printf("skipped %d bytes of contig alloc %x space %x max %x\n", to - memSpace.space, memSpace.allocPtr, memSpace.space, memSpace.maxPtr); #endif /* SWEEP_DEBUG */ /* we've skipped over the marked (and hence no move needed) initial set of * objects. Now begin the main execution loop */ from = to; while (from < memSpace.allocPtr) { fromStart = from; /* debugging only */ while (from < memSpace.allocPtr) { object = (mst_Object)from; if (isMarked(object)) { /* found a non-free chunk */ break; } /* skip over the free memory */ from += size2Bytes(object->objSize); } #ifdef SWEEP_DEBUG printf("skipped free range %x .. %x %d bytes\n", fromStart, from, from - fromStart); #endif /* SWEEP_DEBUG */ if (from >= memSpace.allocPtr) { #ifdef SWEEP_DEBUG printf("hit end of memory\n"); #endif /* SWEEP_DEBUG */ break; /* we've hit the end of active memory */ } fromStart = from; /* span the next in-use contiguous chunk of objects */ while (from < memSpace.allocPtr) { object = (mst_Object)from; if (!isMarked(object)) { /* found a free chunk */ break; } /* unmark this dude & tell the oop where the object *will be* */ oop = unmarkObject(object->objClass); curClass = (OOP)oop->object; oop->object = (mst_Object)(to + ((char *)object - fromStart)); object->objClass = curClass; /* skip over the object */ from += size2Bytes(object->objSize); } /* copy the bytes down */ chunkSize = from - fromStart; #ifdef SWEEP_DEBUG printf("copying range %x .. %x to %x, %d bytes\n", fromStart, from, to, chunkSize); #endif /* SWEEP_DEBUG */ memcpy(to, fromStart, chunkSize); to += chunkSize; } memSpace.allocPtr = to; unmarkBuiltinOOPs(); #ifdef pre_sc_gc /* Thu Jun 22 00:35:45 1995 */ /**/ int stepSize, count; /**/ Method method; /**/ register int i; /**/ /**/ while (curSpace->scanPtr < curSpace->copyPtr) { /* there's more to scan */ /**/ /* if there is no current object, start off with the object's class */ /**/ object = (mst_Object)curSpace->scanPtr; /**/ curClass = object->objClass; /**/ /**/#ifdef debugging /* Mon Oct 28 12:29:31 1991 */ /**//**/ if (curClass == stringClass) { /**//**/ fwrite(object->data, sizeof(Byte), numOOPs(object) * sizeof(OOP), stdout); /**//**/ fflush(stdout); /**//**/ printf("\n----------------------------------------\n"); /**//**/ } /**/#endif /* debugging Mon Oct 28 12:29:31 1991 */ /**/ /**/ /**//* { extern mst_Boolean gcDebug; /**/ if (gcDebug) { /**/ dprintf("copying at %#8x, size %d\n", curSpace->scanPtr, object->objSize); /**/ } /**/ } /**/*/ /**/ /**/ /* Ensure that our class is also present in new space */ /**/ /* don't need to do the isInt test for this case */ /**/ localMaybeMoveOOP(curClass); /**/ /**/ stepSize = object->objSize * sizeof(OOP); /**/ if (curClass == compiledMethodClass) { /**/ /* Compiled methods have to be dealt with specially since they /**/ * have a structure thats unlike a regular Smalltalk object: /**/ * it has two fixed instance variables (description and /**/ * methodHeader), a variable number of literals, and then /**/ * a bunch of bytecodes, which must be skipped over */ /**/ method = (Method)object; /**/ localMaybeMoveOOP(method->descriptor); /**/ if (method->header.headerFlag == 0 || method->header.headerFlag == 3) { /**/ count = method->header.numLiterals; /**/ for (i = 0; i < count; i++) { /**/ localMaybeMoveOOP(method->literals[i]); /**/ } /**/ } /**/ /**/ } else if (!classIsPointers(curClass)) { /**/ /* nothing to scan, just skip over it */ /**/ } else { /**/ /* we've got an object with sub structure, so we set the object /**/ * size pointer to 2 words less than the object size (ignore /**/ * the header; weve already copied the class) and set the /**/ * scan pointer to the first word of the object. We then continue /**/ * to go through the normal scanning procedure (fall out the /**/ * bottom of the if and go back to the top of the loop again) /**/ */ /**/ count = numOOPs(object); /**/ for (i = 0, oop = object->data; i < count; i++, oop++) { /**/ localMaybeMoveOOP(*oop); /**/ } /**/ /**/ } /**/ curSpace->scanPtr += stepSize; /**/ } /**/ #endif /* pre_sc_gc Thu Jun 22 00:35:45 1995 */ } static void markGlobalOOPs() { OOP **oopPtr, oop; /* not clear that using range marking works here */ int i; i = 0; /* copy objects that have global pointers */ for (oopPtr = globalOOPs; *oopPtr; oopPtr++) { oop = **oopPtr; /* printf("**** [maybeMarkGlobal %d %x]\n", i++, oop); */ maybeMarkOOP(oop); } } #ifdef pre_sc_gc /* Thu Jun 22 00:39:38 1995 */ /**//* /**/ * static void moveRootOOPs() /**/ * /**/ * Description /**/ * /**/ * Copies the root objects from old space to new space. All of the root /**/ * objects are those that are mentioned in the set of objects that are /**/ * known specially by the interpreter, those that are being used by the /**/ * interpreter, and some information about compilation state. Also, the /**/ * built-in oops (Characters, nil, true, false) are marked as being in new /**/ * space so that they wont ever be moved. /**/ * /**/ */ /**/static void moveRootOOPs() /**/{ /**/ OOP **oopPtr, oop; /**/ /**/ markBuiltinOOPs(); /**/ /**/ /* copy objects that have global pointers */ /**/ for (oopPtr = globalOOPs; *oopPtr; oopPtr++) { /**/ oop = **oopPtr; /**/ localMaybeMoveOOP(oop); /* use the maybe form here so that we don't /**/ * accidentally move builtins, which have /**/ * already been marked as being in the new /**/ * space /**/ */ /**/ } /**/ /**/ moveProcessorRegisters(); /**/ /**/ copyRegisteredOOPs(); /**/ /**/ copyCompileContext(); /**/} #endif /* pre_sc_gc Thu Jun 22 00:39:38 1995 */ /* * static void markBuiltinOOPs() * * Description * * Marks all of the builtin OOPS (nil, true, false, and the Characters) as * already marked, so they'll be bypassed as the transitive marker * reaches them. * */ static void markBuiltinOOPs() { register OOP oop; for (oop = &oopTable[OOP_TABLE_SIZE]; oop < &oopTable[TOTAL_OOP_TABLE_SLOTS]; oop++) { /* prevent them being fully marked */ oop->flags |= F_REACHABLE; } #ifdef pre_ms_gc /* Sat Jun 10 09:06:20 1995 */ /**/ for (oop = &oopTable[OOP_TABLE_SIZE]; oop < &oopTable[TOTAL_OOP_TABLE_SLOTS]; /**/ oop++) { /**/ oop->flags = (oop->flags & ~F_SPACE) | toSpace | F_EVEN | F_ODD; /**/ } #endif /* pre_ms_gc Sat Jun 10 09:06:20 1995 */ } /* * static void unmarkBuiltinOOPs() * * Description * * Marks all of the builtin OOPS (nil, true, false, and the Characters) as * already marked, so they'll be bypassed as the transitive marker * reaches them. * */ static void unmarkBuiltinOOPs() { register OOP oop; for (oop = &oopTable[OOP_TABLE_SIZE]; oop < &oopTable[TOTAL_OOP_TABLE_SLOTS]; oop++) { oop->flags &= ~F_REACHABLE; } } /* * static void initSpace(space) * * Description * * Initializes the allocation and copying pointers for semispace SPACE. * * Inputs * * space : Semispace index number. * */ static void initSpace(space) struct memorySpaceStruct *space; { char *oldSpace; if (space->totalSize < maxSpaceSize) { oldSpace = space->space; space->space = (char *)realloc(oldSpace, maxSpaceSize); if (space->space == NULL) { space->space = oldSpace; errorf("Could not grow space to %d", maxSpaceSize); /* ??? Should print some kind of warning here, like we can't reallocate * more space */ } else { space->totalSize = maxSpaceSize; } } space->allocPtr = space->space; #ifdef pre_ms_gc /* Sat Jun 24 02:12:03 1995 */ /**/ space->copyPtr = space->scanPtr = space->space; /**/ space->size = space->totalSize; /**/ space->allocPtr = space->space + space->size; #endif /* pre_ms_gc Sat Jun 24 02:12:03 1995 */ space->maxPtr = space->space + space->totalSize; } #ifdef pre_ms_gc /* Sat Jun 10 09:06:40 1995 */ /**/void growBothSpaces(newSize) /**/unsigned long newSize; /**/{ /**/ int i; /**/ /**/ maxSpaceSize = newSize; /**/ /**/ for (i = 0; i < 2; i++) { /**/ initSpace(&spaces[i]); /**/ } /**/} #endif /* pre_ms_gc Sat Jun 10 09:06:40 1995 */ #ifndef INLINE_MACROS /* * void maybeMoveOOP(oop) * * Description * * Move OOP to new space if it's not already there. * * Inputs * * oop : OOP to be examined, and, if it's in old space, moved to new * space. * */ void maybeMoveOOP(oop) OOP oop; { maybeMoveOOPMac(oop); } #endif /* INLINE_MACROS */ #ifdef pre_sc_gc /* Thu Jun 22 00:35:17 1995 */ /**//* /**/ * void moveOOP(oop) /**/ * /**/ * Description /**/ * /**/ * Moves an OOP from old space to new space unconditionally. Basically /**/ * marks the OOP as being in the current new space, copies the object that /**/ * the oop points to to new space, and sets the even/odd flags to keep the /**/ * OOP table garbage collector from reaping this OOP. /**/ * /**/ * Inputs /**/ * /**/ * oop : OOP to be moved. Should always be in OLD space. /**/ * /**/ */ /**/void moveOOP(oop) /**/OOP oop; /**/{ /**/ mst_Object object; /**/ /**/#ifndef OPTIMIZE /**/ if (isFake(oop)) { /**/ printf("moving fake object!!! %x\n", oop); /**/ debug(); /**/ } /**/#endif /* !OPTIMIZE */ /**/ /**/ object = oopToObj(oop); /**/ /* !!! this F_SPACE and TO_SPACE stuff should go */ /**/ oop->flags = (oop->flags & ~(F_SPACE|F_FREE)) | toSpace | evenOddFlag; /**/ oop->object = moveObject(object); /**/} /**/ /**//* /**/ * static Object moveObject(object) /**/ * /**/ * Description /**/ * /**/ * Copies OBJECT from old space to new space. Adjusts the garbage /**/ * collectors pointers to indicate that the object has been added to new /**/ * space so that the scanner will see it. /**/ * /**/ * Inputs /**/ * /**/ * object: Object to be moved to new space. /**/ * /**/ */ /**/static mst_Object moveObject(object) /**/mst_Object object; /**/{ /**/ long size; /**/ /**//* dprintf("moving %8x, size %d\n", curSpace->copyPtr, object->objSize); */ /**/#ifdef believed_obsolete /* Sat Oct 1 13:47:12 1994 */ /**//**/if ((long) object->objSize >= 1000) { /**//**/ debug(); /**//**/} /**/#endif /* believed_obsolete Sat Oct 1 13:47:12 1994 */ /**/ size = object->objSize * sizeof(OOP); /**/ memcpy(curSpace->copyPtr, object, size); /**/ object = (mst_Object)curSpace->copyPtr; /**/ curSpace->copyPtr += size; /**/ curSpace->size -= size; /**/ if (curSpace->copyPtr >= curSpace->allocPtr) { /**/ errorf("Garbage collector failed...ran out of room while copying!!!"); /**/ exit(0); /**/ } /**/ /**/ return (object); /**/} #endif /* pre_sc_gc Thu Jun 22 00:35:17 1995 */ /* * void debug() * * Description * * Used for debugging. You set a breakpoint in the debug routine in the * debugger, and have code call it when you want it to stop. Performs no * action normally. * */ void debug() { } #if defined(GC_TORTURE) /* * void startGCTorture() * * Description * * User level debugging routine to verify correct operation in a range of * code. Invoking this function ensures that the GC torturing is on. * Calls to this function and stopGCTorture nest, so only the outermost * call really has an effect. * * GC torturing means that the garbage collector is run on every * allocation. This means that objects which are not reachable from the * root set will be immediately freed. * */ void startGCTorture() { doGCTorture = true; doTortureCounter++; } /* * void stopGCTorture() * * Description * * User level debugging routine associated with startGCTorture. Turns off * the GC torturing if it's the outermost (in an invocation-stacking * order) one, otherwise, just decrements the torture count. * */ void stopGCTorture() { if (doTortureCounter > 0) { if (--doTortureCounter == 0) { /* on the transition to 0... */ doGCTorture = false; } } } #endif /********************************************************************** *********************************************************************** *********************************************************************** * * Incubator support routines * *********************************************************************** *********************************************************************** ***********************************************************************/ void incInitRegistry() { incOOPBasePtr = (OOP*)malloc(INIT_NUM_INCUBATOR_OOPS * sizeof(OOP *)); incOOPPtr = incOOPBasePtr; incOOPEndPtr = incOOPBasePtr + INIT_NUM_INCUBATOR_OOPS; } void incGrowRegistry() { OOP* oldBase; unsigned long oldPtrOffset; unsigned long oldRegistrySize, newRegistrySize; oldBase = incOOPBasePtr; oldPtrOffset = incOOPPtr - incOOPBasePtr; oldRegistrySize = incOOPEndPtr - incOOPBasePtr; newRegistrySize = oldRegistrySize + INCUBATOR_CHUNK_SIZE; incOOPBasePtr = (OOP *)realloc(incOOPBasePtr, newRegistrySize * sizeof(OOP *)); incOOPPtr = incOOPBasePtr + oldPtrOffset; incOOPEndPtr = incOOPBasePtr + newRegistrySize; } static void markIncubatorOOPs() { markOOPRange(incOOPBasePtr, incOOPPtr); }
These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.