BlockNode.st
changeset 45 e8331ba8ad5d
parent 39 b54658946e66
child 52 d80ec10c3321
--- a/BlockNode.st	Sun Oct 02 23:01:25 1994 +0100
+++ b/BlockNode.st	Mon Oct 10 01:58:23 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -12,8 +12,8 @@
 
 ParseNode subclass:#BlockNode
        instanceVariableNames:'blockArgs statements home inlineBlock exitBlock
-                              blockVars 
-                              needsHome lineNr'
+			      blockVars 
+			      needsHome lineNr'
        classVariableNames:''
        poolDictionaries:''
        category:'System-Compiler-Support'
@@ -21,9 +21,9 @@
 
 BlockNode comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libcomp/BlockNode.st,v 1.9 1994-08-23 16:17:14 claus Exp $
+$Header: /cvs/stx/stx/libcomp/BlockNode.st,v 1.10 1994-10-10 00:57:41 claus Exp $
 '!
 
 !BlockNode class methodsFor:'documentation'!
@@ -31,7 +31,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libcomp/BlockNode.st,v 1.9 1994-08-23 16:17:14 claus Exp $
+$Header: /cvs/stx/stx/libcomp/BlockNode.st,v 1.10 1994-10-10 00:57:41 claus Exp $
 "
 !
 
@@ -136,7 +136,7 @@
     "return via return-statement"
 
     home notNil ifTrue:[
-        home exitWith:something
+	home exitWith:something
     ].
     exitBlock value:something.
     ^ something
@@ -148,14 +148,14 @@
 
 wrongNumberOfArguments:numberGiven
     Block argumentSignal
-        raiseRequestWith:self
-        errorString:('block got ' , numberGiven printString ,
-                     ' args while ' , blockArgs size printString , ' where expected')
+	raiseRequestWith:self
+	errorString:('block got ' , numberGiven printString ,
+		     ' args while ' , blockArgs size printString , ' where expected')
 !
 
 value
     (blockArgs size ~~ 0) ifTrue:[
-        ^ self wrongNumberOfArguments:0
+	^ self wrongNumberOfArguments:0
     ].
     statements isNil ifTrue:[^ nil].
     exitBlock := [:val | ^ val].
@@ -166,7 +166,7 @@
     |oldValue val|
 
     (blockArgs size ~~ 1) ifTrue:[
-        ^ self wrongNumberOfArguments:1
+	^ self wrongNumberOfArguments:1
     ].
     statements isNil ifTrue:[^ nil].
 
@@ -174,8 +174,8 @@
     (blockArgs at:1) value:anArg.
 
     exitBlock := [:v | 
-        (blockArgs at:1) value:oldValue.
-        ^ v
+	(blockArgs at:1) value:oldValue.
+	^ v
     ].
 
     val := statements evaluate.
@@ -188,7 +188,7 @@
     |oldValue1 oldValue2 val|
 
     (blockArgs size ~~ 2) ifTrue:[
-        ^ self wrongNumberOfArguments:2
+	^ self wrongNumberOfArguments:2
     ].
     statements isNil ifTrue:[^ nil].
 
@@ -198,9 +198,9 @@
     (blockArgs at:2) value:arg2.
 
     exitBlock := [:v | 
-        (blockArgs at:1) value:oldValue1.
-        (blockArgs at:2) value:oldValue2.
-        ^ v
+	(blockArgs at:1) value:oldValue1.
+	(blockArgs at:2) value:oldValue2.
+	^ v
     ].
 
     val := statements evaluate.
@@ -214,7 +214,7 @@
     |oldValue1 oldValue2 oldValue3 val|
 
     (blockArgs size ~~ 3) ifTrue:[
-        ^ self wrongNumberOfArguments:3
+	^ self wrongNumberOfArguments:3
     ].
     statements isNil ifTrue:[^ nil].
 
@@ -226,10 +226,10 @@
     (blockArgs at:3) value:arg3.
 
     exitBlock := [:v | 
-        (blockArgs at:1) value:oldValue1.
-        (blockArgs at:2) value:oldValue2.
-        (blockArgs at:3) value:oldValue3.
-        ^ v
+	(blockArgs at:1) value:oldValue1.
+	(blockArgs at:2) value:oldValue2.
+	(blockArgs at:3) value:oldValue3.
+	^ v
     ].
 
     val := statements evaluate.
