ftp.nice.ch/pub/next/developer/languages/smalltalk/smalltalk.1.2.alpha5.s.tar.gz#/smalltalk-1.2.alpha5/lib/oop.h

This is oop.h in view mode; [Download] [Up]

/***********************************************************************
 *
 *	Object Table declarations.
 *
 *	$Revision: 1.5 $
 *	$Date: 1995/09/12 04:34:44 $
 *	$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	      7 Sep 95	  Added incubator support.
 *
 * sbb	     20 Aug 95	  Added growMemoryTo().
 *
 * sbb	      9 Jul 95	  Added lots of new externs.
 *
 * sbb	     23 Jun 95	  Switched to GST header guard prefix.
 *
 * sbb	      9 Jun 95	  Began the conversion to single GC space.
 *
 * sbb	     30 May 95	  Boolean => mst_Boolean.  Object => mst_Object.
 *
 * sbb	     27 Jan 91	  Force INLINE_MACROS on when optimizing.
 *
 * sbyrne     8 Apr 90	  Changed oopFree to oopValid to better reflect the
 *			  semantics.
 *
 * sbyrne    13 Jan 89	  Created.
 *
 */


#ifndef __GSTOOP__
#define __GSTOOP__

/* Comment this out for debugging */
#define INLINE_MACROS

#if defined(OPTIMIZE) && !defined(INLINE_MACROS)
/* Force this on when we're optimizing */
#define INLINE_MACROS
#endif

/* The number of OOPs in the system.  This is exclusive of Character, True,
   False, and UndefinedObject (nil) oops, which are built-ins. */
#define OOP_TABLE_SIZE		(10240 * 16) /* for the nonce, then back to 4 */

#define NUM_CHAR_OBJECTS	256
#define CHAR_OBJECT_BASE	OOP_TABLE_SIZE
#define NUM_BUILTIN_OBJECTS	3
#define BUILTIN_OBJECT_BASE	(CHAR_OBJECT_BASE + NUM_CHAR_OBJECTS)

#define nilOOPIndex		(BUILTIN_OBJECT_BASE + 0)
#define trueOOPIndex		(BUILTIN_OBJECT_BASE + 1)
#define falseOOPIndex		(BUILTIN_OBJECT_BASE + 2)

#define TOTAL_OOP_TABLE_SLOTS \
  ( OOP_TABLE_SIZE + NUM_CHAR_OBJECTS + NUM_BUILTIN_OBJECTS )

/*
 * Given a number of bytes "x", return the number of 32 bit words
 * needed to represent that object, rounded up to the nearest 32 bit
 * word boundary.
 */
#define ROUNDED_WORDS(x) \
  (((x) + sizeof(long) - 1) / sizeof(long))

#define GCIsOn() \
  (gcState)

#define inToSpace <><><>
/* XXX out #define inToSpace(oop) \
  ((((oop)->flags & F_SPACE) == toSpace) || isFake(oop))
*/

#define inFromSpace <><><>
/* XXX OUT /* ### Could use "!= toSpace" instead? (not now, I think) 
#define inFromSpace(oop) \
  (((oop)->flags & (F_SPACE | F_WEAK)) == fromSpace)
*/


/* XXX OUT
/* ### Could use "!= toSpace" instead? (not now, I think) 
#define inFromSpace(oop) \
  (((oop)->flags & (F_SPACE | F_WEAK)) == fromSpace)
*/

#ifdef old_code /* Sat Oct 13 15:40:02 1990 */
/**/#define inToSpace(oop) \
/**/  ((oop)->inSpace == toSpace)
/**/
/**/#define inFromSpace(oop) \
/**/  ((oop)->inSpace == fromSpace)
#endif /* old_code Sat Oct 13 15:40:02 1990 */

#define prepareToStoreMac(destOOP, srcOOP) 

#define maybeMoveOOPMac(oop) 

