Symbol.st
author Claus Gittinger <cg@exept.de>
Fri, 08 Jul 2005 19:15:03 +0200
changeset 8913 b9498d27a554
parent 8830 df7adfaf1a57
child 9231 19a4fcc9c300
permissions -rw-r--r--
64bit; mkSmallInteger

"
 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.
"

"{ Package: 'stx:libbasic' }"

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

!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.
"
!

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.

    [author:]
	Claus Gittinger
"
! !

!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

    "Modified: 26.2.1996 / 12:51:38 / cg"
!

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"
%{
    sym = __INTERNSYMBOL(sym, (OBJ *)0, __context);
%}.
    ^ sym
!

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

%{  /* NOCONTEXT */
    OBJ newSymbol;

    if (__isSymbol(aString)) {
	RETURN (aString);
    }
    if (__isString(aString)) {
	newSymbol = __MKSYMBOL(__stringVal(aString), (OBJ *)0);
	if (newSymbol != nil) {
	    RETURN (newSymbol);
	}
    }
%}.
    aString class ~~ String ifTrue:[
	"/
	"/ only allowed to intern strings
	"/
	^ self mustBeString
    ].
    ^ ObjectMemory allocationFailureSignal raise.
!

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

    ^ self intern:(aCharacter asString)
!

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
! !

!Symbol class methodsFor:'Compatibility-ST80'!

tableSize
    "return the size of the systems symbol table"

    "/ claus: I dont know, if the returned value should be exact.
    "/ the number below is just arbitrary ...

    ^ 10000

    "Created: 18.4.1997 / 20:52:20 / cg"
! !

!Symbol class methodsFor:'binary storage'!

binaryDefinitionFrom:stream manager:manager
    "retrieve a symbol from a binary input stream (nonpublic interface)"

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

    "Modified: / 2.11.1997 / 16:17:06 / cg"
! !

!Symbol class methodsFor:'queries'!

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

    ^ aString asSymbolIfInterned
!

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

    ^ aString knownAsSymbol
!

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
!

hasSharedInstances
    "return true if this class has shared instances, that is, instances
     with the same value are identical.
     True returned here - there is only one of each symbol (per contents)."

    ^ true

! !

!Symbol methodsFor:'Compatibility-VW'!