@@ -244,7 +244,7 @@
     |oldValue1 oldValue2 oldValue3 oldValue4 val|
 
     (blockArgs size ~~ 4) ifTrue:[
-        ^ self wrongNumberOfArguments:4
+	^ self wrongNumberOfArguments:4
     ].
     statements isNil ifTrue:[^ nil].
 
@@ -258,11 +258,11 @@
     (blockArgs at:4) value:arg4.
 
     exitBlock := [:v | 
-        (blockArgs at:1) value:oldValue1.
-        (blockArgs at:2) value:oldValue2.
-        (blockArgs at:3) value:oldValue3.
-        (blockArgs at:4) value:oldValue4.
-        ^ v
+	(blockArgs at:1) value:oldValue1.
+	(blockArgs at:2) value:oldValue2.
+	(blockArgs at:3) value:oldValue3.
+	(blockArgs at:4) value:oldValue4.
+	^ v
     ].
 
     val := statements evaluate.
@@ -278,26 +278,26 @@
     |oldValues val|
 
     (blockArgs size ~~ argArray size) ifTrue:[
-        ^ self wrongNumberOfArguments:argArray size
+	^ self wrongNumberOfArguments:argArray size
     ].
     statements isNil ifTrue:[^ nil].
 
     oldValues := Array new:(argArray size).
     1 to:argArray size do:[:i |
-        oldValues at:i put:(blockArgs at:i) value.
-        (blockArgs at:i) value:(argArray at:i).
+	oldValues at:i put:(blockArgs at:i) value.
+	(blockArgs at:i) value:(argArray at:i).
     ].
     exitBlock := [:v | 
-        1 to:argArray size do:[:i |
-           ( blockArgs at:i) value:(oldValues at:i)
-        ].
-        ^ v
+	1 to:argArray size do:[:i |
+	   ( blockArgs at:i) value:(oldValues at:i)
+	].
+	^ v
     ].
 
     val := statements evaluate.
 
     1 to:argArray size do:[:i |
-        (blockArgs at:i) value:(oldValues at:i)
+	(blockArgs at:i) value:(oldValues at:i)
     ].
     ^ val
 ! !
@@ -322,33 +322,33 @@
     |numArgs kludgeBlock|
 
     (Block implements:(aMessage selector)) ifTrue:[
-        "mhmh - a message which I dont understand, but Block implements
-         send it to a kludgeblock, which will evaluate me again ..."
-        numArgs := blockArgs size.
-        numArgs == 0 ifTrue:[
-            kludgeBlock := [self value]
-        ] ifFalse:[
-            numArgs == 1 ifTrue:[
-                kludgeBlock := [:a1 | self value:a1].
-            ] ifFalse:[
-                numArgs == 2 ifTrue:[
-                    kludgeBlock := [:a1 :a2 | self value:a1 value:a2].
-                ] ifFalse:[
-                    numArgs == 3 ifTrue:[
-                        kludgeBlock := [:a1 :a2 :a3| self value:a1 value:a2 value:a3].
-                    ] ifFalse:[
-                        numArgs == 4 ifTrue:[
-                            kludgeBlock := [:a1 :a2 :a3 :a4| self value:a1 value:a2 value:a3 value:a4].
-                        ] ifFalse:[
-                            ^ self error:'only support blocks with up-to 4 args'
-                        ]
-                    ]
-                ]
-            ]
-        ].
-        ^ kludgeBlock perform:aMessage selector withArguments:aMessage arguments
+	"mhmh - a message which I dont understand, but Block implements
+	 send it to a kludgeblock, which will evaluate me again ..."
+	numArgs := blockArgs size.
+	numArgs == 0 ifTrue:[
+	    kludgeBlock := [self value]
+	] ifFalse:[
+	    numArgs == 1 ifTrue:[
+		kludgeBlock := [:a1 | self value:a1].
+	    ] ifFalse:[
+		numArgs == 2 ifTrue:[
+		    kludgeBlock := [:a1 :a2 | self value:a1 value:a2].
+		] ifFalse:[
+		    numArgs == 3 ifTrue:[
+			kludgeBlock := [:a1 :a2 :a3| self value:a1 value:a2 value:a3].
+		    ] ifFalse:[
+			numArgs == 4 ifTrue:[
+			    kludgeBlock := [:a1 :a2 :a3 :a4| self value:a1 value:a2 value:a3 value:a4].
+			] ifFalse:[
+			    ^ self error:'only support blocks with up-to 4 args'
+			]
+		    ]
+		]
+	    ]
+	].
+	^ kludgeBlock perform:aMessage selector withArguments:aMessage arguments
     ].
