ConstantNode.st
author claus
Thu, 16 Feb 1995 17:27:24 +0100
changeset 62 a8e1828867a8
parent 47 f861ad42703e
child 96 ae3b3d960476
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 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.
"

PrimaryNode subclass:#ConstantNode
       instanceVariableNames:''
       classVariableNames:'TrueNode FalseNode NilNode Const0Node Const1Node
			   Float0Node'
       poolDictionaries:''
       category:'System-Compiler-Support'
!

ConstantNode comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libcomp/ConstantNode.st,v 1.10 1995-02-16 16:27:15 claus Exp $
'!

!ConstantNode class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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/libcomp/ConstantNode.st,v 1.10 1995-02-16 16:27:15 claus Exp $
"
!

documentation
"
    node for parse-trees, representing literal constants
"
! !

!ConstantNode class methodsFor:'queries'!

typeOfConstant:anObject
    "return the constantNode type for an object"

    "the most common case first ..."

    (anObject isMemberOf:SmallInteger) ifTrue:[
	^ #Integer
    ].

    anObject isNumber ifTrue:[
	"the most common case first ..."
	(anObject isMemberOf:Float) ifTrue:[
	    ^ #Float
	].
	anObject isInteger ifTrue:[
	    ^ #Integer
	].
    ].
    anObject isNil ifTrue:[
	^ #Nil
    ].
    (anObject == true) ifTrue:[
	^ #True
    ].
    (anObject == false) ifTrue:[
	^ #False
    ].
    ^ #Literal
! !

!ConstantNode class methodsFor:'instance creation'!

type:t value:val
    "some constant nodes are used so often, its worth caching them"
    (t == #True) ifTrue:[
	TrueNode isNil ifTrue:[
	    TrueNode := (self basicNew) type:t value:val
	].
	^ TrueNode
    ].
    (t == #False) ifTrue:[
	FalseNode isNil ifTrue:[
	    FalseNode := (self basicNew) type:t value:val
	].
	^ FalseNode
    ].
    (t == #Nil) ifTrue:[
	NilNode isNil ifTrue:[
	    NilNode := (self basicNew) type:t value:val
	].
	^ NilNode
    ].
    (t == #Integer) ifTrue:[
	(val == 0) ifTrue:[
	    Const0Node isNil ifTrue:[
		Const0Node := (self basicNew) type:t value:val
	    ].
	    ^ Const0Node
	].
	(val == 1) ifTrue:[
	    Const1Node isNil ifTrue:[
		Const1Node := (self basicNew) type:t value:val
	    ].
	    ^ Const1Node
	]
    ].
    (t == #Float) ifTrue:[
	(val = 0.0) ifTrue:[
	    Float0Node isNil ifTrue:[
		Float0Node := (self basicNew) type:t value:val
	    ].
	    ^ Float0Node
	]
    ].
    ^ (self basicNew) type:t value:val
! !

!ConstantNode methodsFor:'accessing'!

type:t value:val
    type := t.
    value := val
! !

!ConstantNode methodsFor:'queries'!

isConstant
    ^ true
! !

!ConstantNode methodsFor:'evaluating'!

evaluate
    ^ value
!

store:aValue
    "not reached - parser checks for this"

    self error:'store not allowed'.
    ^ aValue
! !

!ConstantNode methodsFor:'code generation'!

codeOn:aStream inBlock:b
    "generated code for the constant"

    (type == #Integer) ifTrue:[
	(value between: -128 and:127) ifTrue:[
	    (value == 0) ifTrue:[
		aStream nextPut:#push0. ^ self
	    ].
	    (value == 1) ifTrue:[
		aStream nextPut:#push1. ^ self
	    ].
	    (value == 2) ifTrue:[
		aStream nextPut:#push2. ^ self
	    ].
	    (value == -1) ifTrue:[
		aStream nextPut:#pushMinus1. ^ self
	    ].
	    aStream nextPut:#pushNum.
	    aStream nextPut:value.
	    ^ self
	].
	(value between:16r-8000 and:16r7FFF) ifTrue:[
	    aStream nextPut:#pushNum16.
	    aStream nextPut:value.
	    aStream nextPut:0. 
	    ^ self
	]
    ].
    (type == #Nil) ifTrue:[
	aStream nextPut:#pushNil. ^ self
    ].
    (type == #True) ifTrue:[
	aStream nextPut:#pushTrue. ^ self
    ].
    (type == #False) ifTrue:[
	aStream nextPut:#pushFalse. ^ self
    ].
    aStream nextPut:#pushLit.
    aStream nextPut:value
!

codeStoreOn:aStream inBlock:codeBlock valueNeeded:valueNeeded
    "not sent - parser checks for this"

    ^ self error:'assignment to literals not allowed'
! !

!ConstantNode methodsFor:'printing'!

displayString
    ^ value displayString
!

printOn:aStream indent:i
    value storeOn:aStream
! !