<< catalogID
    "create and return a new UserMessage, with the receiver as key,
     and the argument as cataglogID.
     VW compatibility."

    ^ UserMessage key:self catalogID:catalogID

    "
     (#theFooMessage << #myMessages) 
     (#theFooMessage << #myMessages >> 'cannot read subclass of metaclass') 
     (#theFooMessage >> 'cannot read subclass of metaclass') 
    "
!

>> aString
    "create and return a new UserMessage, with the receiver as key,
     and the argument as defaultString.
     VW compatibility."

    ^ UserMessage key:self defaultString:aString 

    "
     (#theFooMessage << #myMessages) 
     (#theFooMessage << #myMessages >> 'cannot read subclass of metaclass') 
     (#theFooMessage >> 'cannot read subclass of metaclass') 
    "
! !

!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.
     For uninterned symbols, this is allowed."

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

    "Modified: 19.4.1996 / 11:16:10 / cg"
!

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

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

!Symbol methodsFor:'binary storage'!

storeBinaryDefinitionOn:stream manager:manager
    "append a binary representation of the receiver onto stream.
     Redefined since short Symbol can be stored with a special type code 
     in a more compact way.
     This is an internal interface for the binary storage mechanism."

    |myClass myBasicSize|

    "/ not for subclasses with named instVars.
    (myClass := self class) instSize ~~ 0 ifTrue:[
	^ super storeBinaryDefinitionOn:stream manager:manager
    ].

    myBasicSize := self basicSize.

    "/ can use a more compact representation;
    "/ but not for subclasses ...

    ((myClass == Symbol) 
    and:[myBasicSize <= 255]) ifTrue:[
	"/ special encoding: <codeForSymbol> <len> <bytes> ...
	stream nextPut:(manager codeForSymbol); nextPut:myBasicSize.
    ] ifFalse:[
	manager putIdOfClass:myClass on:stream.
	stream nextNumber:4 put:myBasicSize.
    ].
    stream nextPutBytes:myBasicSize from:self startingAt:1.

    "Modified: / 2.11.1997 / 15:28:56 / cg"
    "Created: / 2.11.1997 / 16:13:47 / cg"
! !

!Symbol methodsFor:'comparing'!

= 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
!

identityHash
    "interned symbols can return a better hash key"

%{  /* NOCONTEXT */

    REGISTER unsigned INT g, val;
    REGISTER unsigned char *cp, *ce;
    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 
	     * We have tested 5-bit shifts as well:
	     *
	     * ST/X Symbols:                 17807 
	     * Hashkey collisions (4bit):       14   0.07%
	     * Hashkey collisions (5bit):      300   1.68%
	     */

	    if (l > 0) {
		val = cp[0];
		if (l > 1) {
		    val = (val << 4) + cp[1];
		    if (l > 2) {
			val = (val << 4) + cp[2];
			if (l > 3) {
			    val = (val << 4) + cp[3];
			    if (l > 4) {
				val = (val << 4) + cp[4];
				if (l > 5) {
				    val = (val << 4) + cp[5];
				    if (l > 6) {
					val = (val << 4) + cp[6];
					for (ce = cp + l, cp += 7; cp < ce; cp++) {
					    if (g = (val & 0xF0000000)) {
						val ^= g >> 24;
						val ^= g;
					    }
					    val = (val << 4) + *cp;
					}
				    }
				}
			    }
			}
		    }
		}
	    } else {
		val = 0;
	    }
	    val = (val * 31415821) & 0x3fffffff;
	} else {
	    val = __MAKE_HASH__(val);
	}
	RETURN ( __mkSmallInteger(val) );
     }
%}.
     ^ super identityHash

     "
	|hashColl hashSet|

	hashColl := OrderedCollection new:20000.
	Symbol allInstancesDo:[:instance |
	    hashColl add:instance identityHash
	].
	hashSet := hashColl asSet.

	Transcript showCR:'Symbols: ', hashColl size printString, 
			  ' unique hash keys: ', hashSet size printString,
			  ' collisions:', (hashColl size - hashSet size) printString.
    "
        
!

~= 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:'converting'!

asString
    "return a string with printname taken from mine"

%{  /* NOCONTEXT */
    OBJ s;

    s = __MKSTRING_ST(self);
    if (s != nil) {
        RETURN (s);
    }
%}.
    ^ (String new:(self size))
        replaceFrom:1 with:self startingAt:1
!

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
! !

!Symbol methodsFor:'copying'!

copy
    "return a copy of myself
     - reimplemented here since symbols are immutable."

     ^ self
!

copyReplaceAll:oldElement with:newElement
    "return a copy of the receiver as a string, where all elements equal to oldElement
     have been replaced by newElement."

"/    'Warning: #copyReplaceAll:with: will change semantics as defined in ANSI soon' errorPrintCR.
    ^ self asString replaceAll:oldElement with:newElement

    "Created: / 18.7.1998 / 23:03:38 / cg"
!

copyReplacing:oldElement withObject:newElement
    "return a copy of the receiver, where all elements equal to oldElement
     have been replaced by newElement.
     ANSI version of what used to be #copyReplaceAll:with:"

    ^ self asString replaceAll:oldElement with:newElement
!

deepCopy
    "return a copy of myself
     - reimplemented here since symbols are immutable."

     ^ self
!

deepCopyUsing:aDictionary
    "return a deep copy of myself
     - reimplemented here since symbols are immutable."

     ^ self
!

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

     ^ self
!

simpleDeepCopy
    "return a copy of myself
     - reimplemented here since symbols are immutable."

     ^ self
! !

!Symbol methodsFor:'printing & storing'!

displayString
    "return a string for displaying the receiver"

    ^ self storeString
!

printOn:aStream
    "append a user printed representation of the receiver to aStream.
     The format is suitable for a human - not meant to be read back.

     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
!

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
!

storeArrayElementOn:aStream
    "store myself on a stream.
     I am stored as an array element, so the '#' may be omitted sometimes.
     Take care for special symbols"

    |storeString|

    storeString := self storeString.
    (self == #true or:[self == #false or:[self == #nil or:[(storeString at:2) == $']]]) ifTrue:[
        aStream nextPutAll:storeString.
    ] ifFalse:[
        aStream nextPutAll:self.
    ].
!

storeOn:aStream
    "store myself on a stream"

    aStream nextPutAll:(self storeString)
!

storeString
    "return a String for storing the receiver"

    |sz "{Class: SmallInteger }" 
     c anyColon|

    sz := self size.
    (sz ~~ 0 and:[(self at:1) isLetter]) ifTrue:[
        anyColon := false.
        2 to:sz do:[:index |
            c := self at:index.
            c == $: ifTrue:[
                (index == sz or:[(self at:(index+1)) isLetterOrDigit]) ifFalse:[
                    ^ '#' , super storeString.
                ].
                anyColon := true.
            ] ifFalse:[
                c isLetterOrDigit ifFalse:[
                    ^ '#' , super storeString 
                ].
            ].
        ].
        "no colon in symbol or symbol ends with a colon"
        (anyColon and:[c ~~ $:]) ifFalse:[
            ^ '#' , self
        ].
    ].
    ^ '#' , super storeString

    "
      #'abc'       storeString     
      #'abc:'      storeString     
      #'abc:def:'  storeString     
      #'abc:def'   storeString            
      #'abc::def'  storeString     
      #'abc &^*'   storeString  
      #'abcdef::'  storeString  
      #'hello''world'  storeString  
      #'' storeString               
      #'''' storeString               
      #'_hello' storeString     
      #'123'  storeString  
    "
! !

!Symbol methodsFor:'queries'!

isInfix
    "return true, if the receiver is a binary message selector"

    ^ self first isLetterOrDigit not

    "
     #at:put: isInfix  
     #at: isInfix      
     #+ isInfix        
     #size isInfix     
    "

    "Created: / 1.11.1997 / 12:34:55 / cg"
    "Modified: / 1.11.1997 / 12:36:37 / cg"
!

isKeyword
    "return true, if the receiver is a keyword message selector"

    ^ self includes:$:

    "
     #at:put: isKeyword  
     #at: isKeyword      
     #+ isKeyword        
     #size isKeyword     
    "

    "Created: / 1.11.1997 / 12:34:55 / cg"
    "Modified: / 1.11.1997 / 12:36:37 / cg"
!

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

    ^ true
!

keywords
    "assuming the receiver is a keyword message selector,
     return the individual keywords (i.e. break it up at colons)
     and return these as a collection.
     For binary and unary selectors, the result may be nonsense."

    |coll s part|

    coll := OrderedCollection new.
    s := ReadStream on:self.
    [s atEnd] whileFalse:[
	part := s through:$:.
	coll add:part
    ].
    ^ coll asArray

    "
     #at:put: keywords  
     #at: keywords      
     #+ keywords        
     #size keywords     
    "
!

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

    ^ String
! !

!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 SystemDictionary.
     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 methodsFor:'tracing'!

traceInto:aRequestor level:level from:referrer
    "double dispatch into tracer, passing my type implicitely in the selector"

    ^ aRequestor traceSymbol:self level:level from:referrer


! !

!Symbol methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter

    ^ aVisitor visitSymbol:self with:aParameter
! !

!Symbol class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Symbol.st,v 1.80 2005-07-08 17:15:03 cg Exp $'
! !