UnaryNd.st
author Stefan Vogel <sv@exept.de>
Fri, 06 Mar 1998 16:38:37 +0100
changeset 657 0ecf1ff6f6bf
parent 626 7192fcd0a851
child 711 25b9a501b97d
permissions -rw-r--r--
Fix #makeMethod:

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

'From Smalltalk/X, Version:3.2.1 on 23-oct-1997 at 2:05:56 pm'                  !

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
    This is a helper class for the compiler.

    [author:]
        Claus Gittinger
"
! !

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

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 canFold globalName|

"
    The constant folding code can usually not optimize things - this may change
    when some kind of constant declaration is added to smalltalk.
"

    canFold := false.

    folding notNil ifTrue:[
        selector := selectorString asSymbolIfInterned.
        selector notNil ifTrue:[
            "/
            "/ do constant folding ...
            "/
            r isGlobal ifTrue:[
                globalName := r name.
                recVal := r evaluate.

                (globalName = 'Character') ifTrue:[
                    ( #( tab cr space backspace esc ) includes:selector)
                    ifTrue:[
                        canFold := true
                    ]
                ].
                (globalName = 'Float') ifTrue:[
                    ( #( pi unity zero ) includes:selector)
                    ifTrue:[
                        (recVal respondsTo:selector) ifTrue:[
                            canFold := true
                        ]
                    ]
                ].
"/ no, this 'optimization' is not good -
"/ if bytecode is transported to another machine.
"/ However, the JIT compiler compensates for this ;-)
"/                (globalName = 'SmallInteger') ifTrue:[
"/                    ( #( minVal maxVal ) includes:selector)
"/                    ifTrue:[
"/                        (recVal respondsTo:selector) ifTrue:[
"/                            canFold := true
"/                        ]
"/                    ]
"/                ]
            ].

            r isConstant ifTrue:[
                "check if we can do it ..."
                recVal := r evaluate.

                "
                 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 ...)
                "
                recVal respondsToArithmetic ifTrue:[
                    (#( negated abs asPoint degreesToRadians radiansToDegrees
                        exp ln log sqrt reciprocal 
                        arcCos arcSin arcTan sin cos tan) includes:selector)
                    ifTrue:[
                        canFold := true
                    ]
                ].
                recVal isCharacter ifTrue:[
                    (#( asciiValue asInteger digitValue) includes:selector) 
                    ifTrue:[
                        canFold := true
                    ]
                ].
                recVal isString ifTrue:[
                    (selector == #withCRs) ifTrue:[
                        canFold := (folding >= #level2) or:[folding == #full]
                    ]
                ].
                (recVal isMemberOf:Array) ifTrue:[
                    (#(asFloatArray asDoubleArray) includes:selector) ifTrue:[
                        canFold := (folding >= #level2) or:[folding == #full]
                    ]
                ]
            ]
        ].

        canFold ifTrue:[
            (recVal respondsTo:selector) ifTrue:[
                SignalSet anySignal "Number domainErrorSignal" handle:[:ex |
                    "in case of an error, abort fold and return original"
                    ex return
                ] do:[
                    result := recVal perform:selector.
                    ^ ConstantNode type:(ConstantNode typeOfConstant:result) value:result
                ].
                "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

    "Modified: 21.10.1997 / 19:10:01 / cg"
! !

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

    |rSel notSelector|

    "
     optimize 
        (a == b) not -> (a ~~ b)
        (a ~~ b) not -> (a == b)
    "
    (selector == #not) ifTrue:[
        (receiver class == BinaryNode) ifTrue:[
            ((rSel := receiver selector) == #==) ifTrue:[
                notSelector := #~~
            ] ifFalse:[
                (rSel == #~~) ifTrue:[
                    notSelector := #==
                ]
            ].
            notSelector notNil ifTrue:[
                (BinaryNode receiver:(receiver receiver)
                            selector:notSelector
                                 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

    "Modified: 23.10.1997 / 02:04:51 / cg"
! !

!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

    "Modified: 23.10.1997 / 02:05:18 / cg"
! !

!UnaryNode class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/Attic/UnaryNd.st,v 1.24 1997-10-23 14:33:29 cg Exp $'
! !