-    super doesNotUnderstand:aMessage
+    ^ super doesNotUnderstand:aMessage
 ! !
 
 !BlockNode methodsFor:'code generation'!
@@ -358,8 +358,8 @@
 
     cheapy := self checkForSimpleBlock.
     cheapy notNil ifTrue:[
-        cheapy codeOn:aStream inBlock:b.
-        ^ self
+	cheapy codeOn:aStream inBlock:b.
+	^ self
     ].
 
     pos := aStream position.
@@ -369,18 +369,18 @@
     aStream nextPut:(blockVars size).      "+2"
     aStream nextPut:(blockArgs size).      "+3"
     statements isNil ifTrue:[
-        aStream nextPut:#pushNil           "+4"
+	aStream nextPut:#pushNil           "+4"
     ] ifFalse:[
-        thisStatement := statements.
-        [thisStatement notNil] whileTrue:[
-            nextStatement := thisStatement nextStatement.
-            nextStatement notNil ifTrue:[
-                thisStatement codeForSideEffectOn:aStream inBlock:self
-            ] ifFalse:[
-                thisStatement codeOn:aStream inBlock:self
-            ].
-            thisStatement := nextStatement
-        ]
+	thisStatement := statements.
+	[thisStatement notNil] whileTrue:[
+	    nextStatement := thisStatement nextStatement.
+	    nextStatement notNil ifTrue:[
+		thisStatement codeForSideEffectOn:aStream inBlock:self
+	    ] ifFalse:[
+		thisStatement codeOn:aStream inBlock:self
+	    ].
+	    thisStatement := nextStatement
+	]
     ].
     aStream nextPut:#retTop.
 
@@ -389,12 +389,12 @@
     "
     code := (aStream contents).
     (code at:pos+4) == #push0 ifTrue:[
-        (code at:pos+5) == #retTop ifTrue:[
-            aStream position:pos.
-            code grow:pos.
-            aStream nextPut:#mk0Block.
-            ^ self
-        ]
+	(code at:pos+5) == #retTop ifTrue:[
+	    aStream position:pos.
+	    code grow:pos.
+	    aStream nextPut:#mk0Block.
+	    ^ self
+	]
     ].
 
     "check for [nil]-block;
@@ -403,12 +403,12 @@
     "
     code := (aStream contents).
     (code at:pos+4) == #pushNil ifTrue:[
-        (code at:pos+5) == #retTop ifTrue:[
-            aStream position:pos.
-            code grow:pos.
-            aStream nextPut:#mkNilBlock.
-            ^ self
-        ]
+	(code at:pos+5) == #retTop ifTrue:[
+	    aStream position:pos.
+	    code grow:pos.
+	    aStream nextPut:#mkNilBlock.
+	    ^ self
+	]
     ].
 
     (aStream contents) at:pos+1 put:(aStream position)
@@ -425,36 +425,36 @@
     |thisStatement nextStatement|
 
     blockVars notNil ifTrue:[
-        "cannot currently compile this block inline (have to move blockvars into
-         surrounding method. generate a make-block and send it value"
+	"cannot currently compile this block inline (have to move blockvars into
+	 surrounding method. generate a make-block and send it value"
 
-        Transcript showCr:'cannot (yet) compile block with blockvars inline'.
-        self codeOn:aStream inBlock:b.
-        aStream nextPut:#value.
-        (MessageNode hasLineNumber:#value) ifTrue:[
-            aStream nextPut:lineNr.
-        ].
-        valueNeeded ifFalse:[
-            aStream nextPut:#drop
-        ].
-        ^ self
+	Transcript showCr:'cannot (yet) compile block with blockvars inline'.
+	self codeOn:aStream inBlock:b.
+	aStream nextPut:#value.
+	(MessageNode hasLineNumber:#value) ifTrue:[
+	    aStream nextPut:lineNr.
+	].
+	valueNeeded ifFalse:[
+	    aStream nextPut:#drop
+	].
+	^ self
     ].
     inlineBlock := true.
     statements isNil ifTrue:[
-        valueNeeded ifTrue:[
-            aStream nextPut:#pushNil
-        ]
+	valueNeeded ifTrue:[
+	    aStream nextPut:#pushNil
+	]
     ] ifFalse:[
-        thisStatement := statements.
-        [thisStatement notNil] whileTrue:[
-            nextStatement := thisStatement nextStatement.
-            (nextStatement notNil or:[valueNeeded not]) ifTrue:[
-                thisStatement codeForSideEffectOn:aStream inBlock:b
-            ] ifFalse:[
-                thisStatement codeOn:aStream inBlock:b
-            ].
-            thisStatement := nextStatement
-        ]
+	thisStatement := statements.
+	[thisStatement notNil] whileTrue:[
+	    nextStatement := thisStatement nextStatement.
+	    (nextStatement notNil or:[valueNeeded not]) ifTrue:[
+		thisStatement codeForSideEffectOn:aStream inBlock:b
+	    ] ifFalse:[
+		thisStatement codeOn:aStream inBlock:b
+	    ].
+	    thisStatement := nextStatement
+	]
     ]
 !
 
