Symbol.st
author claus
Tue, 08 Aug 1995 02:49:43 +0200
changeset 375 e5019c22f40e
parent 370 20f04d9b371b
child 379 5b5a130ccd09
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1988 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

String subclass:#Symbol
       instanceVariableNames:''
       classVariableNames:''
       poolDictionaries:''
       category:'Collections-Text'
!

Symbol comment:'
COPYRIGHT (c) 1988 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Symbol.st,v 1.26 1995-08-08 00:49:18 claus Exp $
'!

!Symbol class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Symbol.st,v 1.26 1995-08-08 00:49:18 claus Exp $
"
!

documentation
"
    Symbols represent unique strings - every symbol with same printString
    exists exactly once in the system; Symbols are used for selectors, global
    variable-keys etc. Symbols can also be used to represent things which are
    enumeration type values in other programming languages (since symbols are
    created at compile time, comparing them using == is a fast pointer compare).

    A symbol may not change its characters - i.e. it is constant over its lifetime.
    Other than that, symbols behave much like strings.
"
! !

!Symbol class methodsFor:'instance creation'!

basicNew:size
    "redefined to return a string instead of a symbol -
     this allows all copy methods inherited from String to
     return strings containing the symbols characters.
     Real symbols are only created with intern: or asSymbol."

    ^ String new:size
!

new:size
    "redefined to return a string instead of a symbol -
     this allows all copy methods inherited from String to
     return strings containing the symbols characters.
     Real symbols are only created with intern: or asSymbol."

    ^ String new:size
!

intern:aString
    "return a unique symbol with printname taken from the String-argument"

%{  /* NOCONTEXT */
    if (__isSymbol(aString)) {
	RETURN (aString);
    }
    if (__isString(aString)) {
	RETURN ( _MKSYMBOL(_stringVal(aString), (OBJ *)0, SENDER) );
    }
%}
.
    ^ self mustBeString
!

fromString:aString
    "same as intern: for Symbol, but may be used to create interned instances
     of subclasses.
     Notice: this fails, if you try to intern an instance of a subclass, AND
     a symbol with the same name already exists. In this case, the original
     symbol is returned. To use it for enum-type symbols, make certain, that the
     names are unique (for example by including the classes name as a prefix-string)."

    |sym len|

    sym := aString asSymbolIfInterned.
    sym notNil ifTrue:[
	^ sym
    ].

    "
     create a new uninterned instance first
    "
    len := aString size.
    sym := super basicNew:len.
    sym replaceFrom:1 to:len with:aString.

    "now, intern it"
%{
    extern OBJ __INTERNSYMBOL();

    sym = __INTERNSYMBOL(sym, (OBJ *)0, __context);
%}.
    ^ sym
!

internCharacter:aCharacter
    "return a unique symbol with printname taken from the Character-argument"

    ^ self intern:(aCharacter asString)
! !

!Symbol class methodsFor:'queries'!

hasInterned:aString ifTrue:trueBlock
    "for ST-80 compatibility - if the argument, aString is known
     as Symbol, evaluate the block with the corresponding symbol
     as argument and return true; otherwise return false"

    |sym|

    (sym := aString asSymbolIfInterned) notNil ifTrue:[
	trueBlock value:sym.
	^ true
    ].
    ^ false
!

hasInterned:aString
    "return true, if the argument, aString is known as Symbol;
     false otherwise"

    ^ aString knownAsSymbol
!

findInterned:aString
    "for ST-80 compatibility - if the argument, aString is known
     as Symbol, return this symbol. Otherwise return nil."

    ^ aString asSymbolIfInterned
! !

!Symbol methodsFor:'accessing'!

basicAt:index put:something
    "report an error if an interned symbol is about to be changed
     - interned symbols may NOT be changed."

    self knownAsSymbol ifTrue:[
	self error:'interned symbols may not be changed'.
	^ something
    ].
    "
     uninterned - allow change
    "
    ^ super basicAt:index put:something
!

byteAt:index put:value
    "report an error if interned - interned symbols may not be changed."

    ^ self basicAt:index put:(value asCharacter)
! !

!Symbol methodsFor:'copying'!

copy
    "return a copy of myself
     - reimplemented here since symbols are unique and copy should
     return a new string with my characters."

     ^ self
!

shallowCopy
    "return a copy of myself
     - reimplemented here since symbols are unique"

     ^ self
!

deepCopy
    "return a copy of myself
     - reimplemented here since symbols are unique and copy should
     return a new string with my characters."

     ^ self
!

deepCopyUsing:aDictionary
    "return a copy of myself
     - reimplemented here since symbols are unique and copy should
     return a new string with my characters."

     ^ self
!

simpleDeepCopy
    "return a copy of myself
     - reimplemented here since symbols are unique and copy should
     return a new string with my characters."

     ^ self
! !

!Symbol methodsFor:'converting'!

asString
    "return a string with printname taken from mine"

%{  /* NOCONTEXT */
    extern OBJ __MKSTRING_ST();
    OBJ s;

    s = __MKSTRING_ST(self COMMA_SND);
    if (s != nil) {
	RETURN (s);
    }
%}.
    "
     memory allocation (for the new string) failed.
     When we arrive here, there was no memory, even after a garbage collect.
     This means, that the VM wanted to get some more memory from the
     OS, which was not kind enough to give it.
     Bad luck - you should increase the swap space on your machine,
     or if you have set a soft memoryLimit, increase it.
    "
    ^ ObjectMemory allocationFailureSignal raise.
!

asSymbol
    "return the receiver as a symbol.
     Since I am a symbol - just return myself"

    ^ self
!

asSymbolIfInterned
    "return the receiver as a symbol if there is one.
     Since I am a symbol - just return myself"

    ^ self
!

