MessageNd.st
author Claus Gittinger <cg@exept.de>
Sat, 09 Dec 1995 23:10:33 +0100
changeset 163 9a7dfd547e69
parent 148 ef0e604209ec
child 166 9f6c57a3bce1
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.
"

ParseNode subclass:#MessageNode
	 instanceVariableNames:'receiver selector argArray lineNr'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'System-Compiler-Support'
!

!MessageNode 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 message sends
"
! !

!MessageNode class methodsFor:'instance creation'!

receiver:recNode selector:selectorString 
    ^ (self basicNew) receiver:recNode selector:selectorString args:nil lineno:0
!

receiver:recNode selector:selectorString arg1:argNode1 arg2:argNode2 fold:folding
    |result recVal argVal selector|

    "
     This is just a demonstration - of how complex constants can be folded.
     This was inspired by some discussion in c.l.s about enhancing the language - I prefer
     enhancing the compiler ....
     The following optimization will convert '#(...) with:#(...) collect:[...]' into an array constant,
     allowing a constant arrays of complex objects.

     Notice: this method is normally disabled - its just a demo after all.
    "
    folding ifTrue:[
	"do constant folding ..."
	(recNode isConstant and:[argNode1 isConstant]) ifTrue:[
	    "check if we can do it ..."
	    selector := selectorString asSymbolIfInterned.
	    selector notNil ifTrue:[
		recVal := recNode evaluate.
		(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 - you will crash so bad ...)
		    "
		    argVal := argNode1 evaluate.
		    ((recVal isMemberOf:Array) and:[argVal isMemberOf:Array]) ifTrue:[
			(selector == #with:collect:) ifTrue:[
			    (argNode2 isMemberOf:BlockNode) ifTrue:[
				(SignalSet anySignal catch:[
				    result := recVal perform:selector with:argVal with:(argNode2 evaluate).
				]) ifTrue:[
				    ^ 'error in constant expression'
				].
				^ ConstantNode type:(ConstantNode typeOfConstant:result) value:result
			    ]
			]
		    ]
		]
	    ]
	]
    ].
    ^ (self basicNew) receiver:recNode selector:selectorString args:(Array with:argNode1 with:argNode2) lineno:0
!

receiver:recNode selector:selectorString arg:argNode
    ^ self receiver:recNode selector:selectorString arg:argNode fold:true
!

