This is sym.c in view mode; [Download] [Up]
/*********************************************************************** * * Symbol Table module. * * $Revision: 1.6 $ * $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 10 Sep 95 Added incubator usage. * * sbb 13 Jul 95 Removed HAVE_ALLOCA_H. * * sbb 11 Jul 95 Added John Stanhope (jehu@vt.edu)'s changes for * Objective-C calling (Thanks John!!!) * * sbb 29 Jun 95 Fixed pool dictionary allocation to not allocate a * large number of immediately thrown away arrays. * * sbb 6 Jun 95 Switched to new file naming scheme. * * sbb 30 May 95 Boolean => mst_Boolean. * * sbb 31 Mar 95 Adjusted a reference to the empty bytes to use the * new, architecture independent macro definitions. * * sbb 8 Oct 94 Fixed the internCountedString bug by deferring OOP * allocation until all instances have ben allocated. * * sbb 2 Oct 94 Fixed a bug in internCountedString that occurs other * places where there is the possibility of doing a * garbage collection just after a newly allocated * object which has not been added to a * root-set-reachable object. The GC sees that there * are no references to the new object, and marks its * oop free and does not copy the just allocated object * into the new current semispace. This problem can * occur anywhere these conditions occur. Given that * allocOOP moves the object to the current space if * it's not already there, for this case to really * occur, you have to have done the allocOOP before you * call the second instantiate or other allocation * primitive. * * sbb 11 Jun 94 Added cObjectPtrSymbol for new call by value * parameter passing mode. * * sbyrne 16 May 90 Changed usages of "entry" to "ent" to prevent * collisions with C compilers which have this * identifier as a reserved word. * * sbyrne 21 Apr 90 Addded byteArraySymbol. * * sbyrne 13 Jan 90 Added thisContextSymbol. * * sbyrne 19 Dec 89 Rebuilt symbol table. Used to use the main OOP table * as a symbol table, due to issues involving initial * bootstrapping of the system. Now using open hash * table built of arrays and linked lists, so that no * special precautions need be taken by the GC system or * the image save/restore facility. * * sbyrne 25 Jul 89 Changed undeclareName to take a parameter that * controls whether the frame index is decremented or * not. It appears that each block gets its own, * non-shared temporaries/arguments, so that if the * block is used in a process, other blocks won't have * strange things happening to their arguments. * * sbyrne 5 Jan 89 Created. * */ #include "gst.h" #include "sym.h" #include "oop.h" #include "comp.h" #include "dict.h" #include "tree.h" #include "lex.h" #include <stdio.h> #include <ctype.h> #if STDC_HEADERS #include <stdlib.h> #include <string.h> #endif /* STDC_HEADERS */ /* if defined, use the hash algorithm given in the dragon book (see usage for * better reference. */ #define dragon_book #if !defined(max) #define max(x, y) \ ( ((x) > (y)) ? (x) : (y) ) #endif #define isSymbol(oop) \ ( !isNil(oop) && (oopClass(oop) == symbolClass) ) typedef struct { OBJ_HEADER; OOP nextLink; OOP symbol; } *SymLink; OOP 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, cObjectPtrSymbol, smalltalkSymbol, symbolTable, byteArraySymbol, byteArrayOutSymbol; #ifdef symbol_table_profiling int adds = 0, reused = 0, reprobes = 0, hitsOn[OOP_TABLE_SIZE]; #endif /* symbol_table_profiling */ void printString(); static SymbolEntry allocSymbolEntry(); #ifdef appears_to_be_unused /* Sun Jul 9 00:21:06 1995 */ /**/static Symbol makeNewSymbol(); #endif /* appears_to_be_unused Sun Jul 9 00:21:06 1995 */ static mst_Boolean isSameString(), isWhiteSpace(); unsigned long hashString(); static void declareName(), undeclareName(), parseVariableName(); static OOP scanName(), internCountedString(); static int instanceVariableIndex(), localVarIndex(); typedef struct SymbolListStruct *SymbolList; struct SymbolListStruct { OOP symbol; int index; SymbolList prevSymbol; }; static SymbolList symbolList; static int methodArguments, frameIndex, maxFrameIndex; int getArgCount() { return (methodArguments); } int getTempCount() { return (maxFrameIndex - methodArguments); } void initArgCount() { methodArguments = 0; } void initTempCount() { } void declareArguments(args) TreeNode args; { symbolList = nil; frameIndex = 0; maxFrameIndex = 0; if (args->nodeType == unaryExprType) { return; } else if (args->nodeType == binaryExprType) { declareName(args->vExpr.expression->vList.name); methodArguments++; } else { for(args = args->vExpr.expression; args != nil; args = args->vList.next) { declareName(args->vList.value->vList.name); methodArguments++; } } } void declareTemporaries(temps) TreeNode temps; { for( ; temps != nil; temps = temps->vList.next) { declareName(temps->vList.name); } } void declareBlockArguments(args) TreeNode args; { for( ; args != nil; args = args->vList.next) { declareName(args->vList.name); } } static void declareName(name) char *name; { SymbolList newList; newList = (SymbolList)malloc(sizeof(struct SymbolListStruct)); newList->symbol = internString(name); newList->index = frameIndex++; maxFrameIndex = max(maxFrameIndex, frameIndex); newList->prevSymbol = symbolList; symbolList = newList; } void undeclareArguments(args) TreeNode args; { if (args == nil) { return; } if (args->nodeType == unaryExprType) { return; } else if (args->nodeType == binaryExprType) { undeclareName(true); } else { for(args = args->vExpr.expression; args != nil; args = args->vList.next) { undeclareName(true); } } } void undeclareTemporaries(temps) TreeNode temps; { for( ; temps != nil; temps = temps->vList.next) { undeclareName(true); } } void undeclareBlockArguments(args) TreeNode args; { if (args == nil) { return; } for( ; args != nil; args = args->vList.next) { undeclareName(false); } } static void undeclareName(decrFrameIndex) mst_Boolean decrFrameIndex; { SymbolList oldList; oldList = symbolList; symbolList = symbolList->prevSymbol; free(oldList); if (decrFrameIndex) { frameIndex--; } } OOP findClassVariable(varName) OOP varName; { OOP classOOP, assocOOP, classVariableOOP; if (oopClass(thisClass) == behaviorClass || oopClass(thisClass) == classDescriptionClass) { /* classDescriptions and above don't have class or pool variables */ /* ### this isn't quite the right test; we probably should be testing for if we have a classClass or some derivative of that */ return (nilOOP); } for (classOOP = thisClass; !isNil(classOOP); classOOP = superClass(classOOP)) { if (oopClass(classOOP) == metaclassClass) { /* pretend that metaclasses have the class variables and shared pools that their instance classes do */ classVariableOOP = metaclassInstance(classOOP); } else { classVariableOOP = classOOP; } assocOOP = dictionaryAssociationAt(classVariableDictionary(classVariableOOP), varName); if (!isNil(assocOOP)) { return (assocOOP); } assocOOP = findSharedPoolVariable(classVariableOOP, varName); if (!isNil(assocOOP)) { return (assocOOP); } } return (nilOOP); } SymbolEntry findVariable(varName) char *varName; { OOP varAssoc, symbol; int index; symbol = internString(varName); index = localVarIndex(symbol); if (index >= 0) { return (allocSymbolEntry(temporaryScope, symbol, index)); } index = instanceVariableIndex(symbol); if (index >= 0) { return (allocSymbolEntry(receiverScope, symbol, index)); } varAssoc = findClassVariable(symbol); if (isNil(varAssoc)) { return (nil); } index = addForcedObject(varAssoc); return (allocSymbolEntry(globalScope, varAssoc, index)); } static int instanceVariableIndex(symbol) OOP symbol; { OOP arrayOOP; int index, numVars; if (oopClass(thisClass) == behaviorClass) { /* behaviors have no instance variables */ return (-1); } arrayOOP = instanceVariableArray(thisClass); numVars = numOOPs(oopToObj(arrayOOP)); for (index = 1; index <= numVars; index++) { if (arrayAt(arrayOOP, index) == symbol) { return (index-1); } } return (-1); } static int localVarIndex(symbol) OOP symbol; { SymbolList s; for (s = symbolList; s != nil && symbol != s->symbol; s = s->prevSymbol); if (s != nil) { /* found one */ return (s->index); } else { return (-1); } } static SymbolEntry allocSymbolEntry(scope, symbol, index) ScopeType scope; OOP symbol; int index; { SymbolEntry ent; ent = (SymbolEntry)malloc(sizeof(struct SymbolEntryStruct)); ent->scope = scope; ent->symbol = symbol; ent->varIndex = index; return (ent); } void freeSymbolEntry(ent) SymbolEntry ent; { free(ent); } OOP makeInstanceVariableArray(superclassOOP, variableString) OOP superclassOOP; Byte *variableString; { OOP arrayOOP, superArrayOOP, name; int index, numInstanceVars, superInstanceVars; Byte *p; IncPtr incPtr; if (variableString == nil) { variableString = (Byte *)""; } if (isNil(superclassOOP)) { superArrayOOP = nilOOP; superInstanceVars = numInstanceVars = 0; } else { superArrayOOP = instanceVariableArray(superclassOOP); superInstanceVars = numInstanceVars = numOOPs(oopToObj(superArrayOOP)); } for (p = variableString; *p; ) { /* skip intervening whitespace */ name = scanName(&p); if (!isNil(name)) { numInstanceVars++; } } if (numInstanceVars == 0) { return (nilOOP); /* no instances here */ } incPtr = incSavePointer(); arrayOOP = arrayNew(numInstanceVars); incAddOOP(arrayOOP); /* inherit variables from parent */ for (index = 1; index <= superInstanceVars; index++) { arrayAtPut(arrayOOP, index, arrayAt(superArrayOOP, index)); } /* now add our own variables */ for (p = variableString; *p; index++) { /* skip intervening whitespace */ name = scanName(&p); /* don't need to add name to incubator * -- it's a symbol so it's already held onto */ if (!isNil(name)) { arrayAtPut(arrayOOP, index, name); } } incRestorePointer(incPtr); return (arrayOOP); } OOP makeClassVariableDictionary(classOOP, variableNames) OOP classOOP; Byte *variableNames; { OOP dictionaryOOP, name; Byte *p; IncPtr incPtr; if (variableNames == nil) { variableNames = (Byte *)""; } incPtr = incSavePointer(); dictionaryOOP = dictionaryNew(); incAddOOP(dictionaryOOP); for (p = variableNames; *p; ) { name = scanName(&p); if (!isNil(name)) { /* ### error if already exists */ /* don't need to add name to incubator * -- it's a symbol so it's already held onto */ dictionaryAtPut(dictionaryOOP, name, nilOOP); } } if (dictionarySize(dictionaryOOP) == 0) { dictionaryOOP = nilOOP; } incRestorePointer(incPtr); return (dictionaryOOP); } OOP makePoolArray(classOOP, poolNames) OOP classOOP; Byte *poolNames; { OOP pools, name; int numPools, i; Byte *p, *e; IncPtr incPtr; if (poolNames == nil) { poolNames = (Byte *)""; } /* count the number of new pool names */ for (p = poolNames, numPools = 0; *p; ) { parseVariableName(&p, &e); if (p != e) { numPools++; p = e; } } incPtr = incSavePointer(); pools = nilOOP; /* ### maybe change this to leave empty array */ for (p = poolNames, i = 1; *p; i++) { name = scanName(&p); if (!isNil(name)) { /* don't need to add name to incubator -- it's a symbol so it's * already held onto. */ /* ### error if already exists in parent?, or if value isn't a dictionary */ /* ### should I keep these as names? or associations? Should I look up the names somewhere other than in the smalltalk dictionary? Need to check for undefineds? */ if (pools == nilOOP) { pools = arrayNew(numPools); incAddOOP(pools); } arrayAtPut(pools, i, dictionaryAt(smalltalkDictionary, name)); } } incRestorePointer(incPtr); return (pools); } /* * static OOP scanName(pp) * * Description * * Scan a variable name (letters and digits, initial letter), and return a * symbol for it. * * Inputs * * pp : pointer to a pointer to the start of the string to be scanned. * May be pointing at either whitespace or start of variable. At * end, points to first character after the parsed variable name, * which may be NUL. * * Outputs * * Symbol for variable name, or nilOOP if none found. pp points to first * char after symbol name (if any). */ static OOP scanName(pp) Byte **pp; { Byte *end, *str; long len; parseVariableName(pp, &end); len = end - *pp; if (len == 0) { return (nilOOP); } str = (Byte *)alloca(len + 1); strncpy(str, *pp, len); str[len] = '\0'; *pp = end; return (internString(str)); } static void parseVariableName(pp, endp) Byte **pp, **endp; { register Byte *p, *e; p = *pp; e = *endp; while (isWhiteSpace(*p)) { p++; } /* ### check for non-null here and not alnum; we've jammed on a bogus char and it's an error */ /* variable name extends from p to e-1 */ for (e = p; *e; e++) { if (!isalnum(*e)) { break; } } *pp = p; *endp = e; } static mst_Boolean isWhiteSpace(c) Byte c; { return (c == ' ' || c == '\t' || c == '\n' || c == '\f'); } OOP internStringOOP(stringOOP) OOP stringOOP; { int len; char copyBuf[100], *copyPtr; OOP symbolOOP; len = stringOOPLen(stringOOP); /* do this slightly more complicated bit of code because: * 1) we don't want to call malloc/free if we can help it * 2) if we just used stringOOPChars (as we used to), we pass the * *dereferenced* value of the stringOOP. internCountedString * can do allocations. If it allocates, and the gc runs, stringOOP * can move, meaning the dereferenced set of chars becomes invalid. * So instead we make a non-moving copy and use that. */ if (len < sizeof(copyBuf)) { copyPtr = copyBuf; } else { copyPtr = (char *)malloc(len); } memcpy(copyPtr, stringOOPChars(stringOOP), len); symbolOOP = internCountedString(copyPtr, len); if (len >= sizeof(copyBuf)) { free(copyPtr); } return symbolOOP; } OOP internString(str) char *str; { int len; len = strlen(str); return (internCountedString(str, len)); } static OOP internCountedString(str, len) Byte *str; int len; { unsigned long index; SymLink link; Symbol symbol; OOP symbolOOP, linkOOP; IncPtr incPtr; index = (hashString(str, len) % numOOPs(oopToObj(symbolTable))) + 1; for (linkOOP = arrayAt(symbolTable, index); !isNil(linkOOP); linkOOP = link->nextLink) { link = (SymLink)oopToObj(linkOOP); if (isSameString(str, link->symbol, len)) { return (link->symbol); } } /* no match, have to add it to head of list */ incPtr = incSavePointer(); symbol = (Symbol)newInstanceWith(symbolClass, (long)len); strncpy(symbol->symString, str, len); symbolOOP = allocOOP(symbol); initEmptyBytes(symbolOOP, len); incAddOOP(symbolOOP); link = (SymLink)newInstance(symLinkClass); link->nextLink = arrayAt(symbolTable, index); link->symbol = nilOOP; /* keep the GC happy */ /* maybeMoveOOP(link->nextLink); /* make sure it's here with us */ link->symbol = symbolOOP; arrayAtPut(symbolTable, index, allocOOP(link)); incRestorePointer(incPtr); return (symbolOOP); } #ifdef appears_to_be_unused /* Sun Jul 9 00:20:46 1995 */ /**/static Symbol makeNewSymbol(str, len) /**/Byte *str; /**/int len; /**/{ /**/ Symbol symbol; /**/ /**/ symbol = (Symbol)newInstanceWith(symbolClass, (long)len); /**/ strncpy(symbol->symString, str, len); /**/ /**/ return (symbol); /**/} #endif /* appears_to_be_unused Sun Jul 9 00:20:46 1995 */ static mst_Boolean isSameString(str, oop, len) char *str; OOP oop; int len; { if (stringOOPLen(oop) == len) { return (strncmp(str, ((Symbol)oopToObj(oop))->symString, len) == 0); } return (false); } int stringOOPLen(oop) OOP oop; { return (oopSizeBytes(oop) - (oop->flags & EMPTY_BYTES)); } unsigned long hashString(str, len) char *str; int len; { #ifdef dragon_book /* from Dragon Book, p436 */ unsigned long hashVal = 0, carry; for ( ; len > 0; str++, len--) { hashVal = (hashVal << 4) + (*str); if (carry = (hashVal & 0xf0000000)) { hashVal ^= (carry >> 24); hashVal ^= carry; } } return (hashVal); #else long result = 0L; for (; len > 0; str++, len--) { result = (result << 1) /* | (result < 0) */; result ^= *str; } return ((unsigned long)result); #endif /* ! dragon_book */ } void printSymbol(symbol) OOP symbol; { if (isNil(symbol)) { printf(nilName); } else { printString(symbol); } } void printString(string) OOP string; { int len; len = stringOOPLen(string); fwrite(oopToObj(string)->data, sizeof(Byte), len, stdout); fflush(stdout); } /* * char *symbolAsString(symbolOOP) * * Description * * Given a symbol, this routine returns a C string that corresponds to the * name of the symbol. The returned value is a pointer to a static area, * so if it's to be used for anything other than immediate output, the * caller needs to make a copy of the retured string. * * Inputs * * symbolOOP: * An OOP for a symbol * * Outputs * * Pointer to a C string that contains the symbol name. */ char *symbolAsString(symbolOOP) OOP symbolOOP; { static char stringBuf[256]; /* probably large enough for most symbols */ int len; Symbol symbol; symbol = (Symbol)oopToObj(symbolOOP); len = stringOOPLen(symbolOOP); if (len >= sizeof(stringBuf)) { errorf("symbol name too long: %d, max is %d", len, sizeof(stringBuf)); } strncpy(stringBuf, symbol->symString, len); stringBuf[len] = '\0'; return (stringBuf); } mst_Boolean okToCheck = false; void checkSymbolChain() { unsigned long i; if (!okToCheck) return; for (i = 1; i <= numOOPs(oopToObj(symbolTable)); i++) { SymLink link; OOP linkOOP; for (linkOOP = arrayAt(symbolTable, i); !isNil(linkOOP); linkOOP = link->nextLink) { link = (SymLink)oopToObj(linkOOP); if (oopClass(linkOOP) != symLinkClass || oopClass(link->symbol) != symbolClass) { printf("Bad symbol %x\n", linkOOP); debug(); } } } } /* * void printSymbols() * * Description * * This routine is used for symbol table debugging only. * */ void printSymbolChain(); /* ### hack */ void printSymbols() { unsigned long i; for (i = 1; i <= numOOPs(oopToObj(symbolTable)); i++) { printf("Table[%d]:\n", i); printSymbolChain(i); printf("\n"); } } void printSymbolChain(i) unsigned long i; { SymLink link; OOP linkOOP; for (linkOOP = arrayAt(symbolTable, i); !isNil(linkOOP); linkOOP = link->nextLink) { link = (SymLink)oopToObj(linkOOP); printf("%d:", linkOOP - oopTable); /* ### */ printSymbol(link->symbol); printf("->"); } } void printSymLink(symLinkOOP) OOP symLinkOOP; { SymLink link; link = (SymLink)oopToObj(symLinkOOP); printObject(link->symbol); } void initSymbols() { andColonSymbol = internString("and:"); andSymbol = internString("&"); atColonPutColonSymbol = internString("at:put:"); atColonSymbol = internString("at:"); atEndSymbol = internString("atEnd"); bitAndColonSymbol = internString("bitAnd:"); bitOrColonSymbol = internString("bitOr:"); bitShiftColonSymbol = internString("bitShift:"); blockCopyColonSymbol = internString("blockCopy:"); byteArraySymbol = internString("byteArray"); byteArrayOutSymbol = internString("byteArrayOut"); charSymbol = internString("char"); classSymbol = internString("class"); cObjectSymbol = internString("cObject"); cObjectPtrSymbol = internString("cObjectPtr"); divideSymbol = internString("/"); doColonSymbol = internString("do:"); doesNotUnderstandColonSymbol = internString("doesNotUnderstand:"); floatSymbol = internString("float"); doubleSymbol = internString("double"); equalSymbol = internString("="); falseSymbol = internString("false"); greaterEqualSymbol = internString(">="); greaterThanSymbol = internString(">"); ifFalseColonIfTrueColonSymbol = internString("ifFalse:ifTrue:"); ifFalseColonSymbol = internString("ifFalse:"); ifTrueColonIfFalseColonSymbol = internString("ifTrue:ifFalse:"); ifTrueColonSymbol = internString("ifTrue:"); integerDivideSymbol = internString("//"); intSymbol = internString("int"); lessEqualSymbol = internString("<="); lessThanSymbol = internString("<"); longSymbol = internString("long"); minusSymbol = internString("-"); newColonSymbol = internString("new:"); newSymbol = internString("new"); nextPutColonSymbol = internString("nextPut:"); nextSymbol = internString("next"); nilSymbol = internString("nil"); notEqualSymbol = internString("~="); notSameObjectSymbol = internString("~~"); orColonSymbol = internString("or:"); orSymbol = internString("|"); plusSymbol = internString("+"); remainderSymbol = internString("\\"); sameObjectSymbol = internString("=="); selfSymbol = internString("self"); sizeSymbol = internString("size"); smalltalkSymbol = internString("smalltalk"); stringOutSymbol = internString("stringOut"); stringSymbol = internString("string"); superSymbol = internString("super"); symbolSymbol = internString("symbol"); thisContextSymbol = internString("thisContext"); timesSymbol = internString("*"); trueSymbol = internString("true"); unknownSymbol = internString("unknown"); valueColonSymbol = internString("value:"); valueColonValueColonSymbol = internString("value:value:"); valueColonValueColonValueColonSymbol = internString("value:value:value:"); valueSymbol = internString("value"); valueWithArgumentsColonSymbol = internString("valueWithArguments:"); variadicSymbol = internString("variadic"); voidSymbol = internString("void"); whileFalseColonSymbol = internString("whileFalse:"); whileTrueColonSymbol = internString("whileTrue:"); }
These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.