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

This is save.c in view mode; [Download] [Up]

/***********************************************************************
 *
 *	Binary image save/restore.
 *
 *	$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	     20 Aug 95	  Switched to using growMemoryTo in loadFromFile so
 *			  that if the saved image space is larger than the
 *			  normal memory space, the space is grown to fit.
 *
 * sbb	     23 Jul 95	  Removed extra stdio.h include
 *
 * sbb	     13 Jul 95	  Removed HAVE_ALLOCA_H include of alloca.h (done in
 *			  gst.h now).
 *
 * sbb	     11 Jul 95	  Added John Stanhope (jehu@vt.edu)'s changes for
 *			  Objective-C calling (Thanks John!!!)
 *
 * sbb	      9 Jul 95	  Fixed to have proper inclues and explicit function
 *			  declarations. 
 *
 * sbb	      6 Jun 95	  Switched to new file naming scheme.
 *
 * sbb	     30 May 95	  Boolean => mst_Boolean.  Object => mst_Object.
 *
 * sbb	     14 Sep 91	  Added support for edit version.
 *
 * sbyrne    17 Apr 90	  Fixing binary save to save only to the maximum used
 *			  OOP slot, instead of saving the entire OOP table.
 *			  This should improve load time and decrease disk
 *			  storage requirements.
 *
 * sbyrne    11 Feb 90	  Changed the header to record the size of the oop
 *			  table, since trying to load back into a system with a
 *			  different sized oop table loses bigtime.
 *
 * sbyrne     5 Apr 89	  modified to reflect change in classes: now their name
 *			  is a Smalltalk string; before, it was a C string that
 *			  had to be saved specially.
 *
 * sbyrne     4 Mar 89	  Created.
 *
 */


#include "gst.h"
#include "save.h"
#include "comp.h"
#include "interp.h"
#include "dict.h"
#include "sym.h"
#include "oop.h"		/* indirectly defines oopAt for sym tab prof */
#include "lib.h"
#include "lex.h"
#include "cint.h"
#include <stdio.h>

#ifndef MAXPATHLEN
#define MAXPATHLEN		1024 /* max length of a file and path */
#endif

#define fromBeginning		0 /* symbolic name for file offset modifier */

/* convert to a relative offset from start of OOP table.  The offset is 0 mod
 * pointer-size, so it still looks like a pointer to the isInt test.  */
#define toRelative(obj) \
  ( (OOP)((long)(obj) - (long)oopTable) )

/* convert from relative offset to actual oop table address */
#define fromRelative(obj) \
  ( (OOP)((long)(obj) + (long)oopTable) )

#ifdef not_used 
/* round "x" up to the next 4 byte boundary */
#define roundUpWord(x) \
  ( ((x) + 3) & ~3 )
#endif

/*
 * The binary image file has the following format:
 *
 *	header
 *	complete oop table
 *	global oop variable data
 *	objects and non-oop object data
 *	char object data
 *	nil object
 *	boolean objects
 */


typedef struct SaveFileHeaderStruct {
  long		version;	/* the Smalltalk version that made this dump */
  unsigned long	objectDataSize;	/* size of object data section in bytes */
  unsigned long	oopTableSize;	/* size of the oop table at dump */
  unsigned long	semiSpaceSize;	/* size of the semi spaces at dump time */
} SaveFileHeader;

typedef struct OOPVectorStruct {
  mst_Object	base;		/* base of the storage */
  mst_Object	ptr;		/* the current object */
} OOPVector;