#define localMaybeMoveOOP <><><>
/*
#define localMaybeMoveOOP(oop) \
{ \
  if (!isInt(oop) && inFromSpace(oop)) { \
    moveOOP(oop); \
  } \
}
*/

#define maybeMarkOOP(oop) \
  if (!isOOPMarked(oop)) { \
    markAnOOP(oop); \
  }


#ifdef OPTIMIZE
#define clearGCFlipFlagsMac() 
#else 
#define clearGCFlipFlagsMac() \
  gcFlipCounter = 0
#endif /* OPTIMIZE */

#define oopAtMac(index) \
  ( &oopTable[index] )

#define oopAvailableMac(index) \
  ( oopTable[index].flags & F_FREE )

#define oopIndexMac(oop) \
  ( (OOP)(oop) - oopTable )

/***********************************************************************

Incubator support.

The incubator concept provides a mechanism to protect newly created
objects from being accidentally garbage collected before they can be
attached to some object which is reachable from the root set.

[It is very likely that this interface will move to gstpub.h as part
of the public interface at some point in the future.]

When to use this interface.
---------------------------

If you are creating some set of objects which will not be immediately (that means, 
before the next object is allocated from the Smalltalk memory system) be
attached to an object which is still "live" (reachable from the root set
of objects), you'll need to use this interface.

The interface provides the following operations:

void     incAddOOP(OOP anOOP)
    Adds a new object to the protected set.

IncPtr   incSavePointer()
    Retrieves the current incubator pointer.  Think of the incubator as a
    stack, and this operation returns the current stack pointer for later
    use (restoration) with the incSetPointer function.

void     incRestoresPointer(IncPtr ptr)
    Sets (restores) the incubator pointer to the given pointer value.

Usage:

Typically, when you are within a function which allocates more than one
object at a time, either directly or indirectly, you'd want to use the 
incubator mechanism.  First you'd save a copy of the current pointer
in a local variable.  Then, for each object you allocate (except the last, 
if you want to be optimal), after you create the object you add it to 
the incubator's list.  When you return, you need to restore the 
incubator's pointer to the value you got with incSavePointer using
the incRestorePointer function.

Here's an example from cint.c:

The old code was (the comments are added for this example):

  desc = (CFuncDescriptor)newInstanceWith(cFuncDescriptorClass, numArgs);
  desc->cFunction = cObjectNew(funcAddr);    // 1
  desc->cFunctionName = stringNew(funcName); // 2
  desc->numFixedArgs = fromInt(numArgs);
  desc->returnType = classifyTypeSymbol(returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] = classifyTypeSymbol(arrayAt(argsOOP, i), false);
  }

  return (allocOOP(desc));

"desc" is originally allocated via newInstance with.  At "1", more storage is
allocated, and the garbage collector has the potential to run and free (since
no live object is referring to it) desc's storage.  At "2" another object
is allocated, and again the potential for losing both desc and desc->cFunction
is there if the GC runs (this actually happened!).  

To fix this code to use the incubator, modify it like this:


  OOP     descOOP;
  IncPtr  ptr;


  incPtr = incSavePointer();
  desc = (CFuncDescriptor)newInstanceWith(cFuncDescriptorClass, numArgs);
  descOOP = allocOOP(desc);
  incAddOOP(descOOP);
  
  desc->cFunction = cObjectNew(funcAddr);
  incAddOOP(desc->cFunction);

  desc->cFunctionName = stringNew(funcName); 
  // since none of the rest of the function (or the functions it calls)
  // allocates any storage, we don't have to add desc->cFunctionName
  // to the incubator's set of objects, although we could if we wanted
  // to be completely safe against changes to the implementations of
  // the functions called from this function.

  desc->numFixedArgs = fromInt(numArgs);
  desc->returnType = classifyTypeSymbol(returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] = classifyTypeSymbol(arrayAt(argsOOP, i), false);
  }

  incRestorePointer(ptr);
  return (descOOP);


Note that it is permissible for a couple of functions to cooperate with
their use of the incubator.  For example, say function A allocates
some objects, then calls function B which allocates some more objects,
and then control returns to A where it does some more execution with the 
allocated objects.  If B is only called by A, B can leave the management
of the incubator pointer up to A, and just register the objects it
allocates with the incubator.  When A does a incRestorePointer, it automatically
clears out the objects that B has registered from the incubator's set of
objects as well; the incubator doesn't know about functions A & B, so as
far as it is concerned, all of the registered objects were registered from
the same function.

[Implementation note: Macros are only used here for speed, since this is
used in relatively busy code and function call overhead would have
measurable impact on the system's performance.  Three global variables are
used instead of one global struct for similar reasons.]

***********************************************************************/


