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

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

/***********************************************************************
 *
 *	Byte code array utility routines.
 *
 *	$Revision: 1.4 $
 *	$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	      9 Jul 95	  Fixed to include proper headers.
 *
 * sbb	      6 Jun 95	  Switched to new file naming scheme.
 *
 * P.Lecoanet 22 Dec 91   Fixed byteCodeLength failing to return 0
 *
 * sbyrne    20 Apr 90	  Added initByteCodes to fix a robustness issue with
 *			  the compiler.
 *
 * sbyrne    27 Dec 88	  created.
 *
 */

#include "gst.h"
#include "byte.h"
#include "lex.h"
#include "sym.h"
#include "dict.h"
#if STDC_HEADERS
#include <string.h> /* for memcpy */
#include <stdlib.h>
#endif /* STDC_HEADERS */
#include <stdio.h>

#define BYTE_CODE_CHUNK_SIZE		64

struct ByteCodeArray {
  Byte		*base;		/* base of the byte code array */
  Byte		*ptr;		/* current byte+1 of byte code array */
  int		maxLen;		/* max allocated len of byte code array
				   can be changed as byte code array grows,
				   and is used to tell when to grow the byte
				   code array. */
};

ByteCodes		currentByteCodes = nil;

static ByteCodes	allocByteCodes();
static void		compileByteCodes(), reallocByteCodes();


/* These are used to decode special send byte codes. */
static char		*mathMessageName[] = {
  "+",
  "-",
  "<",
  ">",
  "<=",
  ">=",
  "=",
  "~=",
  "*",
  "/",
  "\\",
  "@",
  "bitShift:",
  "//",
  "bitAnd:",
  "bitOr:"
};

/* These are the selectors for special case send bytecodes that the compiler 
   generates.  These are used only to print out the generated byte codes. */
static char		*specialMessageName[] = {
  "at:",
  "at:put:",
  "size",
  "next",
  "nextPut:",
  "atEnd",
  "==",
  "class",
  "blockCopy:",
  "value",
  "value:",
  "do:",
  "new",
  "new:",
  "x",
  "y"
};

void compileByte(byte)
Byte byte;
{
  if (currentByteCodes == nil) {
    currentByteCodes = allocByteCodes();
  }

  if ((currentByteCodes->ptr - currentByteCodes->base)
      >= currentByteCodes->maxLen) {
    reallocByteCodes(currentByteCodes);
  }

  *currentByteCodes->ptr++ = byte;
}

void compileAndFreeByteCodes(byteCodes)
ByteCodes byteCodes;
{
  compileByteCodes(byteCodes);
  freeByteCodes(byteCodes);
}

/*
 *	void initByteCodes()
 *
 * Description
 *
 *	Initialize the byte code system.  Basically used to set the byte code
 *	system to a known state, typically in preparation for compilation.
 *
 */
void initByteCodes()
{
  if (currentByteCodes) {
    free(currentByteCodes);	/* ??? this might lose if trashed. */
    currentByteCodes = nil;
  }
}

/*
 *	ByteCodes getByteCodes()
 *
 * Description
 *
 *	Called when byte code compilation is complete, this routine returns the
 *	set of byte codes that were compiled.  Since compilation is complete,
 *	this routine also resets the internal state of the byte code compiler
 *	in preparation for next time.
 *
 * Outputs
 *
 *	A pointer to a byte code array that contains the bytes for the current
 *	compilation.
 */
ByteCodes getByteCodes()
{
  ByteCodes	curByteCodes;

  curByteCodes = currentByteCodes;
  currentByteCodes = nil;

  return (curByteCodes);
}


/*
 *	ByteCodes saveByteCodeArray()
 *
 * Description
 *
 *	Called to save the set of byte codes currently being compiled and
 *	prepare for a new compilation of byte codes.  The current set of byte
 *	codes being compiled is returned for the caller to keep and to later
 *	use in a restoreByteCodeArray call.
 *
 * Outputs
 *
 *	A byte code array pointer to the current byte codes.
 */