OOP		*globalOOPs[] = {
  &andColonSymbol,
  &atColonPutColonSymbol,
  &atColonSymbol,
  &atEndSymbol,
  &bitAndColonSymbol,
  &bitOrColonSymbol,
  &bitShiftColonSymbol,
  &blockCopyColonSymbol,
  &classSymbol,
  &divideSymbol,
  &doColonSymbol,
  &equalSymbol,
  &greaterEqualSymbol,
  &greaterThanSymbol,
  &ifFalseColonIfTrueColonSymbol,
  &ifFalseColonSymbol,
  &ifTrueColonIfFalseColonSymbol,
  &ifTrueColonSymbol,
  &integerDivideSymbol,
  &lessEqualSymbol,
  &lessThanSymbol,
  &minusSymbol,
  &newColonSymbol,
  &newSymbol,
  &nextPutColonSymbol,
  &nextSymbol,
  &notEqualSymbol,
  &notSameObjectSymbol,
  &orColonSymbol,
  &plusSymbol,
  &remainderSymbol,
  &sameObjectSymbol,
  &sizeSymbol,
  &thisContextSymbol,
  &timesSymbol,
  &valueColonSymbol,
  &valueColonValueColonSymbol,
  &valueColonValueColonValueColonSymbol,
  &valueWithArgumentsColonSymbol,
  &valueSymbol,
  &whileFalseColonSymbol,
  &whileTrueColonSymbol,
  &orSymbol,
  &andSymbol,
  &superSymbol,
  &nilSymbol,
  &trueSymbol,
  &falseSymbol,
  &selfSymbol,
  &doesNotUnderstandColonSymbol,
  &unknownSymbol,
  &charSymbol,
  &stringSymbol,
  &stringOutSymbol, 
  &symbolSymbol,
  &intSymbol,
  &longSymbol,
  &floatSymbol,
  &doubleSymbol,
  &voidSymbol,
  &variadicSymbol,
  &cObjectSymbol,
  &smalltalkSymbol,
  &byteArraySymbol,
  &byteArrayOutSymbol,
  &mst_objectClass,
  &magnitudeClass,
  &charClass,
  &timeClass,
  &numberClass,
  &floatClass,
  &integerClass,
  &lookupKeyClass,
  &associationClass,
  &linkClass,
  &processClass,
  &symLinkClass,
  &collectionClass,
  &sequenceableCollectionClass,
  &linkedListClass,
  &semaphoreClass,
  &arrayedCollectionClass,
  &arrayClass,
  &stringClass,
  &symbolClass,
  &byteArrayClass,
  &compiledMethodClass,
  &intervalClass,
  &orderedCollectionClass,
  &sortedCollectionClass,
  &bagClass,
  &mappedCollectionClass,
  &setClass,
  &dictionaryClass,
  &identityDictionaryClass,
  &systemDictionaryClass,
  &undefinedObjectClass,
  &booleanClass,
  &falseClass,
  &trueClass,
  &processorSchedulerClass,
  &delayClass,
  &sharedQueueClass,
  &behaviorClass,
  &classDescriptionClass,
  &classClass,
  &metaclassClass,
  &smalltalkDictionary,
  &messageClass,
  &methodContextClass,
  &blockContextClass,
  &streamClass,
  &positionableStreamClass,
  &readStreamClass,
  &writeStreamClass,
  &readWriteStreamClass,
  &cObjectClass,
  &cTypeClass,
  &fileStreamClass,
  &memoryClass,
  &byteMemoryClass,
  &wordMemoryClass,
  &randomClass,
  &cFuncDescriptorClass,
  &tokenStreamClass,
  &methodInfoClass,
  &fileSegmentClass,
  &nilOOP,
  &trueOOP,
  &falseOOP,
  &processorOOP,
  &symbolTable,
  nil
};


static void	skipOverHeader(), saveObject(), fixupObject(),
		fixupMethodObject(), restoreObject(), restoreMethodObject(),
		saveOOPTable(), fixupAllOOPs(), fixupOOP(),
		restoreAllOOPs(), restoreOOP(), 
		loadOOPTable(), loadNormalOOPs(),
		loadCharOOPs(), loadSpecialOOPs(), saveGlobalOOPs(),
		loadGlobalOOPs(), restoreInstanceVars(),
		saveFileVersion(),
		loadFileVersion(), fixupInstanceVars(), fixupOOPInstanceVars(),
		skipToHeader();

static int	saveAllObjects();


/* This variable contains the OOP slot index of the highest non-free OOP,
 * excluding the built-in ones (i.e., it will always be < OOP_TABLE_SIZE).
 * This is used for optimizing the size of the saved image, and minimizing
 * the load time when restoring the system. */
static int	maxUsedOOPSlot = 0;


