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

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

/***********************************************************************
 *
 *	Byte Code interpreter declarations.
 *
 *	$Revision: 1.3 $
 *	$Date: 1995/07/18 06:25:59 $
 *	$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	     23 Jun 95	  Switched to GST header guard prefix.
 *
 * sbb	     30 May 95	  Boolean => mst_Boolean.
 *
 * sbb	     20 Jan 95	  Added padding for 64bit architectures.
 *
 * sbb	     16 Oct 93	  Changed to have 9 priority levels, as part of the fix
 *			  for ProcessorScheduler>>yield.
 *
 * sbb	     10 Oct 93	  Fixed definition of initProcessSystem.
 *
 * sbb	     24 Nov 91	  Context size increased to 64 (still not enough), to
 *			  prevent inadvertent stomping of memory past the end
 *			  of the stack.
 *
 * sbb	     14 Sep 91	  Increased number of literals to 256, number of
 *			  temporaries to 64, and number of allowable primitives
 *			  to 1024 (overkill?)
 *
 * sbyrne     7 Jan 89	  Created.
 *
 */


#ifndef __GSTINTERP__
#define __GSTINTERP__

#define CONTEXT_STACK_SIZE		64 /* words/OOPS in a context */
#define NUM_PRIORITIES			9

/* These next three defines are the number of bits in a method header for
   the number of literals, the number of temporaries, and the number of
   arguments that the method takes.  If the representation is changed, these
   definitions need to be altered too */
#define NUM_LITERALS_BITS		6  /* byte codes limit this */
#define NUM_TEMPS_BITS			6
#define NUM_ARGS_BITS			5
#define NUM_PRIM_BITS			10

#define MAX_NUM_LITERALS		((1 << NUM_LITERALS_BITS) - 1)
#define MAX_NUM_TEMPS			((1 << NUM_TEMPS_BITS) - 1)
#define MAX_NUM_ARGS			((1 << NUM_ARGS_BITS) - 1)

/*
This is the organization of a method header.  The 1 bit in the high end of
the word indicates that this is an integer, so that the GC won't be tempted
to try to scan the contents of this field, and so we can do bitwise operations
on this value to extract component pieces.

### no longer valid 
!!! make sure this is up to date -- think about what wants to be cheap to
    access and make that thing byte aligned.

   3                   2                   1 
 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|.|.| prim index        | #temps    | #literals |flg| #args   |1|  new
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|1|.|.|.|.|.|flg| prim index    | #args   | #temps  | #literals |  old
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+

each of args temps literals and flags could have another bit

literals 6 0..5
temporarycount 5 6..10
args 5 11..15
largeContext?
primitiveIndex 8 16..23
flags 2 24-25
flags 0 -- use arguments as they are, ignore prim index
flags 1 -- return self
flags 2 -- return instance variable
flags 3 -- call the primitive indexed by primIndex
*/

typedef struct MethodHeaderStruct {
#ifdef WORDS_BIGENDIAN
#ifdef LONG_PAD_BIT_FIELDS
  unsigned	dummy			: 32; /* unused */
#endif
  unsigned				: 2; /* unused */
  unsigned	primitiveIndex		: NUM_PRIM_BITS; /* index of primitve, or 0 */
  unsigned	numTemps		: NUM_TEMPS_BITS;
  unsigned	numLiterals		: NUM_LITERALS_BITS;
  unsigned	headerFlag		: 2; /* numargs, prim self, etc. */
  unsigned	numArgs			: NUM_ARGS_BITS;
  unsigned	intMark			: 1; /* flag this as an Int */
#else
  unsigned	intMark			: 1; /* flag this as an Int */
  unsigned	numArgs			: NUM_ARGS_BITS;
  unsigned	headerFlag		: 2; /* numargs, prim self, etc. */
  unsigned	numLiterals		: NUM_LITERALS_BITS;
  unsigned	numTemps		: NUM_TEMPS_BITS;
  unsigned	primitiveIndex		: NUM_PRIM_BITS; /* index of primitve, or 0 */
  unsigned				: 2; /* unused */
#ifdef LONG_PAD_BIT_FIELDS
  unsigned	dummy			: 32; /* unused */
#endif
#endif /* WORDS_BIGENDIAN */
} MethodHeader;

extern long			byteCodeCounter;
extern mst_Boolean		executionTracing;
extern mst_Boolean		makeCoreFile;
extern mst_Boolean		nonInteractive;


extern OOP			methodLiteralExt(), 
				finishExecutionEnvironment();
extern void			interpret(), sendMessage(), initInterpreter(),
				prepareExecutionEnvironment(), 
				storeMethodLiteralExt(), setFileStreamFile(),
				updateMethodCache(), initSignals(),
				storeMethodLiteralNoGC(),
  				realizeMethodContexts(),
  				initProcessSystem(), restoreObjectPointers(),
				markProcessorRegisters();
extern mst_Boolean		equal();
extern long			hash();
extern MethodHeader		getMethodHeaderExt();

#endif /* __GSTINTERP__ */

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