#define incAddOOP(oop) \
  if (incOOPPtr >= incOOPEndPtr) { \
    incGrowRegistry(); \
  } \
  *incOOPPtr++ = (oop)

#define incSavePointer() \
  (incOOPPtr - incOOPBasePtr)

#define incRestorePointer(ptr) \
  incOOPPtr = (ptr) + incOOPBasePtr;


#ifdef INLINE_MACROS

#define maybeMoveOOP	maybeMoveOOPMac
#define clearGCFlipFlags clearGCFlipFlagsMac
#define oopAt		oopAtMac
#define oopAvailable	oopAvailableMac
#define oopIndex	oopIndexMac
#define prepareToStore	prepareToStoreMac

#else

extern void		maybeMoveOOP(), clearGCFlipFlags(), prepareToStore();
extern OOP		oopAt();
extern mst_Boolean	oopAvailable();
extern long		oopIndex();

#endif /* INLINE_MACROS */



typedef unsigned long	IncPtr;



typedef struct CharObjectStruct {
  OBJ_HEADER;
#ifdef WORDS_BIGENDIAN
  Byte		charVal;
  Byte		dummy[3];	/* filler */
#else
  Byte		dummy[3];	/* filler */
  Byte		charVal;	/* probably not necessary to care about
				   ordering here */
#endif
} CharObject;

struct NilObjectStruct {
  OBJ_HEADER;
};

struct BooleanObjectStruct {
  OBJ_HEADER;
  OOP		booleanValue;
};

extern CharObject		charObjectTable[];
extern struct NilObjectStruct 	nilObject;
extern struct BooleanObjectStruct booleanObjects[];
#ifdef pre_sc_gc /* Sat Jul 27 22:31:18 1991 */
/**/extern OOP			freeOOPs;
#endif /* pre_sc_gc Sat Jul 27 22:31:18 1991 */
extern int			numFreeOOPs;
/* XXX extern unsigned long		toSpace, fromSpace, maxSpaceSize; */
extern unsigned long		maxSpaceSize;
extern mst_Boolean		gcFlipped, gcState, gcMessage;
extern int			gcFlipCounter;

extern OOP			*incOOPBasePtr, *incOOPPtr, *incOOPEndPtr;

extern double			growThresholdPercent, spaceGrowRate;

extern OOP			allocOOP(), charOOPAt(), findAnInstance();
extern void			initOOP(), setOOPAt(), swapObjects(), 
				fixupMetaclassObjects(), moveOOP(), gcOn(),
				setGCState(), gcFlip(), 
				setSpaceInfo(), growBothSpaces(),
  				allocOOPTable(), initMem(), initOOPTable(),
				markAnOOP(), markOOPRange(), printObject(),
				initCharTable(), initNil(), initBooleans(),
				setOOPObject(), debug(),
				incInitRegistry(), incGrowRegistry();
extern Byte			charOOPValue();
extern mst_Object		allocObj(), curSpaceAddr();
extern mst_Boolean		oopIndexValid(), oopValid(), gcOff(), growTo(),
				growMemoryTo();

extern struct OOPStruct		*oopTable;

#endif /* __GSTOOP__ */

These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.