mst_Boolean saveToFile(fileName)
char	*fileName;
{
  FILE		*imageFile;
  unsigned long	objectDataSize;
  mst_Boolean	oldGCState;

  realizeMethodContexts();	/* make sure all contexts are real */

  gcFlip();			/* make sure that the world is compact if
				 * possible */
  oldGCState = gcOff();

#ifdef BINARY_MODE_NEEDED
  imageFile = fopen(fileName, "wb");
#else
  imageFile = fopen(fileName, "w");
#endif
  if (imageFile == NULL) {
    errorf("Couldn't open file %s", fileName);
    return (false);
  }

  skipOverHeader(imageFile);
  saveOOPTable(imageFile);

#ifdef OOP_TABLE_TRACE
printf("After saving oopt table: %d\n", ftell(imageFile));
#endif /* OOP_TABLE_TRACE */

  saveGlobalOOPs(imageFile);

#ifdef OOP_TABLE_TRACE
printf("After global oop table: %d\n", ftell(imageFile));
#endif /* OOP_TABLE_TRACE */

  objectDataSize = saveAllObjects(imageFile);

#ifdef OOP_TABLE_TRACE
printf("After saving all objects table: %d\n", ftell(imageFile));
#endif /* OOP_TABLE_TRACE */

  skipToHeader(imageFile);
  saveFileVersion(imageFile, objectDataSize);

  fclose(imageFile);

  setGCState(oldGCState);
  return (true);
} 


static void skipOverHeader(imageFile)
FILE	*imageFile;
{
  fseek(imageFile, sizeof(SaveFileHeader), fromBeginning);
}

/*
 *	static void saveOOPTable(imageFile)
 *
 * Description
 *
 *	Writes the OOP table out to the image file.  We need to make all
 *	of the object pointers relative, including free OOP table slots, and
 *	we use a parallel vector containing file offsets for the objects that
 *	we developed during saving of the objects themselves as the fixup
 *	table.
 *
 * Inputs
 *
 *	imageFile: 
 *		A stdio FILE to be written to.  It must be positioned
 *		correctly before this routine is called.
 *
 */
static void saveOOPTable(imageFile)
FILE	*imageFile;
{
  fixupAllOOPs();

#ifdef OOP_TABLE_TRACE
printf("there are %d free oops out of %d oops, leaving %d\n",
       numFreeOOPs, OOP_TABLE_SIZE, OOP_TABLE_SIZE - numFreeOOPs);
printf("max used is %d\n", maxUsedOOPSlot);
#endif /* OOP_TABLE_TRACE */

  /* save up to the max oop slot in use */
  fwrite(oopTable, sizeof(struct OOPStruct), maxUsedOOPSlot + 1, imageFile);

  /* then save the constant ones at the end */
  fwrite(&oopTable[OOP_TABLE_SIZE], sizeof(struct OOPStruct),
	 TOTAL_OOP_TABLE_SLOTS - OOP_TABLE_SIZE, imageFile);

  restoreAllOOPs();
}


static void fixupAllOOPs()
{
  int		i;

  maxUsedOOPSlot = 0;

  for (i = 0; i < TOTAL_OOP_TABLE_SLOTS; i++) {
    fixupOOP(i);
  }
}

static void fixupOOP(i)
int	i;
{
  OOP		oop;

  oop = oopAt(i);
  if (!(oop->flags & F_FREE)) {
    if (i < OOP_TABLE_SIZE) {
      maxUsedOOPSlot = i;
    }
    oop->object = (mst_Object)toRelative(oop->object);
  }
}



static void restoreAllOOPs()
{
  int		i;

  for (i = 0; i < TOTAL_OOP_TABLE_SLOTS; i++) {
    restoreOOP(i);
  }
}



static void restoreOOP(i)
int	i;
{
  OOP		oop;

  oop = oopAt(i);
  if (!(oop->flags & F_FREE)) {
    oop->object = (mst_Object)fromRelative(oop->object);
  }
}


static void saveGlobalOOPs(imageFile)
FILE	*imageFile;
{
  OOP		**oopPtr, oop;

  for (oopPtr = globalOOPs; *oopPtr; oopPtr++) {
    oop = toRelative(**oopPtr);
    fwrite(&oop, sizeof(OOP), 1, imageFile);
  }
}