ByteCodes saveByteCodeArray()
{
  ByteCodes	curByteCodes;

  curByteCodes = currentByteCodes;
  currentByteCodes = nil;

  return (curByteCodes);
}


/*
 *	void restoreByteCodeArray(byteCodes)
 *
 * Description
 *
 *	Restores the internal state of the byte code compiler so that it can
 *	continue compiling byte codes into the byte code array "byteCodes",
 *	which should have been returned at some previous point from
 *	saveByteCodeArray().
 *
 * Inputs
 *
 *	byteCodes: 
 *		The byte code array pointer to be restored.  Should have come
 *		from a saveByteCodeArray call.
 *
 */
void restoreByteCodeArray(byteCodes)
ByteCodes byteCodes;
{
  currentByteCodes = byteCodes;
}

int byteCodeLength(byteCodes)
ByteCodes byteCodes;
{
  if (byteCodes == nil) {
    return (0);
  }
  return (byteCodes->ptr - byteCodes->base);
}


/*
 *	int currentByteCodeLength()
 *
 * Description
 *
 *	Return the current number of byte codes that have been compiled.
 *
 * Outputs
 *
 *	Number of byte codes present in the current byte code array right now.
 */
int currentByteCodeLength()
{
  if (currentByteCodes == nil) {
    return (0);
  }

  return (currentByteCodes->ptr - currentByteCodes->base);
}

int isSimpleReturn(byteCodes)
ByteCodes byteCodes;
{
  Byte		*bytes;
  long		byteCodeLen;

  if (byteCodes == nil) {
    return (0);
  }

  byteCodeLen = byteCodeLength(byteCodes);
  bytes = byteCodes->base;

  /* check for ^self */
  if (byteCodeLen == 1 && bytes[0] == (returnIndexed | receiverIndex)) {
    return (1);
  }

  /* check for ^instanceVariable */
  if (byteCodeLen == 2) {
    if ((bytes[0] & ~0x0F) == pushReceiverVariable
	&& bytes[1] == returnMethodStackTop) {
      return (((bytes[0] & 0x0F) << 8) | 2);
    }
  } else if (byteCodeLen == 3) {
    if (bytes[0] == pushIndexed
	 && (bytes[1] & locationMask) == receiverLocation
	 && bytes[2] == returnMethodStackTop) {
      return (((bytes[1] & ~locationMask) << 8) | 2);
    }
  }

  return (0);
}

void copyByteCodes(dest, byteCodes)
Byte	*dest;
ByteCodes byteCodes;
{
  memcpy(dest, byteCodes->base, byteCodeLength(byteCodes));
}

/***********************************************************************
 *
 *	Internal routines.
 *
 ***********************************************************************/

static void compileByteCodes(byteCodes)
register ByteCodes byteCodes;
{
  register Byte		*ptr;

  for (ptr = byteCodes->base; ptr < byteCodes->ptr; ptr++) {
    compileByte(*ptr);
  }
}

static ByteCodes allocByteCodes()
{
  ByteCodes	newByteCodes;

  newByteCodes = (ByteCodes)malloc(sizeof(struct ByteCodeArray));
  newByteCodes->base = (Byte *)malloc(BYTE_CODE_CHUNK_SIZE);
  newByteCodes->ptr = newByteCodes->base;
  newByteCodes->maxLen = BYTE_CODE_CHUNK_SIZE;

  return (newByteCodes);
}

static void reallocByteCodes(byteCodes)
ByteCodes byteCodes;
{
  Byte		*newBytes;
  int		newLen;

  if (byteCodes->maxLen != (byteCodes->ptr - byteCodes->base)) {
    errorf("reallocByteCodes called with maxLen != byteCode len");
  }

  newLen = byteCodes->maxLen + BYTE_CODE_CHUNK_SIZE;
  newBytes = (Byte *)malloc(newLen);
  memcpy(newBytes, byteCodes->base, byteCodes->maxLen);
  free(byteCodes->base);

  byteCodes->base = newBytes;
  byteCodes->ptr = newBytes + byteCodes->maxLen;
  byteCodes->maxLen = newLen;
}