knownAsSymbol 
    "return true if the receiver is known as a symbol.
     Since I am a symbol - just return true"

    ^ true
! !

!Symbol methodsFor:'queries'!

species
    "when copying, or concatenating, return instances of this class"

    ^ String
! 

isSymbol 
    "return true, if the receiver is some kind of symbol.
     Since I am a symbol, return always true"

    ^ true
! !

!Symbol methodsFor:'comparing'!

identityHash
    "interned symbols can return a better hash key"

%{  /* NOCONTEXT */

    REGISTER int g, val;
    REGISTER unsigned char *cp, *cp0;
    int l;

    if (__Class(self) == Symbol) {
	val = __GET_HASH(self);
	/*
	 * only do it, if I have no standard hash key
	 * assigned (which can only happen due to a #become:,
	 * or by creating a symbol uninterned, and interning it
	 * after it got a hashKey assigned.
	 */
	if (val == 0) {
	    cp = _stringVal(self);
	    l = _stringSize(self);
        
	    /*
	     * this is the dragon-book algorithm
	     *
	     * the algorithm hashes pretty good:
	     *   with (currently) 9963 symbols in the system,
	     *   there are only about 200 hash key collisions.
	     *   where the maximum collision count in these 200
	     *   is 3. This means, that in most situations,
	     *   a single probe will find the right element in
	     *   a symbol-hashed collection.
	     */
	    val = 0;
	    for (cp0 = cp, cp += l - 1; cp >= cp0; cp--) {
		val = (val << 5) + (*cp & 0x1F);
		if (g = (val & 0x3E000000))
		    val ^= g >> 25 /* 23 */ /* 25 */;
		val &= 0x3FFFFFFF;
	    }

	    if (l) {
		l |= 1; 
		val = (val * l) & 0x3FFFFFFF;
	    }
	} else {
	    val <<= __HASH_SHIFT__;
	}
	RETURN ( _MKSMALLINT(val) );
     }
%}.
     ^ super identityHash
!

= something
    "return true, if the receiver and argument consist of the same characters.
     Redefined here, for more efficient #= comparison of symbols 
     (which ought to be compared using #==).
     If the argument is a symbol, we use a quick pointer compare, instead of
     the inherited value compare."

%{   /* NOCONTEXT */
    OBJ cls;

    if (! __isNonNilObject(something)) RETURN(false);
    if ((cls = __qClass(something)) == Symbol) {
	RETURN (self == something ? true : false);
    }
    if (cls == String) {
	RETURN (strcmp(__stringVal(self), __stringVal(something)) == 0 ? true : false); 
    }
%}.
    "fall back; could be a TwoByteString, or a collection of Characters"

    ^ super = something
!

~= something
    "return true, if the receiver and argument do not consist of the same characters.
     Redefined here, for more efficient #~= comparison of symbols 
     (which ought to be compared using #~~).
     If the argument is a symbol, we use a quick pointer compare, instead of
     the inherited value compare."

%{   /* NOCONTEXT */
    OBJ cls;

    if (! __isNonNilObject(something)) RETURN(true);	/* cannot be equal */
    if ((cls = __qClass(something)) == Symbol) {
        RETURN (self == something ? false : true);
    }
    if (cls == String) {
        RETURN (strcmp(__stringVal(self), __stringVal(something)) == 0 ? false : true);
    }
%}.
    "fall back; could be a TwoByteString, or a collection of Characters"

    ^ super ~= something
! !

!Symbol methodsFor:'system primitives'!

become:anotherObject
    "make all references to the receiver become references to anotherObject
     and vice-versa. For symbols, some special action is required, to
     correctly handle a become of the global dictionaries.
     Anyway: this is very dangerous - mysterous side-effects are to be
     expected.

     Notice: because of the danger here, this method may report an error
	     in future versions"

    (Smalltalk includesKey:self) ifTrue:[
	super become:anotherObject.
%{
	__rehashSystemDictionaries();
%}.
    ] ifFalse:[
	super become:anotherObject
    ]
!

becomeNil
    "make all references to the receiver become nil - effectively getting
     rid of the receiver. For symbols, this is not allowed, if the receiver
     is used as a key in some SytemDictionary.
     This can be a very dangerous operation - be warned.

     Notice: because of the danger here, this method may report an error
	     in future versions"

    (Smalltalk includesKey:self) ifTrue:[
	self primitiveFailed
    ] ifFalse:[
	super becomeNil
    ]
! !

!Symbol class methodsFor:'binary storage'!

binaryDefinitionFrom: stream manager: manager
    ^ self intern: (super binaryDefinitionFrom: stream manager: manager)
! !

!Symbol methodsFor:'printing & storing'!

printString
    "return a printed representation of the receiver.
     In contrast to ST-80, this does return the symbols characters
     without any leading #. Therefore, you can directly send symbols'
     printStrings to some output device. This is incompatible, but easier
     to use."

"/ ST-80 behavior:
"/  ^ self storeString

    ^ self asString
!

printOn:aStream
    "append a printed representation of the receiver on aStream.
     In contrast to ST-80, this does return the symbols characters
     without any leading #. Therefore, you can directly send symbols'
     printStrings to some output device. This is incompatible, but easier
     to use."

"/ ST-80 behavior:

"/  self storeOn:aStream

    aStream nextPutAll:self
!
 
displayString
    "return a string for displaying the receiver"

    ^ self storeString
!

storeString
    "return a String for storing the receiver"

    (self at:1) isLetter ifTrue:[
	2 to:self size do:[:index |
	    (self at:index) isLetterOrDigit ifFalse:[
		^ '#''' , self , ''''
	    ].
	].
	^ '#' , self
    ].
    ^ '#''' , self , ''''
!

storeOn:aStream
    "store myself on a stream"

    aStream nextPutAll:(self storeString)
! !