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

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

/***********************************************************************
 *
 *	Symbol Table 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	     11 Jul 95	  Added John Stanhope (jehu@vt.edu)'s changes for
 *			  Objective-C calling (Thanks John!!!)
 *
 * sbb	     23 Jun 95	  Switched to GST header guard prefix.
 *
 * sbb	     11 Jun 94	  Added cObjectPtrSymbol.
 *
 * sbyrne    13 Jan 90	  Added thisContextSymbol.
 *
 * sbyrne     1 Jan 89	  Created.
 *
 */

#ifndef __GSTSYM__
#define __GSTSYM__

#define INITIAL_SYMBOL_TABLE_SIZE	521

/* Uncomment this to enable profiling of the symbol table */
/*#define symbol_table_profiling */

typedef enum {
  temporaryScope,
  receiverScope,
  poolScope,
  globalScope
} ScopeType;



typedef struct SymbolStruct {
  OBJ_HEADER;			/* I love inheritance */
  char		symString[1];
} *Symbol;

typedef struct SymbolEntryStruct {
  ScopeType	scope;
  OOP		symbol;
  int		varIndex;	/* index of receiver or temporary */
} *SymbolEntry;

extern SymbolEntry	findVariable();

extern OOP		atColonSymbol, atColonPutColonSymbol, sizeSymbol,
			nextSymbol, nextPutColonSymbol, atEndSymbol, 
  			classSymbol, blockCopyColonSymbol, valueSymbol,
			valueColonValueColonSymbol,
			valueColonValueColonValueColonSymbol,
 			valueWithArgumentsColonSymbol,
			valueColonSymbol, doColonSymbol, newSymbol,
			newColonSymbol, plusSymbol, minusSymbol,
			lessThanSymbol, greaterThanSymbol, lessEqualSymbol,
			greaterEqualSymbol, equalSymbol, notEqualSymbol,
			timesSymbol, divideSymbol, remainderSymbol,
			bitShiftColonSymbol, integerDivideSymbol,
			bitAndColonSymbol, bitOrColonSymbol, sameObjectSymbol,
  			notSameObjectSymbol,
  			whileTrueColonSymbol, whileFalseColonSymbol,
			ifTrueColonSymbol, ifFalseColonSymbol, 
			ifTrueColonIfFalseColonSymbol,
  			ifFalseColonIfTrueColonSymbol, andColonSymbol,
			orColonSymbol, selfSymbol, superSymbol, trueSymbol,
  			falseSymbol, nilSymbol, orSymbol, andSymbol,
			doesNotUnderstandColonSymbol, unknownSymbol,
			charSymbol, stringSymbol, stringOutSymbol, 
			symbolSymbol, intSymbol, longSymbol, floatSymbol,
			doubleSymbol,
			voidSymbol, variadicSymbol, cObjectSymbol,
			cObjectPtrSymbol, smalltalkSymbol, symbolTable,
			thisContextSymbol, byteArraySymbol, byteArrayOutSymbol;

extern OOP		internString(),
  			makeInstanceVariableArray(),
			makeClassVariableDictionary(),
			makePoolArray(), 
			internStringOOP();

extern char		*symbolAsString();

extern int		stringOOPLen(), getArgCount(), getTempCount();
extern void		printString(), printSymbol(), initSymbols(),
			declareArguments(), declareTemporaries(),
			undeclareArguments(), undeclareTemporaries(),
			declareBlockArguments(), undeclareBlockArguments(),
			freeSymbolEntry(), initArgCount(), initTempCount();


#endif /* __GSTSYM__ */

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