void freeByteCodes(byteCodes)
ByteCodes byteCodes;
{
  if (byteCodes != nil) {
    free(byteCodes->base);
    free(byteCodes);
  }
}

void printByteCodes(byteCodes, literalVec)
ByteCodes byteCodes;
OOP	literalVec[];
{
  Byte		*b;
  int		ip;

  if (byteCodes == nil) {
    return;
  }

  for (b = byteCodes->base; b < byteCodes->ptr; b++) {
    ip = b - byteCodes->base;
    printf("%5d:\t", ip);
    printByteCodeName(b, ip, literalVec);
    printf("\n");
    switch (*b) {
    case  0: case  1: case  2: case  3:
    case  4: case  5: case  6: case  7:
    case  8: case  9: case 10: case 11:
    case 12: case 13: case 14: case 15:
      break;

    case 16: case 17: case 18: case 19:
    case 20: case 21: case 22: case 23:
    case 24: case 25: case 26: case 27:
    case 28: case 29: case 30: case 31:
      break;

    case 32: case 33: case 34: case 35:
    case 36: case 37: case 38: case 39:
    case 40: case 41: case 42: case 43:
    case 44: case 45: case 46: case 47:
    case 48: case 49: case 50: case 51:
    case 52: case 53: case 54: case 55:
    case 56: case 57: case 58: case 59:
    case 60: case 61: case 62: case 63:
      break;

    case 64: case 65: case 66: case 67:
    case 68: case 69: case 70: case 71:
    case 72: case 73: case 74: case 75:
    case 76: case 77: case 78: case 79:
    case 80: case 81: case 82: case 83:
    case 84: case 85: case 86: case 87:
    case 88: case 89: case 90: case 91:
    case 92: case 93: case 94: case 95:
      break;

    case  96: case  97: case  98: case  99:
    case 100: case 101: case 102: case 103:
      break;

    case 104: case 105: case 106: case 107:
    case 108: case 109: case 110: case 111:
      break;

    case 112:
      break;

    case 113: 
      break;

    case 114:
      break;

    case 115:
      break;

    case 116:
      break;

    case 117:
      break;

    case 118:
      break;

    case 119:
      break;

    case 120:
      break;
      
    case 121:
      break;

    case 122:
      break;

    case 123:
      break;
      
    case 124:
      break;

    case 125:
      break;

    case 126: case 127:
      break;

    case 128:
      b++;
      break;

    case 129:
      b++;
      break;

    case 130:
      b++;
      break;

    case 131:
      b++;
      break;

    case 132:
      b += 2;
      break;

    case 133:
      b++;
      break;

    case 134:
      b += 2;
      break;

    case 135:
      break;

    case 136:
      break;

    case 137:
      break;

    case 138: case 139: case 140: case 141: 
    case 142: case 143:
      break;

    case 144: case 145: case 146: case 147:
    case 148: case 149: case 150: case 151:
      break;

    case 152: case 153: case 154: case 155:
    case 156: case 157: case 158: case 159:
      break;

    case 160: case 161: case 162: case 163:
    case 164: case 165: case 166: case 167:
      b++;
      break;

    case 168: case 169: case 170: case 171:
      b++;
      break;

    case 172: case 173: case 174: case 175:
      b++;
      break;

    case 176: case 177: case 178: case 179: 
    case 180: case 181: case 182: case 183: 
    case 184: case 185: case 186: case 187: 
    case 188: case 189: case 190: case 191: 
      break;

    case 192: case 193: case 194: case 195: 
    case 196: case 197: case 198: case 199: 
    case 200: case 201: case 202: case 203: 
    case 204: case 205: case 206: case 207: 
      break;

    case 208: case 209: case 210: case 211: 
    case 212: case 213: case 214: case 215: 
    case 216: case 217: case 218: case 219: 
    case 220: case 221: case 222: case 223: 
      break;

    case 224: case 225: case 226: case 227: 
    case 228: case 229: case 230: case 231: 
    case 232: case 233: case 234: case 235: 
    case 236: case 237: case 238: case 239: 
      break;

    case 240: case 241: case 242: case 243: 
    case 244: case 245: case 246: case 247: 
    case 248: case 249: case 250: case 251: 
    case 252: case 253: case 254: case 255: 
      break;

    default:
      break;
    }
  }
  printf("\n");
}

