UnaryNd.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 03:15:59 +0100
changeset 140 1ef1d1395146
parent 135 aa4f7b8f121e
child 148 ef0e604209ec
permissions -rw-r--r--
checkin from browser

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

MessageNode subclass:#UnaryNode
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'System-Compiler-Support'
!

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

documentation
"
    node for parse-trees, representing unary messages
"
!

version
    ^ '$Header: /cvs/stx/stx/libcomp/Attic/UnaryNd.st,v 1.18 1995-11-23 02:15:16 cg Exp $'
! !

!UnaryNode class methodsFor:'instance creation'!

receiver:r selector:s
    "return a new UnaryNode for sending selector s to receiver r.
     Fold constants."

    ^ self receiver:r selector:s fold:true
!

receiver:r selector:selectorString fold:folding
    "return a new UnaryNode for sending selector selectorString to receiver r.
     If folding is true, fold constant expressions."

    |result recVal selector|

"
    The constant folding code can usually not optimize things - this may change
    when some kind of constant declaration is added to smalltalk.
"
    folding ifTrue:[
	"do constant folding ..."
	r isGlobal ifTrue:[
	    (r name = 'Character') ifTrue:[
		recVal := r evaluate.
		selector := selectorString asSymbolIfInterned.
		selector notNil ifTrue:[
		    (#( tab cr space) includes:selector)
		    ifTrue:[
			(recVal respondsTo:selector) ifTrue:[
			    result := recVal perform:selector.
			    ^ ConstantNode type:(ConstantNode typeOfConstant:result)
					  value:result
			]
		    ]
		]
	    ]
	].
	r isConstant ifTrue:[
	    "check if we can do it ..."
	    recVal := r evaluate.
	    selector := selectorString asSymbolIfInterned.
	    selector notNil ifTrue:[
		(recVal respondsTo:selector) ifTrue:[
		    "
		     we could do much more here - but then, we need a dependency from
		     the folded selectors method to the method we generate code for ...
		     limit optimizations to those that will never change 
		     (or, if you change them, it will crash badly anyway ...)
		    "
		    SignalSet anySignal "Number domainErrorSignal" handle:[:ex |
			"in case of an error, abort fold and return original"
			ex return
		    ] do:[
			recVal respondsToArithmetic ifTrue:[
			    (#( negated abs asPoint degreesToRadians radiansToDegrees
				exp ln log sqrt reciprocal 
				arcCos arcSin arcTan sin cos tan) includes:selector)
			    ifTrue:[
				result := recVal perform:selector.
				^ ConstantNode type:(ConstantNode typeOfConstant:result)
					      value:result
			    ]
			].
			recVal isCharacter ifTrue:[
			    (#( asciiValue asInteger digitValue) includes:selector) 
			    ifTrue:[
				result := recVal perform:selector.
				^ ConstantNode type:(ConstantNode typeOfConstant:result)
					      value:result
			    ]
			].
			recVal isString ifTrue:[
			    (selector == #withCRs) ifTrue:[
				result := recVal perform:selector.
				^ ConstantNode type:(ConstantNode typeOfConstant:result)
					      value:result
			    ]
			].
			(recVal isMemberOf:Array) ifTrue:[
			    (#(asFloatArray asDoubleArray) includes:selector) ifTrue:[
				result := recVal perform:selector.
				^ ConstantNode type:(ConstantNode typeOfConstant:result)
					      value:result
			    ]
			].
			^ (self basicNew) receiver:r selector:selector args:nil lineno:0
		    ].
		    "when we reach here, something went wrong (something like 0.0 log)"
		    ^ 'error occured when evaluating constant expression'
		]
	    ]
	]
    ].
    ^ (self basicNew) receiver:r selector:selectorString args:nil lineno:0
! !

!UnaryNode methodsFor:'checks'!

plausibilityCheck
    "check for funny selector - careful to do string compare instead
     of symbol identity compare: I dont want to introduce these as symbols
     into the system (would make the '... is nowhere implemented' warning
     go away."

    ((selector = 'self') or:[
     (selector = 'super') or:[
     (selector = 'thisContext') or:[
     (selector = 'true') or:[
     (selector = 'false') or:[
     (Smalltalk includesKey:selector)]]]]]) ifTrue:[
	^ 'funny selector; possible missing ''.'' or keyword'
    ].

    "more to come ..."
    ^ nil
! !

!UnaryNode methodsFor:'code generation'!

codeOn:aStream inBlock:b for:aCompiler
    "append bytecode for the receiver to aStream."

    "
     optimize 
	(a == b) not -> (a ~~ b)
	(a ~~ b) not -> (a == b)
    "
    (selector == #not) ifTrue:[
	(receiver class == BinaryNode) ifTrue:[
	    (receiver selector == #==) ifTrue:[
		(BinaryNode receiver:(receiver receiver)
			    selector:#~~
				 arg:(receiver arg)) codeOn:aStream inBlock:b for:aCompiler.
		^ self
	    ].
	    (receiver selector == #~~) ifTrue:[
		(BinaryNode receiver:(receiver receiver)
			    selector:#==
				 arg:(receiver arg)) codeOn:aStream inBlock:b for:aCompiler.
		^ self
	    ]
	]
    ].

    "
     optimize 
	Float pi
    "
    (selector == #pi) ifTrue:[
	(receiver isGlobal) ifTrue:[
	    receiver name = 'Float' ifTrue:[
		aCompiler addLiteral:#Float; addLiteral:selector.
		(ConstantNode type:#Float value:(Float pi))
		    codeOn:aStream inBlock:b for:aCompiler.
		^ self
	    ]
	]
    ].

    ^ super codeOn:aStream inBlock:b for:aCompiler
! !

!UnaryNode methodsFor:'evaluating'!

evaluate
    "evaluate the expression represented by the receiver"

    receiver isSuper ifTrue:[
	^ super evaluate
    ].
    ^ (receiver evaluate) perform:selector
! !

!UnaryNode methodsFor:'printing'!

printOn:aStream indent:i
    "prettyprint the expression represented by the receiver"

    |needParen|

    needParen := false.
    receiver isMessage ifTrue:[
	receiver isUnaryMessage ifFalse:[
	    needParen := true
	].
    ].
    needParen ifTrue:[
	aStream nextPutAll:'('
    ].
    receiver printOn:aStream.
    needParen ifTrue:[
	aStream nextPutAll:') '
    ].
    aStream space.
    selector printString printOn:aStream.
"    aStream space.     "
! !

!UnaryNode methodsFor:'queries'!

isUnaryMessage
    "return true, if this node is one for a unary message"
    ^ true
! !