static int saveAllObjects(imageFile)
FILE	*imageFile;
{
  long		objectStart, objectEnd;
  int		i;
  OOP		oop;

  objectStart = ftell(imageFile);
  for (i = 0; i < OOP_TABLE_SIZE; i++) {
    oop = oopAt(i);
    if (!(oop->flags & F_FREE)) {
#ifdef pre_sc_gc /* Sun Jul 28 13:31:33 1991 */
/**/    if (oopValid(oop)) {
#endif /* pre_sc_gc Sun Jul 28 13:31:33 1991 */
      saveObject(imageFile, oop);
    }
  }

  objectEnd = ftell(imageFile);

  /* dump out the character objects, nil, true, and false */
  for (i = OOP_TABLE_SIZE; i < TOTAL_OOP_TABLE_SLOTS; i++) {
    saveObject(imageFile, oopAt(i));
  }

  return (objectEnd - objectStart);
}

static void saveObject(imageFile, oop)
FILE	*imageFile;
OOP	oop;
{
  mst_Object	object;
  int		numFixed, numIndexed;
  mst_Boolean	hasPointers;

  object = oopToObj(oop);
  hasPointers = isPointers(oop);
  numFixed = oopFixedFields(oop);
  numIndexed = numIndexableFields(oop);

  fixupObject(oop, hasPointers, numFixed, numIndexed);
  fwrite(object, sizeof(OOP), object->objSize, imageFile);
  restoreObject(oop, hasPointers, numFixed, numIndexed);
}

static void fixupObject(oop, hasPointers, numFixed, numIndexed)
OOP	oop;
mst_Boolean	hasPointers;
int	numFixed, numIndexed;
{
  int		i;
  mst_Object	object;
  OOP		instOOP, classOOP;

  classOOP = oopClass(oop);

  if (classOOP == compiledMethodClass) {
    fixupMethodObject(oop);
  } else {
    if (hasPointers) {
      for (i = 1; i <= numFixed + numIndexed; i++) {
	instOOP = instVarAt(oop, i);
	if (!isInt(instOOP)) {
	  instVarAtPut(oop, i, toRelative(instOOP));
	}
      }
    }
  }

  object = oopToObj(oop);
  object->objClass = toRelative(object->objClass);
}

static void fixupMethodObject(oop)
OOP	oop;
{
  MethodHeader	header;
  unsigned	i;
  OOP		literalOOP, descriptorOOP;

  descriptorOOP = getMethodDescriptor(oop);
  if (!isInt(descriptorOOP)) {
    setMethodDescriptor(oop, toRelative(descriptorOOP));
  }
  header = getMethodHeaderExt(oop);
  if (header.headerFlag == 1 || header.headerFlag == 2) {
    /* these have no method literals to fix up, so we ignore them */
    return;
  }

  for (i = 0; i < header.numLiterals; i++) {
    literalOOP = methodLiteralExt(oop, i);
    if (!isInt(literalOOP)) {
      storeMethodLiteralNoGC(oop, i, toRelative(literalOOP));
    }
  }
}

static void restoreObject(oop, hasPointers, numFixed, numIndexed)
OOP	oop;
mst_Boolean	hasPointers;
int	numFixed, numIndexed;
{
  mst_Object	object;

  object = oopToObj(oop);

  object->objClass = fromRelative(object->objClass);

  restoreInstanceVars(oop, hasPointers, numFixed, numIndexed);
}

static void restoreInstanceVars(oop, hasPointers, numFixed, numIndexed)
OOP	oop;
mst_Boolean	hasPointers;
int	numFixed, numIndexed;
{
  register int	i;
  OOP		instOOP, classOOP;

  classOOP = oopClass(oop);
  if (classOOP == compiledMethodClass) {
    restoreMethodObject(oop);
  } else {
    if (hasPointers) {
      for (i = 1; i <= numFixed + numIndexed; i++) {
	instOOP = instVarAt(oop, i);
	if (!isInt(instOOP)) {
	  instVarAtPut(oop, i, fromRelative(instOOP));
	}
      }
      if (classOOP == cFuncDescriptorClass) {
	restoreCFuncDescriptor(oop); /* in mstcint.c */
      }
    }
  }
}

static void restoreMethodObject(oop)
OOP	oop;
{
  MethodHeader	header;
  unsigned	i;
  OOP		literalOOP, descriptorOOP;

  descriptorOOP = getMethodDescriptor(oop);
  if (!isInt(descriptorOOP)) {
    setMethodDescriptor(oop, fromRelative(descriptorOOP));
  }

  header = getMethodHeaderExt(oop);
  if (header.headerFlag == 1 || header.headerFlag == 2) {
    /* these have no method literals to fix up, so we ignore them */
    return;
  }

  /* Fix up oop's method literals in place */
  for (i = 0; i < header.numLiterals; i++) {
    literalOOP = methodLiteralExt(oop, i);
    if (!isInt(literalOOP)) {
      storeMethodLiteralNoGC(oop, i, fromRelative(literalOOP));
    }
  }
}


static void skipToHeader(imageFile)
FILE	*imageFile;
{
  rewind(imageFile);
}

static void saveFileVersion(imageFile, objectDataSize)
FILE	*imageFile;
unsigned long objectDataSize;
{
  SaveFileHeader header;

  header.version = ST_MAJOR_VERSION * 1000000 + ST_MINOR_VERSION * 1000
    + ST_EDIT_VERSION;
  header.objectDataSize = objectDataSize;
  header.oopTableSize = maxUsedOOPSlot + 1; /* n slots, numbered 0..n-1 */
  header.semiSpaceSize = maxSpaceSize;

  fwrite(&header, sizeof(SaveFileHeader), 1, imageFile);
}

#ifdef appears_unused /* Sun Jul  9 00:30:31 1995 */
/**/static void skipToOOPTable(imageFile)
/**/FILE	*imageFile;
/**/{
/**/  rewind(imageFile);
/**/}
#endif /* appears_unused Sun Jul  9 00:30:31 1995 */


/***********************************************************************
 *
 *	Binary loading routines.
 *
 ***********************************************************************/


mst_Boolean loadFromFile(fileName)
char	*fileName;
{
  FILE		*imageFile;
  SaveFileHeader header;
  OOPVector	ov;
  mst_Boolean	oldGCState;
  char		fullImageName[MAXPATHLEN];

  oldGCState = gcOff();

  findImageFile(fileName, fullImageName);
#ifdef BINARY_MODE_NEEDED
  imageFile = fopen(fullImageName, "rb");
#else
  imageFile = fopen(fullImageName, "r");
#endif
  if (imageFile == NULL) {
    fclose(imageFile);
    setGCState(oldGCState);
    return (false);
  }

  loadFileVersion(imageFile, &header);
  if (header.version != (ST_MAJOR_VERSION * 1000000 + ST_MINOR_VERSION * 1000
			 + ST_EDIT_VERSION)) {
    /* version mismatch; this image file is invalid */
    fclose(imageFile);
    setGCState(oldGCState);
    return (false);
  }
  
  if (header.semiSpaceSize > maxSpaceSize) {
    growMemoryTo(header.semiSpaceSize);
#ifdef pre_ms_gc /* Sat Jun 24 02:18:31 1995 */
/**/    growBothSpaces(header.semiSpaceSize);
#endif /* pre_ms_gc Sat Jun 24 02:18:31 1995 */
  }

#ifdef old_code /* Tue Apr 17 22:25:33 1990 */
/**/  if (header.oopTableSize != OOP_TABLE_SIZE) {
/**/    return (false);
/**/  }
#endif /* old_code Tue Apr 17 22:25:33 1990 */

  allocOOPTable();
  loadOOPTable(imageFile, header.oopTableSize);

  loadGlobalOOPs(imageFile);

  loadNormalOOPs(imageFile, header.objectDataSize, &ov);
  loadCharOOPs(imageFile);
  loadSpecialOOPs(imageFile);

  fixupInstanceVars(&ov);

  fclose(imageFile);

  setGCState(oldGCState);

dictInit();			/* ### TEMP HACK ### */

  return (true);
}

static void loadFileVersion(imageFile, headerp)
FILE	*imageFile;
SaveFileHeader *headerp;
{
  fread(headerp, sizeof(SaveFileHeader), 1, imageFile);
}

static void loadOOPTable(imageFile, oldSlotsUsed)
FILE	*imageFile;
long 	oldSlotsUsed;
{
  long		i;
  OOP		oop;

/*  fread(oopTable, sizeof(struct OOPStruct), TOTAL_OOP_TABLE_SLOTS, imageFile);*/

  /* load in the valid OOP slots from previous dump */
  fread(oopTable, sizeof(struct OOPStruct), oldSlotsUsed, imageFile);
  
  /* mark the remaining ones as available */
  for (i = oldSlotsUsed; i < OOP_TABLE_SIZE; i++) {
    oop = oopAt(i);
    oop->flags = F_FREE;
  }


  /* read in the constant stuff at the end */
  fread(&oopTable[OOP_TABLE_SIZE], sizeof(struct OOPStruct),
	TOTAL_OOP_TABLE_SLOTS - OOP_TABLE_SIZE, imageFile);

  /* the fixup gets handled by load normal oops */
}


static void loadGlobalOOPs(imageFile)
FILE	*imageFile;
{
  OOP		**oopPtr, *oopVec;
  long		numGlobalOOPs;

  /* !!! a) this is clumsy, and b) this is incorrect -- if the number of
   * global oops changes, I think we're hosed, and this code does nothing
   * to detect or prevent this from happening. */
  for (numGlobalOOPs = 0, oopPtr = globalOOPs; *oopPtr;
       oopPtr++, numGlobalOOPs++);

  oopVec = (OOP *)alloca(numGlobalOOPs * sizeof(OOP));
  fread(oopVec, sizeof(OOP), numGlobalOOPs, imageFile);

  for (oopPtr = globalOOPs; *oopPtr; oopPtr++, oopVec++) {
    **oopPtr = fromRelative(*oopVec);
  }
#ifdef old_code /* Wed Apr 26 21:15:38 1989 */ /* <<<== what dedication...3 days before my wedding -- SBB */
/**/  /* ??? this could be sped up by using alloca, doing one fread, and then
/**/     iterating through the array */
/**/  for (oopPtr = globalOOPs; *oopPtr; oopPtr++) {
/**/    fread(&oop, sizeof(OOP), 1, imageFile);
/**/    **oopPtr = fromRelative(oop);
/**/  }
#endif /* old_code Wed Apr 26 21:15:38 1989 */
}

static void loadNormalOOPs(imageFile, objectDataSize, ovp) 
FILE	*imageFile;
unsigned long objectDataSize;
OOPVector *ovp;
{
  register long	i;
  OOP		oop, prevFreeOOP;
  mst_Object	object, objPtr;

  objPtr = curSpaceAddr();

  ovp->base = objPtr;

  prevFreeOOP = nil;

  fread(objPtr, 1, objectDataSize, imageFile);

#ifdef pre_sc_gc /* Sat Jul 27 22:32:54 1991 */
/**/  freeOOPs = nil;
#endif /* pre_sc_gc Sat Jul 27 22:32:54 1991 */
  numFreeOOPs = 0;
  for (i = 0; i < OOP_TABLE_SIZE; i++) {
    oop = oopAt(i);
    if (!(oop->flags & F_FREE)) {
#ifdef pre_sc_gc /* Sun Jul 28 13:34:39 1991 */
/**/    if (oopValid(oop)) {
#endif /* pre_sc_gc Sun Jul 28 13:34:39 1991 */
      object = objPtr;
      oop->object = object;
#ifdef pre_sc_gc /* Sun Jun 18 15:27:50 1995 */
/**/      /* ### should probably make this setting symbolic/abstracted */
/**/      oop->flags &= ~(F_SPACE|F_EVEN|F_ODD);
/**/      oop->flags |= toSpace;
/**/      if (toSpace) {
/**/	oop->flags |= F_ODD;
/**/      } else {
/**/	oop->flags |= F_EVEN;
/**/      }
#endif /* pre_sc_gc Sun Jun 18 15:27:50 1995 */
      object->objClass = fromRelative(object->objClass);
      objPtr = (mst_Object)((long *)object + object->objSize);
    } else if (oop->flags & F_FREE) {
      /* ignore non-free but non-valid...they'll get handled
       * naturally in due time. */
      numFreeOOPs++;
      oop->flags = F_FREE;	/* just free */
#ifdef pre_sc_gc /* Sat Jul 27 22:00:04 1991 */
/**/      if (prevFreeOOP) {	/* forward chain the oop free list */
/**/	prevFreeOOP->object = (Object)oop;
/**/      }
/**/      if (freeOOPs == nil) {	/* free list points at first free oop in
/**/				   OOP table */
/**/	freeOOPs = oop;
/**/      }
/**/      prevFreeOOP = oop;
#endif /* pre_sc_gc Sat Jul 27 22:00:04 1991 */
    }
  }

#ifdef pre_sc_gc /* Sat Jul 27 22:00:13 1991 */
/**/  if (prevFreeOOP) {
/**/    prevFreeOOP->object = nil;	/* terminate the free list nicely */
/**/  }
#endif /* pre_sc_gc Sat Jul 27 22:00:13 1991 */

  setSpaceInfo(objectDataSize);
  ovp->ptr = objPtr;
}

static void loadCharOOPs(imageFile)
FILE	*imageFile;
{
  int		i;

  fread(charObjectTable, sizeof(CharObject), NUM_CHAR_OBJECTS, imageFile);

/* ### Inconsistency here... using direct refs to oopTable, instead of oopAts
 * like above.  Probably should convert the whole thing to pointers into
 * the oopTable and be done with it.
 */
  for (i = 0; i < NUM_CHAR_OBJECTS; i++) {
    oopTable[i + CHAR_OBJECT_BASE].object = (mst_Object)&charObjectTable[i];
#ifdef pre_sc_gc /* Sun Jun 18 15:28:14 1995 */
/**/    oopTable[i + CHAR_OBJECT_BASE].flags &= ~F_SPACE;
/**/    oopTable[i + CHAR_OBJECT_BASE].flags |= toSpace;
#endif /* pre_sc_gc Sun Jun 18 15:28:14 1995 */
    charObjectTable[i].objClass = fromRelative(charObjectTable[i].objClass);
  }
}

static void loadSpecialOOPs(imageFile)
FILE	*imageFile;
{
  fread(&nilObject, sizeof(struct NilObjectStruct), 1, imageFile);
  nilOOP->object = (mst_Object)&nilObject;
  nilOOP->object->objClass = fromRelative(nilOOP->object->objClass);
/* ### not sure that I can just assign directly into flags...seems ok, though*/
#ifdef pre_sc_gc /* Sun Jun 18 15:28:26 1995 */
/**/  nilOOP->flags = toSpace;
#endif /* pre_sc_gc Sun Jun 18 15:28:26 1995 */
  nilOOP->flags = 0;

  fread(booleanObjects, sizeof(struct BooleanObjectStruct), 2, imageFile);
  trueOOP->object = (mst_Object)&booleanObjects[0];
  falseOOP->object = (mst_Object)&booleanObjects[1];
  trueOOP->object->objClass = fromRelative(trueOOP->object->objClass);
  falseOOP->object->objClass = fromRelative(falseOOP->object->objClass);
/* XXX   trueOOP->flags = falseOOP->flags = toSpace; */
  trueOOP->flags = falseOOP->flags = 0;
}

static void fixupInstanceVars(ovp)
OOPVector *ovp;
{
  int		i;
  OOP		oop;

  for (i = 0; i < TOTAL_OOP_TABLE_SLOTS; i++) {
    oop = oopAt(i);
    if (oopValid(oop)) {
      fixupOOPInstanceVars(oop, ovp);
    }
  }
}

static void fixupOOPInstanceVars(oop, ovp)
OOP	oop;
OOPVector *ovp;
{
  int		numFixed, numIndexed;
  mst_Boolean	hasPointers;

  hasPointers = isPointers(oop);
  numFixed = oopFixedFields(oop);
  numIndexed = numIndexableFields(oop);
  restoreInstanceVars(oop, hasPointers, numFixed, numIndexed);
}


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