void printByteCodeName(bp, ip, literalVec)
Byte	bp[];
int	ip;
OOP	literalVec[];
{
  switch (bp[0]) {
  case  0: case  1: case  2: case  3:
  case  4: case  5: case  6: case  7:
  case  8: case  9: case 10: case 11:
  case 12: case 13: case 14: case 15:
    printf("push Instance Variable[%d]", bp[0] & 15);
    break;

  case 16: case 17: case 18: case 19:
  case 20: case 21: case 22: case 23:
  case 24: case 25: case 26: case 27:
  case 28: case 29: case 30: case 31:
    printf("push Temporary[%d]", bp[0] & 15);
    break;
    
  case 32: case 33: case 34: case 35:
  case 36: case 37: case 38: case 39:
  case 40: case 41: case 42: case 43:
  case 44: case 45: case 46: case 47:
  case 48: case 49: case 50: case 51:
  case 52: case 53: case 54: case 55:
  case 56: case 57: case 58: case 59:
  case 60: case 61: case 62: case 63:
    printf("push Literal[%d]", bp[0] & 31);
    break;
    
  case 64: case 65: case 66: case 67:
  case 68: case 69: case 70: case 71:
  case 72: case 73: case 74: case 75:
  case 76: case 77: case 78: case 79:
  case 80: case 81: case 82: case 83:
  case 84: case 85: case 86: case 87:
  case 88: case 89: case 90: case 91:
  case 92: case 93: case 94: case 95:
    printf("push Global Variable[%d] = ", bp[0] & 31);
    printAssociationKey(literalVec[bp[0] & 31]);
    break;
    
  case  96: case  97: case  98: case  99:
  case 100: case 101: case 102: case 103:
    printf("pop and store Instance Variable[%d]", bp[0] & 7);
    break;
    
  case 104: case 105: case 106: case 107:
  case 108: case 109: case 110: case 111:
    printf("pop and store Temporary[%d]", bp[0] & 7);
    break;
    
  case 112:
    printf("push self");
    break;
    
  case 113: 
    printf("push true");
    break;
    
  case 114:
    printf("push false");
    break;
    
  case 115:
    printf("push nil");
    break;
    
  case 116:
    printf("push -1");
    break;
    
  case 117:
    printf("push 0");
    break;
    
  case 118:
    printf("push 1");
    break;
    
  case 119:
    printf("push 2");
    break;
    
  case 120:
    printf("return self");
    break;
    
  case 121:
    printf("return true");
    break;
    
  case 122:
    printf("return false");
    break;
    
  case 123:
    printf("return nil");
    break;
    
  case 124:
    printf("return Message stack top");
    break;
    
  case 125:
    printf("return Block stack top");
    break;
    
  case 126: case 127:
    printf("Bytecode %d ILLEGAL!!!", bp[0]);
    break;
    
  case 128:
    switch (bp[1] >> 6) {
    case 0:
      printf("push Instance Variable[%d]", bp[1] & 63);
      break;
    case 1:
      printf("push Temporary[%d]", bp[1] & 63);
      break;
    case 2:
      printf("push Constant[%d]", bp[1] & 63);
      break;
    case 3:
      printf("push Global Variable[%d] = ", bp[1] & 63);
      printAssociationKey(literalVec[bp[1] & 63]);
      break;
    }
    break;
    
  case 129:
    switch (bp[1] >> 6) {
    case 0:
      printf("store Instance Variable[%d]", bp[1] & 63);
      break;
    case 1:
      printf("store Temporary[%d]", bp[1] & 63);
      break;
    case 2:
      printf("Illegal store into constant[%d]", bp[1] & 63);
      break;
    case 3:
      printf("store Global Variable[%d] = ", bp[1] & 63);
      printAssociationKey(literalVec[bp[1] & 63]);
      break;
    }
    break;
    
  case 130:
    switch (bp[1] >> 6) {
    case 0:
      printf("pop and store Instance Variable[%d]", bp[1] & 63);
      break;
    case 1:
      printf("pop and store Temporary[%d]", bp[1] & 63);
      break;
    case 2:
      printf("lllegal pop and store into constant[%d]", bp[1] & 63);
      break;
    case 3:
      printf("pop and store Global Variable[%d]", bp[1] & 63);
      printAssociationKey(literalVec[bp[1] & 63]);
      break;
    }
    break;
    
  case 131:
    printf("send selector %d, %d args = ", bp[1] & 31, bp[1] >> 5);
    printSymbol(literalVec[bp[1] & 31]);
    break;
    
  case 132:
    printf("send selector %d, %d args = ", bp[2], bp[1]);
    printSymbol(literalVec[bp[2]]);
    break;
    
  case 133:
    printf("send to super selector %d, %d args = ", bp[1] & 31, bp[1] >> 5);
    printSymbol(literalVec[bp[1] & 31]);
    break;
    
  case 134:
    printf("send to super selector %d, %d args = ", bp[2], bp[1]);
    printSymbol(literalVec[bp[2]]);
    break;
    
  case 135:
    printf("pop stack top");
    break;
    
  case 136:
    printf("duplicate stack top");
    break;
    
    
  case 137:
    printf("push current context");
    break;
    
  case 138: case 139: case 140: case 141: 
  case 142: case 143:
    printf("Illegal bytecode %d!!!", bp[0]);
    break;
    
  case 144: case 145: case 146: case 147:
  case 148: case 149: case 150: case 151:
    printf("jump to %d", (bp[0] & 7) + ip + 1 + 1);
    break;
    
  case 152: case 153: case 154: case 155:
  case 156: case 157: case 158: case 159:
    printf("jump to %d if false", (bp[0] & 7) + ip + 1 + 1);
    break;
    
  case 160: case 161: case 162: case 163:
  case 164: case 165: case 166: case 167:
    printf("jump to %d", ((bp[0]&7)-4) * 256 + bp[1] + ip + 2);
    break;
    
  case 168: case 169: case 170: case 171:
    printf("pop and jump to %d if true", (bp[0]&3) * 256 + bp[1] + ip + 2);
    break;
    
  case 172: case 173: case 174: case 175:
    printf("pop and jump to %d if false", (bp[0]&3) * 256 + bp[1] + ip + 2);
    break;
    
  case 176: case 177: case 178: case 179: 
  case 180: case 181: case 182: case 183: 
  case 184: case 185: case 186: case 187: 
  case 188: case 189: case 190: case 191: 
    printf("send arithmetic message \"%s\"", mathMessageName[bp[0] & 15]);
    break;
    
  case 192: case 193: case 194: case 195: 
  case 196: case 197: case 198: case 199: 
  case 200: case 201: case 202: case 203: 
  case 204: case 205: case 206: case 207: 
    printf("send special message \"%s\"", specialMessageName[bp[0] & 15]);
    break;
    
  case 208: case 209: case 210: case 211: 
  case 212: case 213: case 214: case 215: 
  case 216: case 217: case 218: case 219: 
  case 220: case 221: case 222: case 223: 
    printf("send selector %d, 0 args = ", bp[0] & 15);
    printSymbol(literalVec[bp[0] & 15]);
    break;
    
  case 224: case 225: case 226: case 227: 
  case 228: case 229: case 230: case 231: 
  case 232: case 233: case 234: case 235: 
  case 236: case 237: case 238: case 239: 
    printf("send selector %d, 1 arg = ", bp[0] & 15);
    printSymbol(literalVec[bp[0] & 15]);
    break;
    
  case 240: case 241: case 242: case 243: 
  case 244: case 245: case 246: case 247: 
  case 248: case 249: case 250: case 251: 
  case 252: case 253: case 254: case 255: 
    printf("send selector %d, 2 args = ", bp[0] & 15);
    printSymbol(literalVec[bp[0] & 15]);
    break;
    
  default:
    printf("UNHANDLED BYTE CODE %d!!!", bp[0]);
    break;
  }
}

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