receiver:recNode selector:selectorString arg:argNode fold:folding
    |result recVal argVal selector canFold|

   "
     The constant folding code can usually not optimize much
     - this may change when some kind of constant/macro declaration is added to smalltalk.
    "
    folding ifTrue:[
	"do constant folding ..."
	(recNode isConstant and:[argNode isConstant]) ifTrue:[
	    "check if we can do it ..."
	    selector := selectorString asSymbolIfInterned.
	    selector notNil ifTrue:[
		recVal := recNode evaluate.
		(recVal respondsTo:selector) ifTrue:[
		    canFold := false.
		    "
		     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 - you will crash so bad ...)
		    "
		    argVal := argNode evaluate.
		    (recVal respondsToArithmetic and:[argVal respondsToArithmetic]) ifTrue:[
			(#( @ + - * / // \\ min: max: quo:) includes:selector) ifTrue:[
			    (#( / // \\ ) includes:selector) ifTrue:[
				argVal = 0 ifTrue:[
				    ^ 'division by zero in constant expression'
				].
			    ].
			    canFold := true
			]
		    ].
		    (recVal isMemberOf:String) ifTrue:[
			(argVal isInteger and:[selector == #at:]) ifTrue:[
			    canFold := true
			].
			((argVal isMemberOf:String) and:[selector == #',']) ifTrue:[
			    canFold := true
			]
		    ].
		    canFold ifTrue:[
			(SignalSet anySignal catch:[
			    result := recVal perform:selector with:argVal.
			]) ifTrue:[
			    ^ 'error in constant expression'
			].
			^ ConstantNode type:(ConstantNode typeOfConstant:result) value:result
		    ]
		]
	    ]
	].
	"
	 the folloing optimization cannot be done (although it would be nice)
	 since the array may be modified later.
	"
"/      (recNode isGlobal and:[argNode isConstant])ifTrue:[
"/          selectorString knownAsSymbol ifTrue:[
"/              selector := selectorString asSymbol.
"/              recVal := recNode evaluate.
"/              (recVal respondsTo:selector) ifTrue:[
"/                  (recVal == FloatArray) ifTrue:[
"/                      argVal := argNode evaluate.
"/                      (argVal isMemberOf:Array) ifTrue:[
"/                          (SignalSet anySignal catch:[
"/                              result := recVal perform:selector with:argVal with:argVal.
"/                          ]) ifTrue:[
"/                              ^ 'error in constant expression'
"/                          ].
"/                          ^ ConstantNode type:(ConstantNode typeOfConstant:result) value:result
"/                      ]
"/                  ]
"/              ]
"/          ]
"/      ]
    ].
    ^ (self basicNew) receiver:recNode selector:selectorString args:(Array with:argNode) lineno:0
!

receiver:recNode selector:selectorString args:anArray
    ^ self receiver:recNode selector:selectorString args:anArray fold:true
!

receiver:recNode selector:selectorString args:argArray fold:folding
    |numArgs|

    numArgs := argArray size.
    folding ifTrue:[
	(numArgs == 1) ifTrue:[
	    ^ self receiver:recNode selector:selectorString arg:(argArray at:1) fold:true 
	].

	"uncomment the follwoing for a nice array initializer optimization ..."
"/        (numArgs == 2) ifTrue:[
"/            ^ self receiver:recNode selector:selectorString arg1:(argArray at:1) arg2:(argArray at:2) fold:true 
"/        ].
	numArgs > Method maxNumberOfArguments ifTrue:[
	    ^ 'too many arguments for current VM implementation'.
	].
    ].

    ^ (self basicNew) receiver:recNode selector:selectorString args:argArray lineno:0

    "Modified: 3.9.1995 / 16:41:39 / claus"
! !

!MessageNode class methodsFor:'queries'!

hasLineNumber:sel
    "return true, if special send code needs lineNr"

    (sel == #==) ifTrue:[^ false].
    (sel == #~~) ifTrue:[^ false].
    (sel == #class) ifTrue:[^ false].
    (sel == #isNil) ifTrue:[^ false].
    (sel == #notNil) ifTrue:[^ false].
    ^ true
!

isBuiltIn1ArgSelector:sel
    "return true, if selector sel is built-in.
     (i.e. there is a single bytecode for it)"

    (sel == #at:) ifTrue:[^ true].
    (sel == #value:) ifTrue:[^ true].
    (sel == #bitAnd:) ifTrue:[^ true].
    (sel == #bitOr:) ifTrue:[^ true].
    (sel == #new:) ifTrue:[^ true].
    (sel == #basicNew:) ifTrue:[^ true].
    ^ false
!

isBuiltIn2ArgSelector:sel
    "return true, if selector sel is built-in.
     (i.e. there is a single bytecode for it)"

    (sel == #at:put:) ifTrue:[^ true].
    ^ false
!

isBuiltInUnarySelector:sel
    "return true, if unary selector sel is built-in. 
     (i.e. there is a single bytecode for it)"

    (sel == #peek) ifTrue:[^ true].
    (sel == #value) ifTrue:[^ true].
    (sel == #next) ifTrue:[^ true].
    (sel == #class) ifTrue:[^ true].
    (sel == #size) ifTrue:[^ true].
    (sel == #x) ifTrue:[^ true].
    (sel == #y) ifTrue:[^ true].
    (sel == #width) ifTrue:[^ true].
    (sel == #height) ifTrue:[^ true].
    (sel == #origin) ifTrue:[^ true].
    (sel == #extent) ifTrue:[^ true].
    (sel == #asInteger) ifTrue:[^ true].
    (sel == #rounded) ifTrue:[^ true].
    (sel == #isNil) ifTrue:[^ true].
    (sel == #notNil) ifTrue:[^ true].
    (sel == #not) ifTrue:[^ true].
    (sel == #new) ifTrue:[^ true].
    (sel == #basicNew) ifTrue:[^ true].
    ^ false
! !

!MessageNode methodsFor:'accessing'!

arg1
    ^ argArray at:1
!

args
    ^ argArray
!

lineNumber
     ^ lineNr
!

lineNumber:num
     lineNr := num
!

receiver
    ^ receiver
!

receiver:r selector:s args:a lineno:l
    receiver := r.
    selector := s asSymbol.
    argArray := a.
    lineNr := l
!

selector
    ^ selector
! !

!MessageNode methodsFor:'checks'!

plausibilityCheck
    |rec arg operand|

    "
     it once took me almost an hour, to find a '==' which
     should have been an '=' (you cannot compare floats with ==)
     (well, I looked at the '==' at least 50 times -
      - but didn't think about it ...).
     thats reason enough to add this check here.
     I will add more as heuristic knowledge increases ...
     (send me comments on common programming errors ...)
    "

    "
     check #== appled to Floats, Strings or Fractions
    "
    ((selector == #==) or:[selector == #~~]) ifTrue:[
	receiver isConstant ifTrue:[
	    rec := receiver evaluate.
	    ((rec isMemberOf:String) or:[
	     (rec isMemberOf:Float) or:[
	     (rec isMemberOf:Fraction)]]) ifTrue:[
		operand := rec
	    ].
	].
	(argArray at:1) isConstant ifTrue:[
	    arg := (argArray at:1) evaluate.
	    ((arg isMemberOf:String) or:[
	     (arg isMemberOf:Float) or:[
	     (arg isMemberOf:Fraction)]]) ifTrue:[
		operand := arg
	    ].
	].
	operand notNil ifTrue:[
	    (selector == #==) ifTrue:[
		^ 'identity compare is unsafe here'
	    ].
	    ^ 'identity compare will usually return true here'
	]
    ].

    "
     [...] ifTrue:...
     an error often occuring when you are a beginner ...
    "
    ((selector == #ifTrue:) or:[selector == #ifFalse:]) ifTrue:[
	receiver isBlock ifTrue:[
	    (Block canUnderstand:selector) ifFalse:[
		^ 'blocks usually do not respond to ' , selector , ' messages'
	    ].
	].
	(argArray at:1) isBlock ifFalse:[
	    ^ 'will fail at runtime, if argument to ' , selector , ' does not evaluate to a block'
	]
    ].
    ((selector == #ifTrue:ifFalse:) or:[selector == #ifFalse:ifTrue:]) ifTrue:[
	receiver isBlock ifTrue:[
	    (Block canUnderstand:selector) ifFalse:[
		^ 'blocks usually do not respond to ' , selector , ' messages'
	    ].
	].
	(argArray at:1) isBlock ifFalse:[
	    ^ 'will fail at runtime, if 1st. argument to ' , selector , ' does not evaluate to a block'
	].
	(argArray at:2) isBlock ifFalse:[
	    ^ 'will fail at runtime, if 2nd. argument to ' , selector , ' does not evaluate to a block'
	]
    ].

    "
     (...) whileTrue:[
    "
    ((selector == #whileTrue:) or:[selector == #whileFalse:]) ifTrue:[
	receiver isBlock ifFalse:[
	    "
	     only warn, if code was originally parenthized
	    "
	    receiver parenthized ifTrue:[
		^ 'will fail at runtime, if receiver of ' , selector , ' does not evaluate to a block'
	    ]
	].
	(argArray at:1) isBlock ifFalse:[
	    ^ 'will fail at runtime, if argument to ' , selector , ' does not evaluate to a block'
	].
    ].
    ^ nil
! !

!MessageNode methodsFor:'code generation'!

XXcodeWhileOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for [...] whilexxx:[ ... ]"

    |pos pos2 theReceiver theArg theByteCode optByteCode|

    (selector == #whileTrue:) ifTrue:[
	theByteCode := #falseJump
    ] ifFalse:[
	theByteCode := #trueJump
    ].

    theReceiver := receiver.
    optByteCode := self optimizedConditionFor:theReceiver with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := receiver statements expression arg1
	].
	theReceiver := receiver statements expression receiver.
	theByteCode := optByteCode
    ].

    valueNeeded ifTrue:[aStream nextPut:#pushNil].
    pos := aStream position.
    optByteCode notNil ifTrue:[
	theReceiver codeOn:aStream inBlock:b for:aCompiler.
	theArg notNil ifTrue:[
	    theArg codeOn:aStream inBlock:b for:aCompiler
	]
    ] ifFalse:[
	theReceiver codeInlineOn:aStream inBlock:b for:aCompiler
    ].

    (lineNr between:1 and:255) ifTrue:[
	aStream nextPut:#lineno; nextPut:lineNr.
    ].

    aStream nextPut:theByteCode.
    pos2 := aStream position.
    aStream nextPut:0.
    valueNeeded ifTrue:[aStream nextPut:#drop].
    (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
    aStream nextPut:#jump; nextPut:pos.
    (aStream contents) at:pos2 put:(aStream position).
!

codeAndIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for (x and:[y]) ifxxx:[ ... ]"

    |theByteCode optByteCode theReceiver theArg pos1 pos2 pos3 code here jmp|


    theByteCode := #falseJump.
    theReceiver := receiver receiver.

    optByteCode := self optimizedConditionFor:theReceiver
					 with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := theReceiver arg1
	].
	theReceiver := theReceiver receiver.
	theByteCode := optByteCode
    ].
    theReceiver codeOn:aStream inBlock:b for:aCompiler.
    theArg notNil ifTrue:[
	theArg codeOn:aStream inBlock:b for:aCompiler
    ].
    aStream nextPut:theByteCode.
    pos1 := aStream position.
    aStream nextPut:0.

    theReceiver := receiver arg1.
    theReceiver codeInlineOn:aStream inBlock:b for:aCompiler.
    (selector == #ifTrue:) ifTrue:[
	jmp := #falseJump
    ] ifFalse:[
	jmp := #trueJump
    ].
    aStream nextPut:jmp.
    pos2 := aStream position.
    aStream nextPut:0.

    code := aStream contents.
    (selector == #ifFalse:) ifTrue:[
	code at:pos1 put:(aStream position)
    ].
    (argArray at: 1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.

    valueNeeded ifTrue:[
	aStream nextPut:#jump.
	pos3 := aStream position.
	aStream nextPut:0.
	here := aStream position.
	(selector == #ifTrue:) ifTrue:[
	    code at:pos1 put:here
	].
	code at:pos2 put:here.
	aStream nextPut:#pushNil.
	code at:pos3 put:(aStream position)
    ] ifFalse:[
	here := aStream position.
	(selector == #ifTrue:) ifTrue:[
	    code at:pos1 put:here
	].
	code at:pos2 put:here
    ]
!

codeAndOrOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for x and/or:[y] - but not in an if"

    |pos theReceiver theByteCode|

self halt:'not yet implemented'.
    theReceiver := receiver.
    (selector == #and:) ifTrue:[
        theByteCode := #falseJump
    ] ifFalse:[
        theByteCode := #trueJump
    ].
"
    (self canOptimizeConditionFor:receiver) ifTrue:[
        theByteCode := self optimizedConditionFor:theReceiver
                                             with:theByteCode.
        theReceiver := theReceiver receiver
    ].
"
    theReceiver codeOn:aStream inBlock:b for:aCompiler.
    aStream nextPut:theByteCode.
    pos := aStream position.
    aStream nextPut:0.
    (argArray at: 1) codeInlineOn:aStream inBlock:b for:aCompiler.
    (aStream contents) at:pos put:(aStream position).
    valueNeeded ifFalse:[aStream nextPut:#drop]

    "Created: 9.12.1995 / 23:05:52 / cg"
!

codeForCascadeOn:aStream inBlock:b for:aCompiler
    "like codeOn, but always leave the receiver instead of the result"

    |nargs isBuiltIn code litIndex|

    argArray isNil ifTrue:[
	nargs := 0
    ] ifFalse:[
	nargs := argArray size
    ].

    isBuiltIn := false.

    (nargs == 0) ifTrue:[
	isBuiltIn := self class isBuiltInUnarySelector:selector
    ].
    (nargs == 1) ifTrue:[
	isBuiltIn := self class isBuiltIn1ArgSelector:selector
    ].
    (nargs == 2) ifTrue:[
	isBuiltIn := self class isBuiltIn2ArgSelector:selector
    ].

    receiver codeOn:aStream inBlock:b for:aCompiler.
    aStream nextPut:#dup.

    "can we use a send-bytecode ?"
    isBuiltIn ifTrue:[
	receiver isSuper ifFalse:[
	    (nargs > 0) ifTrue:[
		(argArray at:1) codeOn:aStream inBlock:b for:aCompiler.
		(nargs > 1) ifTrue:[
		    (argArray at:2) codeOn:aStream inBlock:b for:aCompiler
		]
	    ].
	    aStream nextPut:selector.
	    (self class hasLineNumber:selector) ifTrue:[
		aStream nextPut:lineNr.
	    ].
	    aStream nextPut:#drop.
	    ^ self
	]
    ].

    "no - generate a send"
    argArray notNil ifTrue:[
	argArray do:[:arg |
	    arg codeOn:aStream inBlock:b for:aCompiler
	]
    ].
    litIndex := aCompiler addLiteral:selector.
    litIndex <= 255 ifTrue:[
	receiver isSuper ifTrue:[
	    receiver isHere ifTrue:[
		code := #hereSend
	    ] ifFalse:[
		code := #superSend.
	    ].
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:nargs; nextPut:nil; nextPut:#drop.
	    ^ self
	].
	(nargs <= 3) ifTrue:[
	    code := #(sendDrop0 sendDrop1 sendDrop2 sendDrop3) at:(nargs+1).
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex.
	    ^ self
	].

	aStream nextPut:#sendDrop; nextPut:lineNr; nextPut:litIndex; nextPut:nargs.
	^ self
    ].
    "need 16bit litIndex"
    receiver isSuper ifTrue:[
	receiver isHere ifTrue:[
	    code := #hereSendL
	] ifFalse:[
	    code := #superSendL.
	].
	aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs; nextPut:nil; nextPut:#drop.
	^ self
    ].
    aStream nextPut:#sendDropL; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs
!

codeForSideEffectOn:aStream inBlock:b for:aCompiler
    self codeOn:aStream inBlock:b valueNeeded:false for:aCompiler
!

codeIfElseOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for x ifxxx:[ ... ] yyy:[ ...]"

    |pos pos2 theReceiver theArg theByteCode optByteCode subsel code|

    theReceiver := receiver.

"
    (theReceiver isMessage) ifTrue:[
	subsel := theReceiver selector.
	(subsel == #and:) ifTrue:[
	    self codeAndIfElseOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	    ^ self
	].
	(subsel == #or:) ifTrue:[
	    self codeOrIfElseOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	    ^ self
	]
    ].
"
    (selector == #ifTrue:ifFalse:) ifTrue:[
	theByteCode := #falseJump
    ] ifFalse:[
	(selector == #ifFalse:ifTrue:) ifTrue:[
	    theByteCode := #trueJump
	]
    ].
    optByteCode := self optimizedConditionFor:theReceiver
					 with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := theReceiver arg1
	].
	theReceiver := theReceiver receiver.
	theByteCode := optByteCode
    ].
    theByteCode notNil ifTrue:[
	theReceiver codeOn:aStream inBlock:b for:aCompiler.
	theArg notNil ifTrue:[
	    theArg codeOn:aStream inBlock:b for:aCompiler
	].

	(lineNr between:1 and:255) ifTrue:[
	    aStream nextPut:#lineno; nextPut:lineNr.
	].

	aStream nextPut:theByteCode.
	pos := aStream position.
	aStream nextPut:0.
	(argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	aStream nextPut:#jump.
	pos2 := aStream position.
	aStream nextPut:0.
	code := aStream contents.
	code at:pos put:(aStream position).
	(argArray at:2) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	code at:pos2 put:(aStream position)
    ]
!

codeIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for x ifxxx:[ ... ]"

    |pos pos2 theReceiver theArg theByteCode optByteCode subsel code
     needLineNr|

    theReceiver := receiver.

    (theReceiver isMessage) ifTrue:[
	subsel := theReceiver selector.
	(subsel == #and:) ifTrue:[
	    self codeAndIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	    ^ self
	].
	(subsel == #or:) ifTrue:[
	    self codeOrIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
	    ^ self
	]
    ].
    (selector == #ifTrue:) ifTrue:[
	theByteCode := #falseJump
    ] ifFalse:[
	theByteCode := #trueJump
    ].
    optByteCode := self optimizedConditionFor:theReceiver
					 with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := theReceiver arg1
	].
	theReceiver := theReceiver receiver.
	theByteCode := optByteCode
    ].

    theReceiver codeOn:aStream inBlock:b for:aCompiler.
    theArg notNil ifTrue:[
	theArg codeOn:aStream inBlock:b for:aCompiler
    ].

    needLineNr := true.
    theArg isNil ifTrue:[
	theReceiver isMessage ifTrue:[
	    (self class hasLineNumber:(theReceiver selector)) ifTrue:[
		theReceiver lineNumber == lineNr ifTrue:[
		    needLineNr := false
		]
	    ]
	]
    ].

    needLineNr ifTrue:[
	(lineNr between:1 and:255) ifTrue:[
	    aStream nextPut:#lineno; nextPut:lineNr.
	]
    ].

    aStream nextPut:theByteCode.
    pos := aStream position.
    aStream nextPut:0.
    (argArray at: 1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.

    code := aStream contents.
    valueNeeded ifTrue:[
	aStream nextPut:#jump.
	pos2 := aStream position.
	aStream nextPut:0.
	code at:pos put:(aStream position).
	aStream nextPut:#pushNil.
	code at:pos2 put:(aStream position)
    ] ifFalse:[
	code at:pos put:(aStream position)
    ]
!

codeOn:aStream inBlock:b for:aCompiler
    self codeOn:aStream inBlock:b valueNeeded:true for:aCompiler
!

codeOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    |recType nargs isBuiltIn litIndex cls clsLitIndex code|

    argArray isNil ifTrue:[
	nargs := 0
    ] ifFalse:[
	nargs := argArray size
    ].

    isBuiltIn := false.
    recType := receiver type.

    (nargs == 0) ifTrue:[
	(recType == #ThisContext) ifTrue:[
	    valueNeeded ifFalse:[
		"for now, only do it in methods"
		b isNil ifTrue:[
		    (selector == #restart) ifTrue:[
			aStream nextPut:#jump; nextPut:1.      "jump to start"
			^ self
		    ].
		].
		(selector == #return) ifTrue:[  "^ nil"
		    aStream nextPut:#retNil.
		    ^ self
		].
	    ]
	].

	receiver isBlock ifTrue:[
	    selector == #value ifTrue:[
		receiver codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
		^ self
	    ].
	].
	isBuiltIn := self class isBuiltInUnarySelector:selector
    ].

    (nargs == 1) ifTrue:[
	(recType == #ThisContext) ifTrue:[
	    valueNeeded ifFalse:[
		(selector == #return:) ifTrue:[
		    (argArray at:1) codeOn:aStream inBlock:b for:aCompiler.  "^ value"
		    aStream nextPut:#retTop.
		    ^ self
		].
	     ].
	].

	((argArray at:1) isBlock) ifTrue:[
	    ((selector == #ifTrue:) or:[selector == #ifFalse:]) ifTrue:[
		receiver isBlock ifFalse:[
		    self codeIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
		    ^ self
		].
	    ].
"
	    ((selector == #and:) or:[selector == #or:]) ifTrue:[
		self codeAndOrOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
		^ self
	    ].
"
	    (selector == #timesRepeat:) ifTrue:[
		(receiver isConstant and:[receiver evaluate isNumber]) ifTrue:[
		    self codeTimesRepeatOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
		    ^ self
		]
	    ].

	    ((selector == #whileTrue:) or:[selector == #whileFalse:]) ifTrue:[
		(receiver isBlock) ifTrue:[
		    self codeWhileOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
		    ^ self
		]
	    ]
	].
	isBuiltIn := self class isBuiltIn1ArgSelector:selector
    ].

    (nargs == 2) ifTrue:[
	((selector == #ifTrue:ifFalse:) or:[selector == #ifFalse:ifTrue:]) ifTrue:[
	    receiver isBlock ifFalse:[
		(argArray at:1) isBlock ifTrue:[
		    (argArray at:2) isBlock ifTrue:[
			self codeIfElseOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
			^ self
		    ]
		]
	    ]
	].
	isBuiltIn := self class isBuiltIn2ArgSelector:selector
    ].

    "can we use a send-bytecode ?"
    isBuiltIn ifTrue:[
	receiver isSuper ifFalse:[
	    receiver codeOn:aStream inBlock:b for:aCompiler.
	    (nargs > 0) ifTrue:[
		(argArray at:1) codeOn:aStream inBlock:b for:aCompiler.
		(nargs > 1) ifTrue:[
		    (argArray at:2) codeOn:aStream inBlock:b for:aCompiler
		]
	    ].
	    aStream nextPut:selector.
	    (self class hasLineNumber:selector) ifTrue:[
		aStream nextPut:lineNr.
	    ].
	    valueNeeded ifFalse:[
		aStream nextPut:#drop
	    ].
	    ^ self
	]
    ].

    ((nargs == 0) and:[selector == #yourself]) ifTrue:[
	"yourself is often added to get the receiver -
	 we get it without the yourself-message"

	valueNeeded ifTrue:[
	    receiver codeOn:aStream inBlock:b for:aCompiler
	].
	^ self
    ].

    "no - generate a send"

    receiver isSuper ifTrue:[
	cls := aCompiler targetClass.
	receiver isHere ifTrue:[
	    code := #hereSend.
	] ifFalse:[
	    code := #superSend.
	    cls := cls superclass.
	].
	clsLitIndex := aCompiler addLiteral:cls.
    ] ifFalse:[
	clsLitIndex := 0.
    ].

    litIndex := aCompiler addLiteral:selector.
    (litIndex <= 255 and:[clsLitIndex <= 255]) ifTrue:[
	(recType ~~ #Self) ifTrue:[
	    receiver codeOn:aStream inBlock:b for:aCompiler
	].
	argArray notNil ifTrue:[
	    argArray do:[:arg |
		arg codeOn:aStream inBlock:b for:aCompiler
	    ]
	].

	receiver isSuper ifTrue:[
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:nargs; nextPut:clsLitIndex.
	    valueNeeded ifFalse:[
		aStream nextPut:#drop
	    ].
	    ^ self
	].

	(nargs <= 3) ifTrue:[
	    |codes|

	    valueNeeded ifTrue:[
		(receiver type == #Self) ifTrue:[
		    codes := #(sendSelf0 sendSelf1 sendSelf2 sendSelf3)
		] ifFalse:[
		    codes := #(send0 send1 send2 send3)
		]
	    ] ifFalse:[
		(receiver type == #Self) ifTrue:[
		    codes := #(sendSelfDrop0 sendSelfDrop1 sendSelfDrop2 sendSelfDrop3)
		] ifFalse:[
		    codes := #(sendDrop0 sendDrop1 sendDrop2 sendDrop3)
		]
	    ].
	    aStream nextPut:(codes at:(nargs + 1)); nextPut:lineNr; nextPut:litIndex.
	    ^ self
	].

	(recType == #Self) ifTrue:[
	    code := #sendSelf
	] ifFalse:[
	    valueNeeded ifTrue:[
		code := #send
	    ] ifFalse:[
		code := #sendDrop
	    ]
	].
	aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:nargs.
	valueNeeded ifFalse:[
	    (recType == #Self) ifTrue:[
		aStream nextPut:#drop
	    ]
	].
	^ self
    ].

    "needs 16bit literal index"

    receiver isSuper ifTrue:[
	argArray notNil ifTrue:[
	    argArray do:[:arg |
		arg codeOn:aStream inBlock:b for:aCompiler
	    ]
	].
	receiver isHere ifTrue:[
	    code := #hereSendL
	] ifFalse:[
	    code := #superSendL.
	].
	aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs; nextPut:clsLitIndex; nextPut:0.
    ] ifFalse:[
	recType ~~ #Self ifTrue:[
	    receiver codeOn:aStream inBlock:b for:aCompiler.
	].
	argArray notNil ifTrue:[
	    argArray do:[:arg |
		arg codeOn:aStream inBlock:b for:aCompiler
	    ]
	].

	recType == #Self ifTrue:[
	    code := #sendSelfL
	] ifFalse:[
	    code := #sendL
	].
	aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs.
    ].
    valueNeeded ifFalse:[
	aStream nextPut:#drop
    ].

    "Modified: 3.9.1995 / 12:55:42 / claus"
!

codeOrIfOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for (x or:[y]) ifxxx:[ ... ]"

    |theByteCode optByteCode theReceiver theArg pos1 pos2 pos3 code here jmp|

    theByteCode := #trueJump.
    theReceiver := receiver receiver.

    optByteCode := self optimizedConditionFor:theReceiver with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := theReceiver arg1
	].
	theReceiver := theReceiver receiver.
	theByteCode := optByteCode
    ].
    theReceiver codeOn:aStream inBlock:b for:aCompiler.
    theArg notNil ifTrue:[
	theArg codeOn:aStream inBlock:b for:aCompiler
    ].
    aStream nextPut:theByteCode.
    pos1 := aStream position.
    aStream nextPut:0.


    theReceiver := receiver arg1.

"new:"
    (selector == #ifTrue:) ifTrue:[
	theByteCode := #falseJump
    ] ifFalse:[
	theByteCode := #trueJump
    ].
    optByteCode := self optimizedConditionFor:theReceiver with:theByteCode.
    optByteCode notNil ifTrue:[
	theReceiver isBlock ifTrue:[
	    theReceiver := theReceiver statements expression
	].
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := theReceiver arg1
	].
	theReceiver := theReceiver receiver.
	theByteCode := optByteCode.

	theReceiver codeOn:aStream inBlock:b for:aCompiler.
	theArg notNil ifTrue:[
	    theArg codeOn:aStream inBlock:b for:aCompiler
	].
	aStream nextPut:theByteCode.

    ] ifFalse:[
"org"
	theReceiver codeInlineOn:aStream inBlock:b for:aCompiler.
	(selector == #ifTrue:) ifTrue:[
	    jmp := #falseJump
	] ifFalse:[
	    jmp := #trueJump
	].
	aStream nextPut:jmp
    ].
    pos2 := aStream position.
    aStream nextPut:0.
    (selector == #ifTrue:) ifTrue:[
	(aStream contents) at:pos1 put:(aStream position)
    ].
    (argArray at: 1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.

    code := aStream contents.
    valueNeeded ifTrue:[
	aStream nextPut:#jump.
	pos3 := aStream position.
	aStream nextPut:0.
	here := aStream position.
	(selector == #ifFalse:) ifTrue:[
	    code at:pos1 put:here
	].
	code at:pos2 put:here.
	aStream nextPut:#pushNil.
	code at:pos3 put:(aStream position)
    ] ifFalse:[
	here := aStream position.
	(selector == #ifFalse:) ifTrue:[
	    code at:pos1 put:here
	].
	code at:pos2 put:here
    ]
!

codeSendOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "like code on, but assumes that receiver has already been
     coded onto stack - needed for cascade"

    |nargs isBuiltIn code litIndex|

    argArray isNil ifTrue:[
	nargs := 0
    ] ifFalse:[
	nargs := argArray size
    ].

    isBuiltIn := false.

    (nargs == 0) ifTrue:[
	isBuiltIn := self class isBuiltInUnarySelector:selector
    ].
    (nargs == 1) ifTrue:[
	isBuiltIn := self class isBuiltIn1ArgSelector:selector
    ].
    (nargs == 2) ifTrue:[
	isBuiltIn := self class isBuiltIn2ArgSelector:selector
    ].

    "can we use a send-bytecode ?"
    isBuiltIn ifTrue:[
	receiver isSuper ifFalse:[
	    (nargs > 0) ifTrue:[
		(argArray at:1) codeOn:aStream inBlock:b for:aCompiler.
		(nargs > 1) ifTrue:[
		    (argArray at:2) codeOn:aStream inBlock:b for:aCompiler
		]
	    ].
	    aStream nextPut:selector.
	    (self class hasLineNumber:selector) ifTrue:[
		aStream nextPut:lineNr.
	    ].
	    valueNeeded ifFalse:[
		aStream nextPut:#drop
	    ].
	    ^ self
	]
    ].

    argArray notNil ifTrue:[
	argArray do:[:arg |
	    arg codeOn:aStream inBlock:b for:aCompiler
	]
    ].

    receiver isSuper ifTrue:[
	litIndex := aCompiler addLiteral:selector.
	litIndex <= 255 ifTrue:[
	    receiver isHere ifTrue:[
		code := #hereSend
	    ] ifFalse:[
		code := #superSend.
	    ].
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:nargs; nextPut:nil.
	] ifFalse:[
	    receiver isHere ifTrue:[
		code := #hereSendL
	    ] ifFalse:[
		code := #superSendL.
	    ].
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs; nextPut:nil.
	].
	valueNeeded ifFalse:[
	    aStream nextPut:#drop
	].
	^ self
    ].
    (nargs == 0) ifTrue:[
	(selector == #yourself) ifTrue:[
	    "yourself is often added to get the receiver -
	     we get it without the yourself-message"

	    valueNeeded ifFalse:[
		aStream nextPut:#drop
	    ].
	    ^ self
	].
    ].

    litIndex := aCompiler addLiteral:selector.
    litIndex <= 255 ifTrue:[
	(nargs <= 3) ifTrue:[
	    valueNeeded ifTrue:[
		code := #(send0 send1 send2 send3) at:(nargs+1).
	    ] ifFalse:[
		code := #(sendDrop0 sendDrop1 sendDrop2 sendDrop3) at:(nargs+1).
	    ].
	    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex.
	    ^ self
	].

	valueNeeded ifTrue:[
	    code := #send
	] ifFalse:[
	    code := #sendDrop
	].
	aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:nargs.
	^ self
    ].

    valueNeeded ifTrue:[
	code := #sendL
    ] ifFalse:[
	code := #sendDropL
    ].
    aStream nextPut:code; nextPut:lineNr; nextPut:litIndex; nextPut:0; nextPut:nargs
!

codeTimesRepeatOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for n timesRepeat:[ ... ]"

    |pos pos2 theReceiver|

    theReceiver := receiver.
    theReceiver codeOn:aStream inBlock:b for:aCompiler.
    valueNeeded ifTrue:[aStream nextPut:#dup].

    pos := aStream position.
"/    aStream nextPut:#dup; nextPut:#push0; nextPut:#>; nextPut:lineNr; nextPut:#falseJump.
"/    aStream nextPut:#dup; nextPut:#gt0; nextPut:lineNr; nextPut:#falseJump.
    aStream nextPut:#pushgt0; nextPut:lineNr; nextPut:#falseJump.
    pos2 := aStream position.
    aStream nextPut:0.

    (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
    aStream nextPut:#minus1; nextPut:lineNr; nextPut:#jump; nextPut:pos.

    (aStream contents) at:pos2 put:(aStream position).
    aStream nextPut:#drop.
!

codeWhileOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
    "generate code for [...] whilexxx:[ ... ]"

    |pos pos2 theReceiver theArg theByteCode optByteCode|

    (selector == #whileTrue:) ifTrue:[
	theByteCode := #falseJump
    ] ifFalse:[
	theByteCode := #trueJump
    ].

    theReceiver := receiver.
    optByteCode := self optimizedConditionFor:theReceiver with:theByteCode.
    optByteCode notNil ifTrue:[
	((optByteCode == #eqJump) or:[optByteCode == #notEqJump]) ifTrue:[
	    theArg := receiver statements expression arg1
	].
	theReceiver := receiver statements expression receiver.
	theByteCode := optByteCode
    ].

"/ OLD:
"/    valueNeeded ifTrue:[aStream nextPut:#pushNil].
"/
    pos := aStream position.
    optByteCode notNil ifTrue:[
	theReceiver codeOn:aStream inBlock:b for:aCompiler.
	theArg notNil ifTrue:[
	    theArg codeOn:aStream inBlock:b for:aCompiler
	]
    ] ifFalse:[
	theReceiver codeInlineOn:aStream inBlock:b for:aCompiler
    ].

    (lineNr between:1 and:255) ifTrue:[
	aStream nextPut:#lineno; nextPut:lineNr.
    ].

    aStream nextPut:theByteCode.
    pos2 := aStream position.
    aStream nextPut:0.
"/ OLD:
"/    valueNeeded ifTrue:[aStream nextPut:#drop].
"/
"/ OLD:
"/    (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
"/ NEW:
    (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
    aStream nextPut:#jump; nextPut:pos.
    (aStream contents) at:pos2 put:(aStream position).
"/ NEW:
    valueNeeded ifTrue:[aStream nextPut:#pushNil].
!

optimizedConditionFor:aReceiver with:aByteCode
    |rec sel|

    rec := aReceiver.
    (rec isBlock) ifTrue:[
	rec statements nextStatement isNil ifTrue:[
	    rec := rec statements expression
	]
    ].
    (rec isUnaryMessage) ifTrue:[
	sel := rec selector.
	(sel == #isNil) ifTrue:[
	    "/
	    "/ isNil trueJmp  -> nilJump
	    "/ isNil falseJmp -> notNilJump
	    "/
	    (aByteCode == #trueJump) ifTrue:[^ #nilJump].
	    (aByteCode == #falseJump) ifTrue:[^ #notNilJump]
	].
	(sel == #notNil) ifTrue:[
	    "/
	    "/ notNil trueJmp  -> notNilJump
	    "/ notNil falseJmp -> nilJump
	    "/
	    (aByteCode == #trueJump) ifTrue:[^ #notNilJump].
	    (aByteCode == #falseJump) ifTrue:[^ #nilJump]
	].
	(sel == #not) ifTrue:[
	    "/
	    "/ not trueJmp  -> falseJump
	    "/ not falseJmp -> trueJump
	    "/
	    (aByteCode == #trueJump) ifTrue:[^ #falseJump].
	    (aByteCode == #falseJump) ifTrue:[^ #trueJump]
	].
	^ nil
    ].
    (rec isBinaryMessage) ifTrue:[
	sel := rec selector.
	rec arg1 isConstant ifTrue:[
	    (rec arg1 value == 0) ifTrue:[
		"/
		"/ ==0 trueJmp  -> zeroJump
		"/ ==0 falseJmp -> notZeroJump
		"/
		(sel == #==) ifTrue:[
		    (aByteCode == #trueJump) ifTrue:[^ #zeroJump].
		    (aByteCode == #falseJump) ifTrue:[^ #notZeroJump]
		].
		"/
		"/ ~~0 trueJmp  -> notZeroJump
		"/ ~~0 falseJmp -> zeroJump
		"/
		(sel == #~~) ifTrue:[
		    (aByteCode == #falseJump) ifTrue:[^ #zeroJump].
		    (aByteCode == #trueJump) ifTrue:[^ #notZeroJump]
		].
		^ nil
	    ]
	].
	(sel == #==) ifTrue:[
	    "/
	    "/ == trueJmp  -> eqJump
	    "/ == falseJmp -> notEqJump
	    "/
	    (aByteCode == #trueJump) ifTrue:[^ #eqJump].
	    (aByteCode == #falseJump) ifTrue:[^ #notEqJump]
	].
	(sel == #~~) ifTrue:[
	    "/
	    "/ ~~ trueJmp  -> notEqJump
	    "/ ~~ falseJmp -> eqJump
	    "/
	    (aByteCode == #falseJump) ifTrue:[^ #eqJump].
	    (aByteCode == #trueJump) ifTrue:[^ #notEqJump]
	]
    ].
    ^ nil
! !

!MessageNode methodsFor:'evaluating'!

evaluate
    |r nargs argValueArray class|

    receiver isSuper ifTrue:[
	r := receiver value.
	receiver isHere ifTrue:[
	    class := receiver definingClass.
	] ifFalse:[
	    class := receiver definingClass superclass.
	].
	argArray notNil ifTrue:[
	    argValueArray := argArray collect:[:arg | arg evaluate].
	] ifFalse:[
	    argValueArray := #()
	].
	^ r perform:selector inClass:class withArguments:argValueArray
    ].


    argArray isNil ifTrue:[
	^ (receiver evaluate) perform:selector
    ].
    nargs := argArray size.
    (nargs == 1) ifTrue:[
	^ (receiver evaluate) perform:selector with:(argArray at:1) evaluate
    ].
    (nargs == 2) ifTrue:[
	^ (receiver evaluate) perform:selector
				 with:(argArray at:1) evaluate
				 with:(argArray at:2) evaluate
    ].
    (nargs == 3) ifTrue:[
	^ (receiver evaluate) perform:selector
				 with:(argArray at:1) evaluate
				 with:(argArray at:2) evaluate
				 with:(argArray at:3) evaluate
    ].
    r := receiver evaluate.
    argValueArray := argArray collect:[:arg | arg evaluate].
    ^ r perform:selector withArguments:argValueArray
!

evaluateForCascade
    |r nargs argValueArray class|

    receiver isSuper ifTrue:[
	r := receiver value.
	class := receiver definingClass.
	receiver isHere ifFalse:[
	    class := class superclass.
	].
	argArray notNil ifTrue:[
	    argValueArray := argArray collect:[:arg | arg evaluate].
	] ifFalse:[
	    argValueArray := #()
	].
	r perform:selector inClass:class withArguments:argValueArray.
	^ r
    ].

    r := receiver evaluate.
    argArray isNil ifTrue:[
	r perform:selector.
	^ r
    ].
    nargs := argArray size.
    (nargs == 1) ifTrue:[
	r perform:selector with:(argArray at:1) evaluate.
	^ r
    ].
    (nargs == 2) ifTrue:[
	r perform:selector with:(argArray at:1) evaluate
			   with:(argArray at:2) evaluate.
	^ r
    ].
    (nargs == 3) ifTrue:[
	r perform:selector with:(argArray at:1) evaluate
			   with:(argArray at:2) evaluate
			   with:(argArray at:3) evaluate.
	^ r
    ].
    argValueArray := argArray collect:[:arg | arg evaluate].
    r perform:selector withArguments:argValueArray.
    ^ r
! !

!MessageNode methodsFor:'printing'!

printOn:aStream indent:i
    |needParen selectorParts index index2 arg|

    (#(whileTrue: whileFalse:) includes:selector) ifTrue:[
	receiver isBlock ifTrue:[
	    ^ self printWhileOn:aStream indent:i
	].
    ].

    index := 1.
    selectorParts := OrderedCollection new.
    [index == 0] whileFalse:[
	index2 := selector indexOf:$: startingAt:index.
	index2 ~~ 0 ifTrue:[
	    selectorParts add:(selector copyFrom:index to:index2).
	    index2 := index2 + 1
	].
	index := index2
    ].

    needParen := false.
    receiver isMessage ifTrue:[
	receiver isUnaryMessage ifFalse:[
	    receiver isBinaryMessage ifFalse:[
		needParen := true
	    ].
	].
    ].
    needParen ifTrue:[
	aStream nextPutAll:'('
    ].
    receiver printOn:aStream indent:i.
    needParen ifTrue:[
	aStream nextPutAll:')'
    ].

    1 to:(argArray size) do:[:argIndex |
	aStream space.
	(selectorParts at:argIndex) printOn:aStream.
	aStream space.
	arg := argArray at:argIndex.
	needParen := false.
	arg isMessage ifTrue:[
	    arg isBinaryMessage ifFalse:[
		arg isUnaryMessage ifFalse:[
		    needParen := true
		]
	    ].
	].
	needParen ifTrue:[
	    aStream nextPutAll:'('
	].
	arg printOn:aStream indent:i.
	needParen ifTrue:[
	    aStream nextPutAll:') '
	].
    ]
!

printWhileOn:aStream indent:i
    |needParen arg|

    "special handling of whileTrue/whileFalse"

    aStream nextPutAll:'['.
    receiver statements printOn:aStream indent:i.
    aStream nextPutAll:'] whileTrue: '.

    arg := argArray at:1.
    needParen := false.
    arg isMessage ifTrue:[
	arg isBinaryMessage ifFalse:[
	    arg isUnaryMessage ifFalse:[
		needParen := true
	    ]
	].
    ].
    needParen ifTrue:[
	aStream nextPutAll:'('
    ].
    arg printOn:aStream indent:i.
    needParen ifTrue:[
	aStream nextPutAll:') '
    ].
! !

!MessageNode methodsFor:'queries'!

isMessage
    ^ true
! !

!MessageNode class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/Attic/MessageNd.st,v 1.34 1995-12-09 22:10:33 cg Exp $'
! !