@@ -469,58 +469,58 @@
     |cheapy e val code|
 
     statements isNil ifTrue:[
-        "a []-block"
+	"a []-block"
 
-        val := nil
+	val := nil
     ] ifFalse:[
-        statements nextStatement notNil ifTrue:[^ nil].
-        (statements isMemberOf:StatementNode) ifFalse:[^ nil].
+	statements nextStatement notNil ifTrue:[^ nil].
+	(statements isMemberOf:StatementNode) ifFalse:[^ nil].
 
-        e := statements expression.
-        e isConstant ifFalse:[^ nil].
+	e := statements expression.
+	e isConstant ifFalse:[^ nil].
 
-        val := e value.
+	val := e value.
     ].
 
     val == 0 ifTrue:[
-        "a [0]-block"
+	"a [0]-block"
 
-        code := ByteArray with:(ByteCodeCompiler byteCodeFor:#ret0).
+	code := ByteArray with:(ByteCodeCompiler byteCodeFor:#ret0).
     ].
     val == 1 ifTrue:[
-        "a [1]-block"
+	"a [1]-block"
 
-        code := ByteArray with:(ByteCodeCompiler byteCodeFor:#push1)
-                          with:(ByteCodeCompiler byteCodeFor:#retTop).
+	code := ByteArray with:(ByteCodeCompiler byteCodeFor:#push1)
+			  with:(ByteCodeCompiler byteCodeFor:#retTop).
     ].
 
     val == true ifTrue:[
-        "a [true]-block"
+	"a [true]-block"
 
-        code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retTrue).
+	code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retTrue).
     ].
 
     val == false ifTrue:[
-        "a [false]-block"
+	"a [false]-block"
 
-        code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retFalse).
+	code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retFalse).
     ].
 
     val == nil ifTrue:[
-        "a [nil]-block"
+	"a [nil]-block"
 
-        code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retNil).
+	code := ByteArray with:(ByteCodeCompiler byteCodeFor:#retNil).
     ].
 
     code notNil ifTrue:[
-        cheapy := Block code:nil
-                    byteCode:code
-                    nargs:(blockArgs size)
-                    sourcePosition:nil 
-                    initialPC:nil 
-                    literals:nil
-                    dynamic:false.
-        ^ ConstantNode type:#Block value:cheapy
+	cheapy := Block code:nil
+		    byteCode:code
+		    numArgs:(blockArgs size)
+		    sourcePosition:nil 
+		    initialPC:nil 
+		    literals:nil
+		    dynamic:false.
+	^ ConstantNode type:#Block value:cheapy
     ].
 
     ^ nil
@@ -531,16 +531,16 @@
 printOn:aStream indent:i
     aStream nextPut:$[.
     1 to:blockArgs size do:[:index |
-        aStream nextPut:$:.
-        aStream nextPutAll:(blockArgs at:index) name.
-        aStream space.
-        aStream nextPut:$|
+	aStream nextPut:$:.
+	aStream nextPutAll:(blockArgs at:index) name.
+	aStream space.
+	aStream nextPut:$|
     ].
     statements notNil ifTrue:[
-        aStream cr.
-        statements printAllOn:aStream indent:i + 4.
-        aStream cr. 
-        aStream spaces:i.
+	aStream cr.
+	statements printAllOn:aStream indent:i + 4.
+	aStream cr. 
+	aStream spaces:i.
     ].
     aStream nextPut:$]
 ! !