[squeak-dev] The Inbox: Compiler-eem.79.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 6 00:33:15 UTC 2009


A new version of Compiler was added to project The Inbox:
http://source.squeak.org/inbox/Compiler-eem.79.mcz

==================== Summary ====================

Name: Compiler-eem.79
Author: eem
Time: 5 September 2009, 4:42:29 am
UUID: f52d0730-d744-40d2-bdd1-f7412fc1b8f1
Ancestors: Compiler-eem.78

Fourth package of eight in closure compiler fixes 9/5/2009.

Second stage of the closure compiler fixes for
- miscompilation of optimized blocks
- bugs in statement highlighting in the debugger
- storing the selector as the penultimate literal of a method
  directly unless it has properties, in which case it has an
  AdditionalMethodState.  Saves significant space.

Throws the switch to the new closure analysis in BlockNode>>analyseArguments:temporaries:rootNode: using in place of analyseTempsWithin:rootNode:assignmentPools: analyseTempsWithin:rootNode:.

This requires
	Exceptions-eem.12
	Kernel-eem.242
	Compiler-eem.78

=============== Diff against Compiler-eem.78 ===============

Item was changed:
  ----- Method: MethodNode>>printPropertiesOn: (in category 'printing') -----
  printPropertiesOn: aStream
  	properties ifNil: [^self].
+ 	properties propertyKeysAndValuesDo:
+ 		[:prop :val|
+ 		aStream crtab; nextPut: $<.
+ 		prop = #on:in:
+ 			ifTrue:
+ 				[prop keywords with: val do:
+ 					[:k :v | aStream nextPutAll: k; space; nextPutAll: v; space]]
+ 			ifFalse:
+ 				[prop = #on
+ 					ifTrue: [aStream nextPutAll: prop; nextPutAll:': '; nextPutAll: val] 
+ 					ifFalse: [aStream nextPutAll: prop; nextPutAll:': '; print: val]]. 
+ 		aStream nextPut: $>]!
- 	properties pragmas do:
- 		[ :each |
- 		 "Don't decompile basic primitives that return self, i-vars, etc."
- 		 each keyword = #primitive:
- 			ifFalse: [ aStream crtab: 1. each printOn: aStream ]
- 			ifTrue: [ ((each argumentAt: 1) between: 255 and: 519) ifFalse:
- 						[ aStream crtab: 1. self printPrimitiveOn: aStream ] ] ]!

Item was changed:
  ----- Method: MethodNode>>printWithClosureAnalysisOn: (in category 'printing') -----
  printWithClosureAnalysisOn: aStream 
  
  	precedence = 1
  		ifTrue: 
  			[(self selector includesSubString: '()/')
  				ifTrue: [aStream nextPutAll: (self selector copyUpTo: $)).
  						arguments
  							do: [:arg| aStream nextPutAll: arg key]
  							separatedBy: [aStream nextPutAll: ', '].
  						aStream nextPut: $)]
  				ifFalse: [aStream nextPutAll: self selector]]  "no node for method selector"
  		ifFalse: 
  			[self selector keywords with: arguments do: 
  				[:kwd :arg | 
  				aStream nextPutAll: kwd; space.
  				arg printDefinitionForClosureAnalysisOn: aStream.
  				aStream space]].
  	comment == nil ifFalse: 
  			[aStream crtab: 1.
  			 self printCommentOn: aStream indent: 1].
  	temporaries size > 0 ifTrue: 
  			[aStream crtab: 1; nextPut: $|.
  			temporaries do: [:temp | 
  				aStream space.
  				temp printDefinitionForClosureAnalysisOn: aStream].
  			aStream space; nextPut: $|].
  	primitive > 0 ifTrue:
  		[(primitive between: 255 and: 519) ifFalse:  "Dont decompile quick prims  e.g, ^ self or ^instVar"
  			[aStream crtab: 1.
  			 self printPrimitiveOn: aStream]].
  	self printPropertiesOn: aStream.
+ 	self printPragmasOn: aStream.
  	aStream crtab: 1.
  	block printWithClosureAnalysisStatementsOn: aStream indent: 0!

Item was changed:
  ----- Method: Compiler>>compiledMethodFor:in:to:notifying:ifFail:logged: (in category 'public access') -----
  compiledMethodFor: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag
+ 	"Compiles the sourceStream into a parse tree, then generates code
+ 	 into a method, and answers it.  If receiver is not nil, then the text can
+ 	 refer to instance variables of that receiver (the Inspector uses this).
+ 	 If aContext is not nil, the text can refer to temporaries in that context
+ 	 (the Debugger uses this). If aRequestor is not nil, then it will receive a 
+ 	 notify:at: message before the attempt to evaluate is aborted."
- 	"Compiles the sourceStream into a parse tree, then generates code into a 
- 	method. This method is then installed in the receiver's class so that it 
- 	can be invoked. In other words, if receiver is not nil, then the text can 
- 	refer to instance variables of that receiver (the Inspector uses this). If 
- 	aContext is not nil, the text can refer to temporaries in that context (the 
- 	Debugger uses this). If aRequestor is not nil, then it will receive a 
- 	notify:at: message before the attempt to evaluate is aborted. Finally, the 
- 	compiled method is invoked from here as DoIt or (in the case of 
- 	evaluation in aContext) DoItIn:. The method is subsequently removed 
- 	from the class, but this will not get done if the invocation causes an 
- 	error which is terminated. Such garbage can be removed by executing: 
- 	Smalltalk allBehaviorsDo: [:cl | cl removeSelector: #DoIt; removeSelector: 
- 	#DoItIn:]."
  
  	| methodNode method |
  	class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class.
  	self from: textOrStream class: class context: aContext notifying: aRequestor.
+ 	methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value].
- 	methodNode := self translate: sourceStream noPattern: true ifFail:
- 		[^failBlock value].
  	method := methodNode generate: #(0 0 0 0).
  	self interactive ifTrue:
+ 		[method := method copyWithTempsFromMethodNode: methodNode].
+ 	logFlag ifTrue:
+ 		[SystemChangeNotifier uniqueInstance evaluated: sourceStream contents context: aContext].
+ 	^method!
- 		[method := method copyWithTempNames: methodNode tempNames].
- 	
- 	logFlag ifTrue: [SystemChangeNotifier uniqueInstance evaluated: sourceStream contents context: aContext].
- 	^ method.!

Item was changed:
  ----- Method: Decompiler>>popIntoTemporaryVariable: (in category 'instruction decoding') -----
  popIntoTemporaryVariable: offset
  	| maybeTVTag tempVector start |
  	maybeTVTag := stack last.
  	((maybeTVTag isMemberOf: Association)
  	 and: [maybeTVTag key == #pushNewArray]) ifTrue:
+ 		[blockStartsToTempVars notNil "implies we were intialized with temp names."
+ 			ifTrue: "Use the provided temps"
+ 				[self assert: ((tempVector := tempVars at: offset + 1 ifAbsent: [ParseNode basicNew]) isTemp
+ 							 and: [tempVector isIndirectTempVector
+ 							 and: [tempVector remoteTemps size = maybeTVTag value size]])]
+ 			ifFalse: "Synthesize some remote temps"
+ 				[tempVector := maybeTVTag value.
+ 				 offset + 1 <= tempVars size
+ 					ifTrue:
+ 						[start := 2.
+ 						 tempVector at: 1 put: (tempVars at: offset + 1)]
+ 					ifFalse:
+ 						[tempVars := (Array new: offset + 1)
+ 										replaceFrom: 1
+ 										to: tempVars size
+ 										with: tempVars.
+ 						start := 1].
+ 				 start to: tempVector size do:
+ 					[:i|
+ 					tempVector
+ 						at: i
+ 						put: (constructor
+ 								codeTemp: numLocalTemps + offset + i - 1
+ 								named: 't', (tempVarCount + i) printString)].
+ 				tempVars at: offset + 1 put: (constructor codeRemoteTemp: offset + 1 remoteTemps: tempVector)].
+ 		 tempVarCount := tempVarCount + maybeTVTag value size.
- 		[tempVector := maybeTVTag value.
- 		 offset + 1 <= tempVars size
- 			ifTrue:
- 				[start := 2.
- 				 tempVector at: 1 put: (tempVars at: offset + 1)]
- 			ifFalse:
- 				[tempVars := (Array new: offset + 1)
- 								replaceFrom: 1
- 								to: tempVars size
- 								with: tempVars.
- 				start := 1].
- 		 start to: tempVector size do:
- 			[:i|
- 			tempVector
- 				at: i
- 				put: (constructor codeTemp: numLocalTemps + offset + i - 1)].
- 		 tempVars at: offset + 1 put: (constructor codeRemoteTemp: offset + 1 remoteTemps: tempVector).
  		 stack removeLast.
  		 ^self].
  	self pushTemporaryVariable: offset; doStore: statements!

Item was changed:
  ----- Method: TempVariableNode>>addWriteWithin:at: (in category 'code generation (closures)') -----
  addWriteWithin: scopeBlock "<BlockNode>" at: location "<Integer>"
  	writingScopes ifNil: [writingScopes := Dictionary new].
+ 	(writingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location.
+ 	remoteNode ifNotNil:
+ 		[remoteNode addReadWithin: scopeBlock at: location]!
- 	(writingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location!

Item was changed:
  ----- Method: BlockNode>>computeCopiedValues: (in category 'code generation (closures)') -----
  computeCopiedValues: rootNode
  	| referencedValues |
  	referencedValues := rootNode referencedValuesWithinBlockExtent: blockExtent.
+ 	^((referencedValues reject: [:temp| temp isDefinedWithinBlockExtent: blockExtent])
+ 		asSortedCollection: ParseNode tempSortBlock)
+ 			asArray!
- 	^((referencedValues reject:
- 		[:temp| temp isDefinedWithinBlockExtent: blockExtent]) asSortedCollection:
- 			[:t1 :t2 | t1 index < t2 index]) asArray!

Item was changed:
  ----- Method: MethodNode>>printOn: (in category 'printing') -----
  printOn: aStream
  	| selectorNode |
  	selectorNode := self selectorNode.
  	precedence = 1
  		ifTrue:
  			[selectorNode isForFFICall
  				ifTrue: [selectorNode
  							printAsFFICallWithArguments: arguments
  							on: aStream
  							indent: 0]
  				ifFalse: [aStream nextPutAll: selectorNode key]]
  		ifFalse:
  			[selectorNode key keywords with: arguments do:
  				[:kwd :arg |
  				aStream nextPutAll: kwd; space; nextPutAll: arg key; space]].
  	comment == nil ifFalse:
  		[aStream crtab: 1.
  		 self printCommentOn: aStream indent: 1].
  	block printTemporaries: temporaries on: aStream doPrior: [aStream crtab: 1].
  	primitive > 0 ifTrue:
  		[(primitive between: 255 and: 519) ifFalse:  "Dont decompile quick prims  e.g, ^ self or ^instVar"
  			[aStream crtab: 1.
  			 self printPrimitiveOn: aStream]].
  	self printPropertiesOn: aStream.
+ 	self printPragmasOn: aStream.
  	aStream crtab: 1.
  	block printStatementsOn: aStream indent: 0!

Item was changed:
  ----- Method: MethodNode>>rawSourceRangesAndMethodDo: (in category 'source mapping') -----
  rawSourceRangesAndMethodDo: aBinaryBlock
  	"Evaluate aBinaryBlock with the rawSourceRanges and method generated from the receiver."
  
  	| methNode method |
+ 	methNode := encoder classEncoding parserClass new
+ 					encoderClass: encoder class;
+ 					parse: (sourceText "If no source, use decompile string as source to map from"
+ 							ifNil: [self decompileString]
+ 							ifNotNil: [sourceText])
+ 					class: self methodClass.
- 	methNode := sourceText
- 					ifNil: "No source, use decompile string as source to map from"
- 						[self parserClass new
- 							encoderClass: encoder class;
- 							parse: self decompileString
- 							class: self methodClass]
- 					ifNotNil: [self prepareForRegeneration.
- 							 self].
  	method := methNode generate: #(0 0 0 0).  "set bytecodes to map to"
  	^aBinaryBlock
  		value: methNode encoder rawSourceRanges
  		value: method!

Item was changed:
  ----- Method: BlockNode>>addHoistedTemps: (in category 'code generation (closures)') -----
  addHoistedTemps: additionalTemporaries "<SequenceableCollection>"
  	additionalTemporaries do:
+ 		[:temp|
+ 		temp definingScope ifNil:
+ 			[temp definingScope: self]].
+ 	temporaries := (temporaries isNil or: [temporaries isEmpty])
+ 					ifTrue: [additionalTemporaries copy]
+ 					ifFalse:
+ 						[temporaries last isIndirectTempVector
+ 							ifTrue: [temporaries allButLast, additionalTemporaries, { temporaries last }]
+ 							ifFalse: [temporaries, additionalTemporaries]]!
- 		[:temp| temp definingScope: self].
- 	temporaries := (temporaries == nil ifTrue: [#()] ifFalse: [temporaries]), additionalTemporaries!

Item was changed:
  ----- Method: Parser>>addPragma: (in category 'pragmas') -----
  addPragma: aPragma
+ 	properties := properties copyWith: aPragma!
- 	self properties addPragma: aPragma!

Item was changed:
  ----- Method: Decompiler>>jump:if: (in category 'instruction decoding') -----
  jump: dist if: condition
  
  	| savePc sign elsePc elseStart end cond ifExpr thenBlock elseBlock
+ 	  thenJump elseJump condHasValue isIfNil saveStack blockBody |
- 	  thenJump elseJump condHasValue isIfNil saveStack |
  	stack last == CascadeFlag ifTrue: [^ self case: dist].
  	elsePc := lastPc.
  	elseStart := pc + dist.
  	end := limit.
  	"Check for bfp-jmp to invert condition.
  	Don't be fooled by a loop with a null body."
  	sign := condition.
  	savePc := pc.
  	self interpretJump ifNotNil:
  		[:elseDist|
  		 (elseDist >= 0 and: [elseStart = pc]) ifTrue:
  			 [sign := sign not.  elseStart := pc + elseDist]].
  	pc := savePc.
  	ifExpr := stack removeLast.
  	(isIfNil := stack size > 0 and: [stack last == IfNilFlag]) ifTrue:
  		[stack removeLast].
  	saveStack := stack.
  	stack := OrderedCollection new.
  	thenBlock := self blockTo: elseStart.
  	condHasValue := hasValue or: [isIfNil].
  	"ensure jump is within block (in case thenExpr returns)"
  	thenJump := exit <= end ifTrue: [exit] ifFalse: [elseStart].
  	"if jump goes back, then it's a loop"
  	thenJump < elseStart
  		ifTrue:
  			["Must be a while loop...
+ 			  thenJump will jump to the beginning of the while expr.  In the case of while's
+ 			  with a block in the condition, the while expr should include more than just
+ 			  the last expression: find all the statements needed by re-decompiling."
- 			  thenJump will jump to the beginning of the while expr."
  			stack := saveStack.
+ 			pc := thenJump.
+ 			blockBody := self statementsTo: elsePc.
+ 			"discard unwanted statements from block"
+ 			blockBody size - 1 timesRepeat: [statements removeLast].
  			statements addLast:
  				(constructor
+ 					codeMessage: (constructor codeBlock: blockBody returns: false)
- 					codeMessage: (constructor codeBlock: { ifExpr } returns: false)
  					selector: (constructor
  								codeSelector: (sign
  												ifTrue: [#whileFalse:]
  												ifFalse: [#whileTrue:])
  								code: #macro)
  					arguments: { thenBlock }).
+ 			pc := elseStart.
  			self convertToDoLoop]
  		ifFalse:
  			["Must be a conditional..."
  			elseBlock := self blockTo: thenJump.
  			elseJump := exit.
  			"if elseJump is backwards, it is not part of the elseExpr"
  			elseJump < elsePc ifTrue:
  				[pc := lastPc].
  			cond := isIfNil
  						ifTrue:
  							[constructor
  								codeMessage: ifExpr ifNilReceiver
  								selector: (constructor
  											codeSelector: (sign ifTrue: [#ifNotNil:] ifFalse: [#ifNil:])
  											code: #macro)
  								arguments: (Array with: thenBlock)]
  						ifFalse:
  							[constructor
  								codeMessage: ifExpr
  								selector: (constructor codeSelector: #ifTrue:ifFalse: code: #macro)
  								arguments:	(sign
  												ifTrue: [{elseBlock. thenBlock}]
  												ifFalse: [{thenBlock. elseBlock}])].
  			stack := saveStack.
  			condHasValue
  				ifTrue: [stack addLast: cond]
  				ifFalse: [statements addLast: cond]]!

Item was changed:
  ----- Method: TempVariableNode>>printWithClosureAnalysisOn:indent: (in category 'printing') -----
  printWithClosureAnalysisOn: aStream indent: level 
  
+ 	aStream nextPutAll: name.
+ 	readingScopes notNil ifTrue:
+ 		[(readingScopes inject: Set new into: [:them :reads| them addAll: reads. them]) asSortedCollection do:
+ 			[:location|
+ 			aStream space; nextPut: $r; nextPut: $@; print: location]].
+ 	writingScopes notNil ifTrue:
+ 		[(writingScopes inject: Set new into: [:them :writes| them addAll: writes. them]) asSortedCollection do:
+ 			[:location|
+ 			aStream space; nextPut: $w; nextPut: $@; print: location]]!
- 	aStream nextPutAll: name!

Item was changed:
  ----- Method: Parser>>queryUndefined (in category 'error correction') -----
  queryUndefined
  	| varStart varName | 
+ 	varName := parseNode key.
+ 	varStart := self endOfLastToken + requestorOffset - varName size + 1.
- 	varName _ parseNode key.
- 	varStart _ self endOfLastToken + requestorOffset - varName size + 1.
  	requestor selectFrom: varStart to: varStart + varName size - 1; select.
  	(UndefinedVariable name: varName) ifFalse: [^ self fail]!

Item was changed:
  ----- Method: Decompiler>>initSymbols: (in category 'initialize-release') -----
  initSymbols: aClass
- 	| nTemps namedTemps |
  	constructor method: method class: aClass literals: method literals.
  	constTable := constructor codeConstants.
  	instVars := Array new: aClass instSize.
+ 	tempVarCount := method numTemps.
+ 	"(tempVars isNil
+ 	 and: [method holdsTempNames]) ifTrue:
+ 		[tempVars := method tempNamesString]."
+ 	tempVars isString
+ 		ifTrue:
+ 			[blockStartsToTempVars := self mapFromBlockStartsIn: method
+ 											toTempVarsFrom: tempVars
+ 											constructor: constructor.
+ 			 tempVars := blockStartsToTempVars at: method initialPC]
+ 		ifFalse:
+ 			[| namedTemps |
+ 			namedTemps := tempVars ifNil: [(1 to: tempVarCount) collect: [:i| 't', i printString]].
+ 			tempVars := (1 to: tempVarCount) collect:
+ 							[:i | i <= namedTemps size
+ 								ifTrue: [constructor codeTemp: i - 1 named: (namedTemps at: i)]
+ 								ifFalse: [constructor codeTemp: i - 1]]].
- 	nTemps := method numTemps.
- 	namedTemps := tempVars ifNil: [method tempNames].
- 	tempVars := (1 to: nTemps) collect:
- 				[:i | i <= namedTemps size
- 					ifTrue: [constructor codeTemp: i - 1 named: (namedTemps at: i)]
- 					ifFalse: [constructor codeTemp: i - 1]].
  	1 to: method numArgs do:
  		[:i|
  		(tempVars at: i) beMethodArg]!

Item was changed:
  ----- Method: Parser>>method:context:encoder: (in category 'expression types') -----
  method: doit context: ctxt encoder: encoderToUse
  	" pattern [ | temporaries ] block => MethodNode."
  
  	| sap blk prim temps messageComment methodNode |
+ 	properties := AdditionalMethodState new.
- 	properties := MethodProperties new.
  	encoder := encoderToUse.
  	sap := self pattern: doit inContext: ctxt.
  	"sap={selector, arguments, precedence}"
  	properties selector: (sap at: 1).
  	encoder selector: (sap at: 1).
  	(sap at: 2) do: [:argNode | argNode beMethodArg].
+ 	doit ifFalse: [self pragmaSequence].
- 	doit ifFalse: [ self pragmaSequence ].
  	temps := self temporaries.
  	messageComment := currentComment.
  	currentComment := nil.
+ 	doit ifFalse: [self pragmaSequence].
- 	doit ifFalse: [ self pragmaSequence ].
  	prim := self pragmaPrimitives.
  	self statements: #() innerBlock: doit.
  	blk := parseNode.
  	doit ifTrue: [blk returnLast]
  		ifFalse: [blk returnSelfIfNoOther: encoder].
  	hereType == #doIt ifFalse: [^self expected: 'Nothing more'].
  	self interactive ifTrue: [self removeUnusedTemps].
  	methodNode := self newMethodNode comment: messageComment.
+ 	^methodNode
- 	^ methodNode
  		selector: (sap at: 1)
  		arguments: (sap at: 2)
  		precedence: (sap at: 3)
  		temporaries: temps
  		block: blk
  		encoder: encoder
  		primitive: prim
  		properties: properties!

Item was changed:
  ----- Method: MethodNode>>printPrimitiveOn: (in category 'printing') -----
+ printPrimitiveOn: aStream
- printPrimitiveOn: aStream 
  	"Print the primitive on aStream"
+ 	| primDecl |
+ 	primitive = 0 ifTrue:
+ 		[^self].
+ 	primitive = 120 ifTrue: "External call spec"
+ 		[^aStream print: encoder literals first].
- 	| primIndex primDecl |
- 	primIndex := primitive.
- 	primIndex = 0
- 		ifTrue: [^ self].
- 	primIndex = 120
- 		ifTrue: ["External call spec"
- 			^ aStream print: encoder literals first].
  	aStream nextPutAll: '<primitive: '.
+ 	primitive = 117
+ 		ifTrue:
+ 			[primDecl := encoder literals at: 1.
+ 			 (primDecl at: 2) asString printOn: aStream.
+ 			 (primDecl at: 1) ifNotNil:
+ 				[:moduleName|
+ 				aStream nextPutAll:' module: '.
+ 				moduleName asString printOn: aStream]]
+ 		ifFalse:
+ 			[aStream print: primitive].
+ 	self primitiveErrorVariableName ifNotNil:
+ 		[:primitiveErrorVariableName|
+ 		 aStream nextPutAll: ' error: '; nextPutAll: primitiveErrorVariableName].
- 	primIndex = 117
- 		ifTrue: [primDecl := encoder literals at: 1.
- 			aStream nextPut: $';
- 				
- 				nextPutAll: (primDecl at: 2);
- 				 nextPut: $'.
- 			(primDecl at: 1) notNil
- 				ifTrue: [aStream nextPutAll: ' module:';
- 						 nextPut: $';
- 						
- 						nextPutAll: (primDecl at: 1);
- 						 nextPut: $']]
- 		ifFalse: [aStream print: primIndex].
  	aStream nextPut: $>.
  	Smalltalk at: #Interpreter ifPresent:[:cls|
+ 		aStream nextPutAll: ' "',
+ 							((cls classPool at: #PrimitiveTable) at: primitive + 1),
+ 							'" ']!
- 		aStream nextPutAll: ' "'
- 				, ((cls classPool at: #PrimitiveTable)
- 						at: primIndex + 1) , '" '].!

Item was changed:
  ----- Method: BlockNode>>addRemoteTemp:rootNode: (in category 'code generation (closures)') -----
  addRemoteTemp: aTempVariableNode rootNode: rootNode "<MethodNode>"
+ 	"Add aTempVariableNode to my actualScope's sequence of
+ 	 remote temps.  If I am an optimized block then the actual
+ 	 scope is my actualScopeIfOptimized, otherwise it is myself."
  	temporaries isArray ifTrue:
  		[temporaries := temporaries asOrderedCollection].
  	remoteTempNode == nil ifTrue:
  		[remoteTempNode := RemoteTempVectorNode new
+ 								name: self remoteTempNodeName
- 								name: '<', blockExtent first printString, '-', blockExtent last printString, '>'
  								index: arguments size + temporaries size
  								type: LdTempType
  								scope: 0.
+ 		 actualScopeIfOptimized
+ 			ifNil:
+ 				[temporaries addLast: remoteTempNode.
+ 				 remoteTempNode definingScope: self]
+ 			ifNotNil: [actualScopeIfOptimized addHoistedTemps: { remoteTempNode }]].
- 		 temporaries addLast: remoteTempNode.
- 		 remoteTempNode definingScope: self].
  	remoteTempNode addRemoteTemp: aTempVariableNode encoder: rootNode encoder.
+ 	"use remove:ifAbsent: because the deferred analysis for optimized
+ 	 loops can result in the temp has already been hoised into the root."
+ 	temporaries remove: aTempVariableNode ifAbsent: [].
- 	temporaries remove: aTempVariableNode.
  	^remoteTempNode!

Item was changed:
  ----- Method: BlockNode>>analyseArguments:temporaries:rootNode: (in category 'code generation (closures)') -----
  analyseArguments: methodArguments temporaries: methodTemporaries rootNode: rootNode "<MethodNode>" "^<Sequence of: <TempVarNade>>"
  	"Top level entry-point for analysing temps within the hierarchy of blocks in the receiver's method.
  	 Answer the (possibly modified) sequence of temp vars.
  	 Need to hoist temps out of macro-optimized blocks into their actual blocks.
  	 Need to note reads and writes to temps from blocks other than their actual blocks to determine
  	 whether blocks can be local (simple slots within a block/method context) or remote (slots in
  	 indirection vectors that are shared between contexts by sharing indirection vectors).
  
  	 The algorithm is based on numbering temporary reads and writes and block extents.
  	 The index used for numbering starts at zero and is incremented on every block entry
  	 and block exit.  So the following
  		| a b blk r1 r2 t |
  		a := 1. b := 2. t := 0.
  		blk := [ | s | s := a + b. t := t + s].
  		r1 := blk value.
  		b := -100.
  		r2 := blk value.
  		r1 -> r2 -> t
  	is numbered as
  		method block 0 to: 6:
  		| a b blk r1 r2 t |
  		a w at 1 := 1. b w at 1 := 2. t w at 1 := 0.
  		blk w at 5 := [entry at 2 | s |
  					 t  w at 3 := t r at 3 + a r at 3 + b r at 3
  					] exit at 4.
  		r1 w at 5 := blk r at 5 value.
  		b w at 5 := nil.
  		r2 w at 5 := blk r at 5 value.
  		r1 r at 5 -> r2 r at 5 -> t r at 5
  	So:
+ 		b and blk cannot be copied because for both there exists a write @5 that follows a
- 		b and blk cannot be copied because fpr both there exists a write @5 that follows a
  			read @4 within block 2 through 4
+ 		t must be remote because there exists a write @3 within block (2 to: 4)
+ 	Complications are introduced by optimized blocks.  In the following temp is written to
+ 	after it is closed over by [ temp ] since the inlined block is executed more than once.
+ 		| temp coll |
+ 		coll := OrderedCollection new.
+ 		1 to: 5 do: [ :index | 
+ 			temp := index. 
+ 			coll add: [ temp ] ].
+ 		self assert: (coll collect: [:ea| ea value]) asArray = #(5 5 5 5 5)
+ 	In the following i is local to the block and must be initialized each time around the loop
+ 	but if the block is inlined it must be declared at method level.
+ 		| col |
+ 		col := OrderedCollection new.
+ 		1 to: 3 do: [ :each | | i | i := each. col add: [ i ]. i := i + 1 ].
+ 		self assert: (col collect: [ :each | each value ]) asArray = #(2 3 4)"
- 		t must be remote because there exists a write @3 within block (2 to: 4)"
  	self assert: (arguments isEmpty or: [arguments hasEqualElements: methodArguments]).
  	arguments := methodArguments asArray. "won't change"
  	self assert: (temporaries isNil or: [temporaries isEmpty or: [temporaries hasEqualElements: methodTemporaries]]).
  	temporaries := OrderedCollection withAll: methodTemporaries.
  
  	self assert: optimized not. "the top-level block should not be optimized."
+ 	self analyseTempsWithin: self rootNode: rootNode assignmentPools: Dictionary new.
- 	self analyseTempsWithin: self rootNode: rootNode.
  
  	"The top-level block needs to reindex temporaries since analysis may have rearranged them.
+ 	 This happens when temps are made remote and/or a remote node is added."
- 	 This happens during sizing for nested blocks."
  	temporaries withIndexDo:
  		[:temp :offsetPlusOne| temp index: arguments size + offsetPlusOne - 1].
  
  	"Answer the (possibly modified) sequence of temps."
  	^temporaries asArray!

Item was changed:
  ----- Method: MethodNode>>selector:arguments:precedence:temporaries:block:encoder:primitive: (in category 'initialize-release') -----
  selector: selOrFalse arguments: args precedence: p temporaries: temps block: blk encoder: anEncoder primitive: prim 
+ 	"Initialize the receiver with respect to the arguments given."
+ 
+ 	encoder := anEncoder.
+ 	selectorOrFalse := selOrFalse.
+ 	precedence := p.
+ 	arguments := args.
+ 	temporaries := temps.
+ 	block := blk.
+ 	primitive := prim!
- 	
- 	self 
- 		selector: selOrFalse
- 		arguments: args
- 		precedence: p
- 		temporaries: temps
- 		block: blk encoder:
- 		anEncoder 
- 		primitive: prim 
- 		properties: MethodProperties new.!

Item was changed:
  ----- Method: DecompilerConstructorForClosures>>codeMethod:block:tempVars:primitive:class: (in category 'constructor') -----
  codeMethod: selector block: block tempVars: vars primitive: primitive class: class
  
+ 	| blockNode selectorNode visibleTemps invisibleTemps arguments temporaries |
+ 	selectorNode := self codeSelector: selector code: nil.
- 	| node visibleTemps invisibleTemps arguments temporaries |
- 	node := self codeSelector: selector code: nil.
  	tempVars := vars.
  	visibleTemps := OrderedCollection new.
  	invisibleTemps := OrderedCollection new.
  	tempVars do: [:t|
  				   ((t isIndirectTempVector or: [t scope >= 0])
  						ifTrue: [visibleTemps]
  						ifFalse: [invisibleTemps]) addLast: t].
  	arguments := visibleTemps copyFrom: 1 to: nArgs.
  	temporaries := visibleTemps copyFrom: nArgs + 1 to: visibleTemps size.
  	block
  		arguments: arguments;
  		temporaries: temporaries.
+ 	blockNode := BytecodeAgnosticMethodNode new
+ 		selector: selectorNode
- 	^BytecodeAgnosticMethodNode new
- 		selector: node
  		arguments: arguments
  		precedence: selector precedence
  		temporaries: temporaries
  		block: block
  		encoder: (EncoderForV3PlusClosures new initScopeAndLiteralTables
  					temps: visibleTemps, invisibleTemps
  					literals: literalValues
  					class: class)
  		primitive: primitive
+ 		properties: method properties copy.
+ 	blockNode properties method: blockNode.
+ 	^blockNode!
- 		properties: method properties!

Item was changed:
  ----- Method: Decompiler>>decompile:in:method:using: (in category 'public access') -----
  decompile: aSelector in: aClass method: aMethod using: aConstructor
  
+ 	| block node |
- 	| block |
  	constructor := aConstructor.
  	method := aMethod.
  	self initSymbols: aClass.  "create symbol tables"
  	method isQuick
  		ifTrue: [block := self quickMethod]
  		ifFalse: 
  			[stack := OrderedCollection new: method frameSize.
  			caseExits := OrderedCollection new.
  			statements := OrderedCollection new: 20.
  			numLocalTemps := 0.
  			super method: method pc: method initialPC.
+ 			"skip primitive error code store if necessary"
+ 			(method primitive ~= 0 and: [self willStore]) ifTrue:
+ 				[pc := pc + 2.
+ 				 tempVars := tempVars asOrderedCollection].
  			block := self blockTo: method endPC + 1.
  			stack isEmpty ifFalse: [self error: 'stack not empty']].
+ 	node := constructor
+ 				codeMethod: aSelector
+ 				block: block
+ 				tempVars: tempVars
+ 				primitive: method primitive
+ 				class: aClass.
+ 	method primitive > 0 ifTrue:
+ 		[node removeAndRenameLastTempIfErrorCode].
+ 	^node!
- 	^(constructor
- 		codeMethod: aSelector
- 		block: block
- 		tempVars: tempVars
- 		primitive: method primitive
- 		class: aClass)
- 			accept: TempNumberNormalizingVisitor new;
- 			yourself!

Item was changed:
  ----- Method: Decompiler>>withTempNames: (in category 'initialize-release') -----
+ withTempNames: tempNames "<Array|String>"
+ 	"Optionally initialize the temp names to be used when decompiling.
+ 	 For backward-copmpatibility, if tempNames is an Array it is a single
+ 	 vector of temp names, probably for a blue-book-compiled method.
+ 	 If tempNames is a string it is a schematic string that encodes the
+ 	 layout of temp vars in the method and any closures/blocks within it.
+ 	 Decoding encoded tempNames is done in decompile:in:method:using:
+ 	 which has the method from which to derive blockStarts.
+ 	 See e.g. BytecodeEncoder>>schematicTempNamesString for syntax."
+ 	tempVars := tempNames!
- withTempNames: tempNameArray
- 	tempVars := tempNameArray!

Item was changed:
  ----- Method: Decompiler class>>recompileAllTest (in category 'testing') -----
  recompileAllTest
+ 	"[Decompiler recompileAllTest]"
- 	"[self recompileAllTest]"
  	"decompile every method and compile it back; if the decompiler is correct then the system should keep running.  :)"
  	
  	| decompiled ast compiled |
  	SystemNavigation default allBehaviorsDo: [ :behavior |
  		Utilities informUser: (behavior printString) during: [
  			behavior selectors do: [ :sel |
  				decompiled := Decompiler new decompile: sel in: behavior.
  				ast := Compiler new compile: decompiled in: behavior notifying: nil ifFail: [ self error: 'failed' ].
  				compiled := ast generate: (behavior compiledMethodAt: sel) trailer.
  				behavior addSelector: sel withMethod: compiled. ] ] ]!

Item was changed:
  ----- Method: Decompiler>>decompileBlock: (in category 'public access') -----
  decompileBlock: aBlock 
  	"Decompile aBlock, returning the result as a BlockNode.  
  	Show temp names from source if available."
  	"Decompiler new decompileBlock: [3 + 4]"
+ 	| startpc end homeClass blockNode methodNode home source |
- 	| startpc end homeClass blockNode tempNames home source |
  	(home := aBlock home) ifNil: [^ nil].
  	method := home method.
  	(homeClass := home who first) == #unknown ifTrue: [^ nil].
  	constructor := self constructorForMethod: aBlock method.
+ 	method fileIndex ~~ 0 ifTrue: "got any source code?"
+ 		[source := [method getSourceFromFile]
- 	method fileIndex ~~ 0
- 		ifTrue: ["got any source code?"
- 			source := [method getSourceFromFile]
  						on: Error
  						do: [:ex | ^ nil].
+ 		 methodNode := [homeClass compilerClass new
+ 								parse: source
+ 								in: homeClass
+ 								notifying: nil]
+ 							on: (Smalltalk classNamed: 'SyntaxErrorNotification')
+ 							do: [:ex | ^ nil].
+ 		 self withTempNames: methodNode schematicTempNamesString].
- 			tempNames := ([homeClass compilerClass new
- 						parse: source
- 						in: homeClass
- 						notifying: nil]
- 						on: (Smalltalk classNamed: 'SyntaxErrorNotification')
- 						do: [:ex | ^ nil]) tempNames.
- 			self withTempNames: tempNames].
  	self initSymbols: homeClass.
  	startpc := aBlock startpc.
  	end := aBlock isClosure
  				ifTrue: [(method at: startpc - 2) * 256
  					  + (method at: startpc - 1) + startpc - 1]
  				ifFalse:
+ 					[(method at: startpc - 2) \\ 16 - 4 * 256
+ 					+ (method at: startpc - 1) + startpc - 1].
- 					[(method at: startpc - 2)
- 						\\ 16 - 4 * 256
- 						+ (method at: startpc - 1) + startpc - 1].
  	stack := OrderedCollection new: method frameSize.
  	caseExits := OrderedCollection new.
  	statements := OrderedCollection new: 20.
  	super
  		method: method
  		pc: (aBlock isClosure ifTrue: [startpc - 4] ifFalse: [startpc - 5]).
  	aBlock isClosure ifTrue:
  		[numLocalTemps := #decompileBlock: "Get pushClosureCopy... to hack fake temps for copied values"].
  	blockNode := self blockTo: end.
  	stack isEmpty ifFalse: [self error: 'stack not empty'].
  	^blockNode statements first!

Item was changed:
  ----- Method: Parser>>pragmaPrimitives (in category 'pragmas') -----
  pragmaPrimitives
+ 	| primitives |
+ 	properties isEmpty ifTrue:
+ 		[^0].
+ 	primitives := properties pragmas select:
+ 					[:pragma|
+ 					self class primitivePragmaSelectors includes: pragma keyword].
+ 	primitives isEmpty ifTrue:
+ 		[^0].
+ 	primitives size > 1 ifTrue:
+ 		[^self notify: 'Ambigous primitives'].
+ 	^self perform: primitives first keyword withArguments: primitives first arguments!
- 	| pragmas primitives |
- 	self properties pragmas isEmpty
- 		ifTrue: [ ^ 0 ].
- 	pragmas := Pragma allNamed: #primitive from: self class to: Parser.
- 	primitives := self properties pragmas select: [ :prim |
- 		pragmas anySatisfy: [ :prag | 
- 			prag selector = prim keyword ] ].
- 	primitives isEmpty 
- 		ifTrue: [ ^ 0 ].
- 	primitives size = 1 
- 		ifFalse: [ ^ self notify: 'Ambigous primitives' ].
- 	^ primitives first message sendTo: self!

Item was changed:
  ----- Method: Parser>>removeUnusedTemps (in category 'error correction') -----
  removeUnusedTemps
  	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
  
  	| str end start madeChanges | 
+ 	madeChanges := false.
+ 	str := requestor text asString.
- 	madeChanges _ false.
- 	str _ requestor text string.
  	((tempsMark between: 1 and: str size)
  		and: [(str at: tempsMark) = $|]) ifFalse: [^ self].
  	encoder unusedTempNames do:
  		[:temp |
  		(UnusedVariable name: temp) ifTrue:
+ 			[(encoder encodeVariable: temp) isUndefTemp
+ 				ifTrue:
+ 					[end := tempsMark.
+ 					["Beginning at right temp marker..."
+ 					start := end - temp size + 1.
+ 					end < temp size or: [temp = (str copyFrom: start to: end)
+ 							and: [(str at: start-1) isSeparator & (str at: end+1) isSeparator]]]
+ 						whileFalse:
+ 							["Search left for the unused temp"
+ 							end := requestor nextTokenFrom: end direction: -1].
+ 					end < temp size ifFalse:
+ 						[(str at: start-1) = $  ifTrue: [start := start-1].
+ 						requestor correctFrom: start to: end with: ''.
+ 						str := str copyReplaceFrom: start to: end with: ''. 
+ 						madeChanges := true.
+ 						tempsMark := tempsMark - (end-start+1)]]
+ 				ifFalse:
+ 					[self inform:
+ 'You''ll first have to remove the\statement where it''s stored into' withCRs]]].
+ 	madeChanges ifTrue: [ReparseAfterSourceEditing signal]!
- 		[(encoder encodeVariable: temp) isUndefTemp
- 			ifTrue:
- 			[end _ tempsMark.
- 			["Beginning at right temp marker..."
- 			start _ end - temp size + 1.
- 			end < temp size or: [temp = (str copyFrom: start to: end)
- 					and: [(str at: start-1) isSeparator & (str at: end+1) isSeparator]]]
- 			whileFalse:
- 				["Search left for the unused temp"
- 				end _ requestor nextTokenFrom: end direction: -1].
- 			end < temp size ifFalse:
- 				[(str at: start-1) = $  ifTrue: [start _ start-1].
- 				requestor correctFrom: start to: end with: ''.
- 				str _ str copyReplaceFrom: start to: end with: ''. 
- 				madeChanges _ true.
- 				tempsMark _ tempsMark - (end-start+1)]]
- 			ifFalse:
- 			[self inform:
- 'You''ll first have to remove the
- statement where it''s stored into']]].
- 	madeChanges ifTrue: [ParserRemovedUnusedTemps signal]!

Item was changed:
  ----- Method: ParseNode>>printCommentOn:indent: (in category 'printing') -----
  printCommentOn: aStream indent: indent 
  	| thisComment |
  	self comment == nil ifTrue: [^ self].
  	1 to: self comment size
  	   do: [:index |
  		index > 1 ifTrue: [aStream crtab: indent].
  		aStream nextPut: $".
  		thisComment := self comment at: index.
  		self printSingleComment: thisComment
  			on: aStream
  			indent: indent.
+ 		aStream nextPut: $"]!
- 		aStream nextPut: $"].
- 	self comment: nil!

Item was changed:
  ----- Method: TempVariableNode>>isDefinedWithinBlockExtent: (in category 'code generation (closures)') -----
  isDefinedWithinBlockExtent: anInterval
+ 	^anInterval rangeIncludes: definingScope actualScope blockExtent first!
- 	^anInterval rangeIncludes: definingScope blockExtent first!

Item was changed:
  ----- Method: BlockNode>>printTemporaries:on:doPrior: (in category 'printing') -----
  printTemporaries: tempSequence on: aStream doPrior: aBlock
  	"Print any in-scope temporaries.  If there are any evaluate aBlock
  	 prior to printing.  Answer whether any temporaries were printed."
+ 	| tempStream seen |
+ 	tempSequence ifNil:
+ 		[^false].
+ 	tempStream := (String new: 16) writeStream.
+ 	"This is for the decompiler which canmot work out which optimized block a particular temp is
+ 	 local to and hence may produce diplicates as in
+ 		expr ifTrue: [| aTemp | ...] ifFalse: [| aTemp | ...]"
+ 	seen := Set new.
- 	(tempSequence == nil
- 	 or: [tempSequence size = 0
- 	 or: [tempSequence allSatisfy: [:temp|
- 								   temp scope < 0
- 								   and: [temp isIndirectTempVector not]]]]) ifTrue:
- 		[^false].
- 	aBlock value.
- 	aStream nextPut: $|.
  	tempSequence do:
  		[:tempNode |
  		tempNode isIndirectTempVector
  			ifTrue:
  				[tempNode remoteTemps do:
  					[:tempVariableNode|
+ 					 (tempVariableNode scope >= 0
+ 					  and: [(seen includes: tempNode key) not]) ifTrue:
+ 						[tempStream space; nextPutAll: (seen add: tempVariableNode key)]]]
- 					 tempVariableNode scope >= 0 ifTrue:
- 						[aStream space; nextPutAll: tempVariableNode key]]]
  			ifFalse:
+ 				[(tempNode scope >= -1
+ 				  and: ["This is for the decompiler which may create a block arg when converting
+ 						a while into a to:do: but won't remove it form temporaries"
+ 					   tempNode isBlockArg not
+ 				  and: [(seen includes: tempNode key) not]]) ifTrue:
+ 					[tempStream space; nextPutAll: (seen add: tempNode key)]]].
+ 	tempStream position = 0 ifTrue:
+ 		[^false].
+ 	aBlock value.
+ 	aStream nextPut: $|; nextPutAll: tempStream contents; space; nextPut: $|.
- 				[tempNode scope >= 0 ifTrue:
- 					[aStream space; nextPutAll: tempNode key]]].
- 	aStream
- 		space;
- 		nextPut: $|.
  	^true!

Item was changed:
  ----- Method: MethodNode>>generate: (in category 'code generation') -----
  generate: trailer 
  	"The receiver is the root of a parse tree. Answer a CompiledMethod. The
  	argument, trailer, is the references to the source code that is stored with 
  	every CompiledMethod."
  
+ 	| literals blkSize method nArgs nLits primErrNode stack strm |
- 	| blkSize nLits literals stack strm nArgs method |
  	self generate: trailer ifQuick: 
  		[:m |
  		literals := encoder allLiterals.
  		(nLits := literals size) > 255 ifTrue:
  			[^self error: 'Too many literals referenced'].
  		1 to: nLits do: [:lit | m literalAt: lit put: (literals at: lit)].
  		m properties: properties.
  		^m].
+ 	primErrNode := self primitiveErrorVariableName ifNotNil:
+ 						[encoder fixTemp: self primitiveErrorVariableName].
  	nArgs := arguments size.
+ 	blkSize := (block sizeForEvaluatedValue: encoder)
+ 				+ (primErrNode ifNil: [0] ifNotNil: [2 "We force store-long (129)"]).
- 	blkSize := block sizeForEvaluatedValue: encoder.
  	(nLits := (literals := encoder allLiterals) size) > 255 ifTrue:
  		[^self error: 'Too many literals referenced'].
  	method := CompiledMethod	"Dummy to allocate right size"
  				newBytes: blkSize
  				trailerBytes: trailer 
  				nArgs: nArgs
  				nTemps: encoder maxTemp
  				nStack: 0
  				nLits: nLits
  				primitive: primitive.
  	strm := ReadWriteStream with: method.
  	strm position: method initialPC - 1.
  	stack := ParseStack new init.
+ 	primErrNode ifNotNil: [primErrNode emitStore: stack on: strm].
  	block emitForEvaluatedValue: stack on: strm.
  	stack position ~= 1 ifTrue:
  		[^self error: 'Compiler stack discrepancy'].
  	strm position ~= (method size - trailer size) ifTrue:
  		[^self error: 'Compiler code size discrepancy'].
  	method needsFrameSize: stack size.
  	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
  	method properties: properties.
  	^method!

Item was changed:
  ----- Method: TempVariableNode>>addReadWithin:at: (in category 'code generation (closures)') -----
  addReadWithin: scopeBlock "<BlockNode>" at: location "<Integer>"
  	readingScopes ifNil: [readingScopes := Dictionary new].
+ 	(readingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location.
+ 	remoteNode ifNotNil:
+ 		[remoteNode addReadWithin: scopeBlock at: location]!
- 	(readingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location!

Item was changed:
  ----- Method: TempVariableNode>>analyseClosure: (in category 'code generation (closures)') -----
  analyseClosure: rootNode "<MethodNode>"
+ 	"Analyse whether the temporary needs to be made remote
+ 	 or not, and answer whether it was made remote.
+ 	 A temp cannot be local if it is written to remotely,
+ 	 or if it is written to after it is closed-over.  An exception
+ 	 is an inlined block argument that appears to be written
+ 	 remotely but is actually local to a block."
- 	"A temp cannot be local if it is written to remotely,
- 	  or if it is written to after it is closed-over."
  	| latestWrite |
+ 	self isBlockArg ifTrue: [^false].
+ 	remoteNode ifNotNil: [^false]. "If already remote, don't remote a second time"
  	latestWrite := 0.
  	((writingScopes notNil
  	 and: [writingScopes associations anySatisfy: [:assoc|
  			[:blockScope :refs|
  			refs do: [:write| latestWrite := write max: latestWrite].
  			"A temp cannot be local if it is written to remotely."
+ 			blockScope actualScope ~~ definingScope actualScope]
- 			blockScope ~~ definingScope]
  				value: assoc key value: assoc value]])
  	or: [readingScopes notNil
  		and: [readingScopes associations anySatisfy: [:assoc|
  				[:blockScope :refs|
  				 "A temp cannot be local if it is written to after it is closed-over."
+ 				 blockScope actualScope ~~ definingScope actualScope
- 				 blockScope ~~ definingScope
  				 and: [refs anySatisfy: [:read| read < latestWrite]]]
  					value: assoc key value: assoc value]]]) ifTrue:
+ 		[remoteNode := definingScope addRemoteTemp: self rootNode: rootNode.
+ 		 ^true].
+ 	^false!
- 		[remoteNode := definingScope addRemoteTemp: self rootNode: rootNode]!

Item was changed:
  ----- Method: Decompiler>>doClosureCopyCopiedValues:numArgs:blockSize: (in category 'control') -----
  doClosureCopyCopiedValues: blockCopiedValues numArgs: numArgs blockSize: blockSize
+ 	| savedTemps savedTempVarCount savedNumLocalTemps
+ 	  jump blockArgs blockTemps blockTempsOffset block |
- 	| savedTemps savedNumLocalTemps jump blockArgs blockTemps blockTempsOffset block |
  	savedTemps := tempVars.
+ 	savedTempVarCount := tempVarCount.
  	savedNumLocalTemps := numLocalTemps.
  	jump := blockSize + pc.
  	numLocalTemps := BlockLocalTempCounter tempCountForBlockAt: pc - 4 in: method.
- 	blockArgs := (1 to: numArgs) collect:
- 					[:i| (constructor codeTemp: i - 1) beBlockArg].
  	blockTempsOffset := numArgs + blockCopiedValues size.
+ 	(blockStartsToTempVars notNil "implies we were intialized with temp names."
+ 	 and: [blockStartsToTempVars includesKey: pc])
+ 		ifTrue:
+ 			[tempVars := blockStartsToTempVars at: pc]
+ 		ifFalse:
+ 			[blockArgs := (1 to: numArgs) collect:
+ 							[:i| (constructor
+ 									codeTemp: i - 1
+ 									named: 't', (tempVarCount + i) printString)
+ 								  beBlockArg].
+ 			blockTemps := (1 to: numLocalTemps) collect:
+ 							[:i| constructor
+ 									codeTemp: i + blockTempsOffset - 1
+ 									named: 't', (tempVarCount + i + numArgs) printString].
+ 			tempVars := blockArgs, blockCopiedValues, blockTemps].
- 	blockTemps := (1 to: numLocalTemps) collect:
- 					[:i| constructor codeTemp: i + blockTempsOffset - 1].
- 	tempVars := blockArgs, blockCopiedValues, blockTemps.
  	numLocalTemps timesRepeat:
  		[self interpretNextInstructionFor: self.
  		 stack removeLast].
+ 	tempVarCount := tempVarCount + numArgs + numLocalTemps.
  	block := self blockTo: jump.
  	stack addLast: (constructor
  					codeArguments: (tempVars copyFrom: 1 to: numArgs)
  					temps: (tempVars copyFrom: blockTempsOffset + 1 to: blockTempsOffset + numLocalTemps)
  					block: block).
  	tempVars := savedTemps.
+ 	tempVarCount := savedTempVarCount.
  	numLocalTemps := savedNumLocalTemps!

Item was changed:
  ----- Method: TempVariableNode>>index: (in category 'code generation (closures)') -----
  index: anInteger
+ 	"For renumbering temps in the closure compiler."
- 	"For renumbering temps in the closure compiler.
- 	 Intended to be used only in BlockNode>>postNumberingProcessTemps:"
  	index := anInteger.
  	code := self code: index type: LdTempType!

Item was changed:
  ----- Method: Encoder>>doItInContextName (in category 'encoding') -----
  doItInContextName
+ 	^'ThisContext'!
- 	^'_thisContext'!

Item was changed:
  ----- Method: Compiler>>evaluate:in:to:notifying:ifFail:logged: (in category 'public access') -----
  evaluate: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag
+ 	"Compiles the sourceStream into a parse tree, then generates code into a 
+ 	method. This method is then installed in the receiver's class so that it 
+ 	can be invoked. In other words, if receiver is not nil, then the text can 
+ 	refer to instance variables of that receiver (the Inspector uses this). If 
+ 	aContext is not nil, the text can refer to temporaries in that context (the 
+ 	Debugger uses this). If aRequestor is not nil, then it will receive a 
+ 	notify:at: message before the attempt to evaluate is aborted. Finally, the 
+ 	compiled method is invoked from here as DoIt or (in the case of 
+ 	evaluation in aContext) DoItIn:. The method is subsequently removed 
+ 	from the class, but this will not get done if the invocation causes an 
+ 	error which is terminated. Such garbage can be removed by executing: 
+ 	Smalltalk allBehaviorsDo: [:cl | cl removeSelector: #DoIt; removeSelector: 
+ 	#DoItIn:]."
- 	"Compiles the sourceStream into a parse tree, then generates code into a method. In other words, if receiver is not nil, then the text can refer to instance variables of that receiver (the Inspector uses this). If aContext is not nil, the text can refer to temporaries in that context (the Debugger uses this). If aRequestor is not nil, then it will receive a notify:at: message before the attempt to evaluate is aborted. Finally, the compiled method is directly invoked without modifying the receiving-class."
  
+ 	| methodNode method value toLog itsSelection itsSelectionString |
+ 	class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class.
- 	| methodNode method value toLog itsSelectionString itsSelection |
- 	class := (aContext isNil 
- 		ifTrue: [ receiver ] 
- 		ifFalse: [ aContext receiver ])
- 			class.
  	self from: textOrStream class: class context: aContext notifying: aRequestor.
+ 	methodNode := self translate: sourceStream noPattern: true ifFail:
+ 		[^failBlock value].
+ 	method := methodNode generate: #(0 0 0 0).
+ 	self interactive ifTrue:
+ 		[method := method copyWithTempsFromMethodNode: methodNode].
+ 	
+ 	value := receiver
+ 				withArgs: (context ifNil: [#()] ifNotNil: [{context}])
+ 				executeMethod: method.
+ 
+ 	logFlag ifTrue:[
+ 		toLog := ((requestor respondsTo: #selection)  
+ 			and:[(itsSelection := requestor selection) notNil
+ 			and:[(itsSelectionString := itsSelection asString) isEmptyOrNil not]])
+ 				ifTrue:[itsSelectionString]
+ 				ifFalse:[sourceStream contents].
+ 		SystemChangeNotifier uniqueInstance evaluated: toLog context: aContext].
+ 	^ value!
- 	methodNode := self 
- 		translate: sourceStream
- 		noPattern: true 
- 		ifFail: [ ^ failBlock value ].
- 	method := methodNode generate.
- 	method selector ifNil: [method selector: #DoIt].
- 	self interactive
- 		ifTrue: [ method := method copyWithTempNames: methodNode tempNames ].
- 	value := receiver 
- 		withArgs: (context isNil
- 			ifTrue: [ #() ]
- 			ifFalse: [ Array with: aContext ])
- 		executeMethod: method.
- 	logFlag ifTrue:
- 		[toLog := ((requestor respondsTo: #selection)  and:
- 			[(itsSelection := requestor selection) notNil] and:
- 			[(itsSelectionString := itsSelection asString) isEmptyOrNil not] )
- 			ifTrue: 
- 				[itsSelectionString]
- 			ifFalse:
- 				[sourceStream contents].
- 		SystemChangeNotifier uniqueInstance evaluated: toLog context: aContext ].
- 	^ value.!

Item was removed:
- ----- Method: CascadeNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	{ receiver }, messages do:
- 		[:node| node analyseTempsWithin: scopeBlock rootNode: rootNode]!

Item was removed:
- ----- Method: PrimitiveNode>>printPrimitiveOn: (in category 'as yet unclassified') -----
- printPrimitiveOn: aStream 
- 	"Print the primitive on aStream"
- 
- 	| primIndex primDecl |
- 	primIndex := primitiveNum.
- 	primIndex = 0 ifTrue: [^ self].
- 	primIndex = 120 ifTrue: [
- 		"External call spec"
- 		^ aStream print: spec].
- 	aStream nextPutAll: '<primitive: '.
- 	primIndex = 117 ifTrue: [
- 		primDecl := spec.
- 		aStream nextPut: $';
- 			nextPutAll: (primDecl at: 2);
- 			nextPut: $'.
- 		(primDecl at: 1) ifNotNil: [
- 			aStream nextPutAll: ' module: ';
- 				nextPut: $';
- 				nextPutAll: (primDecl at: 1);
- 				nextPut: $'].
- 	] ifFalse: [aStream print: primIndex].
- 	aStream nextPut: $>.
- 	(primIndex ~= 117 and: [primIndex ~= 120]) ifTrue: [
- 		Smalltalk at: #Interpreter ifPresent: [:cls |
- 			aStream nextPutAll: ' "', 
- 				((cls classPool at: #PrimitiveTable) at: primIndex + 1) , '" '
- 		].
- 	].
- !

Item was removed:
- ----- Method: TempVariableNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	self addReadWithin: scopeBlock at: rootNode locationCounter!

Item was removed:
- ----- Method: MessageNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	special > 0 ifTrue:
- 		[receiver ifOptimizedBlockHoistTempsInto: scopeBlock.
- 		 "caseOf: is complicated.  We need to handle it specially.
- 		  The cases are within a BraceNode where each case is of the form
- 			[guard block] -> [action block]"
- 		 (selector key beginsWith: 'caseOf:') ifTrue:
- 			[arguments first elements do:
- 				[:messageNode|
- 				messageNode receiver ifOptimizedBlockHoistTempsInto: scopeBlock.
- 				messageNode arguments first ifOptimizedBlockHoistTempsInto: scopeBlock]].
- 		 arguments do:
- 			[:node|
- 			node == nil ifFalse: "last argument of optimized to:do: can be nil"
- 				[node ifOptimizedBlockHoistTempsInto: scopeBlock]]].
- 
- 	"receiver is nil in cascades"
- 	receiver == nil ifFalse:
- 		[receiver analyseTempsWithin: scopeBlock rootNode: rootNode].
- 	arguments do:
- 		[:node|
- 		node == nil ifFalse: "last argument of optimized to:do: can be nil"
- 			[node analyseTempsWithin: scopeBlock rootNode: rootNode]]!

Item was removed:
- ----- Method: ReturnNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	"Note we could do this:
- 		scopeBlock ~~ rootNode block ifTrue:
- 			[scopeBlock noteNonLocalReturn].
- 	 and pass up the flag in <BlockNode>>>analyseTempsWithin:rootNode:
- 	 which may be fast but may also screw up the debugger.  For now we
- 	 consider clean blocks a premature optimization."
- 	self flag: 'consider clean blocks'.
- 	expr analyseTempsWithin: scopeBlock rootNode: rootNode!

Item was removed:
- ----- Method: BlockNode>>postNumberingProcessTemps: (in category 'code generation (closures)') -----
- postNumberingProcessTemps: rootNode "<MethodNode>"
- 	(temporaries isNil or: [temporaries isEmpty]) ifTrue:
- 		["Add all arguments to the pool so that copiedValues can be computed during sizing."
- 		 rootNode addLocalsToPool: arguments.
- 		 ^self].
- 
- 	"A temp can be local (and copied if it is not written to after it is captured.
- 	 A temp cannot be local if it is written to remotely.
- 	 Need to enumerate a copy of the temporaries because any temps becoming remote
- 	 will be removed from temporaries in analyseClosure: (and a single remote temp node
- 	 will get added)"
- 	temporaries copy do:
- 		[:each| each analyseClosure: rootNode].
- 
- 	"Now we may have added a remoteTempNode.  So we need a statement to initialize it."
- 	remoteTempNode ~~ nil ifTrue:
- 		["statements isArray ifTrue:
- 			[statements := statements asOrderedCollection]." "true for decompiled trees"
- 		(statements notEmpty
- 		 and: [statements first isAssignmentNode
- 		 and: [statements first variable isTemp
- 		 and: [statements first variable isIndirectTempVector]]])
- 			ifTrue: "If this is a decompiled tree there already is a temp vector initialization node."
- 				[statements first variable become: remoteTempNode]
- 			ifFalse:
- 				[statements addFirst: (remoteTempNode nodeToInitialize: rootNode encoder)]].
- 
- 	"Now add all arguments and locals to the pool so that copiedValues can be computed during sizing."
- 	rootNode
- 		addLocalsToPool: arguments;
- 		addLocalsToPool: temporaries!

Item was removed:
- ----- Method: PrimitiveNode class>>null (in category 'as yet unclassified') -----
- null
- 
- 	^ self new num: 0!

Item was removed:
- ----- Method: NewArrayNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	"This is a no-op except in TempVariableNode"
- 	^self!

Item was removed:
- ----- Method: RemoteTempVectorNode>>cleanUpForRegeneration (in category 'debugger access') -----
- cleanUpForRegeneration
- 	super cleanUpForRegeneration.
- 	remoteTemps := nil!

Item was removed:
- ----- Method: TempNumberNormalizingVisitor>>initialize (in category 'initialize-release') -----
- initialize
- 	count := 0.
- 	temps := IdentitySet new!

Item was removed:
- ----- Method: BytecodeEncoder>>blockExtentsToTempRefs (in category 'temps') -----
- blockExtentsToTempRefs
- 	| blockExtentsToTempRefs |
- 	blockExtentsToLocals ifNil:
- 		[^nil].
- 	blockExtentsToTempRefs := Dictionary new.
- 	blockExtentsToLocals keysAndValuesDo:
- 		[:blockExtent :locals|
- 		blockExtentsToTempRefs
- 			at: blockExtent
- 			put: (locals collect:
- 					[:local|
- 					local isIndirectTempVector
- 						ifTrue: [local remoteTemps collect:
- 									[:remoteLocal| remoteLocal key]]
- 						ifFalse: [local key]])].
- 	^blockExtentsToTempRefs!

Item was removed:
- ----- Method: BlockNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	| blockStart |
- 	optimized ifTrue:
- 		[self assert: (temporaries isEmpty and: [arguments isNil or: [arguments size <= 1]]).
- 		 statements do:
- 			[:statement|
- 			 statement analyseTempsWithin: scopeBlock rootNode: rootNode].
- 		 ^self].
- 
- 	rootNode noteBlockEntry:
- 		[:entryNumber|
- 		 blockStart := entryNumber.
- 		 arguments notNil ifTrue: [arguments do: [:temp| temp definingScope: self]].
- 		 temporaries notNil ifTrue: [temporaries do: [:temp| temp definingScope: self]]].
- 
- 	statements do:
- 		[:statement|
- 		 statement analyseTempsWithin: self rootNode: rootNode].
- 
- 	rootNode noteBlockExit:
- 		[:exitNumber|
- 		 blockExtent := blockStart to: exitNumber].
- 
- 	self postNumberingProcessTemps: rootNode!

Item was removed:
- ----- Method: PrimitiveNode>>spec: (in category 'as yet unclassified') -----
- spec: literal
- 
- 	spec := literal!

Item was removed:
- ----- Method: RegenerationPreparingVisitor>>visitTempVariableNode: (in category 'visiting') -----
- visitTempVariableNode: aTempNode
- 	aTempNode cleanUpForRegeneration!

Item was removed:
- ----- Method: BlockNode>>cleanUpForRegeneration (in category 'debugger access') -----
- cleanUpForRegeneration
- 	arguments notNil ifTrue:
- 		[arguments do: [:temp| temp cleanUpForRegeneration]].
- 	temporaries notNil ifTrue:
- 		[temporaries do: [:temp| temp cleanUpForRegeneration]].
- 	(temporaries notNil
- 	 and: [temporaries notEmpty
- 	 and: [temporaries last isIndirectTempVector]]) ifTrue:
- 		[temporaries := temporaries allButLast.
- 		 (statements notEmpty
- 		  and: [statements first isAssignmentNode
- 		  and: [statements first variable isTemp
- 		  and: [statements first variable isIndirectTempVector]]]) ifTrue:
- 			[statements removeFirst]].
- 	remoteTempNode := nil!

Item was removed:
- ----- Method: PrimitiveNode>>num (in category 'as yet unclassified') -----
- num
- 
- 	^ primitiveNum!

Item was removed:
- ----- Method: PrimitiveNode>>sourceText (in category 'as yet unclassified') -----
- sourceText
- 
- 	^ String streamContents: [:stream |
- 		self printPrimitiveOn: stream]!

Item was removed:
- ----- Method: TempNumberNormalizingVisitor>>visitTempVariableNode: (in category 'visiting') -----
- visitTempVariableNode: aTempVariableNode
- 		self renumberTemp: aTempVariableNode!

Item was removed:
- ----- Method: BraceNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	elements do: [:node| node analyseTempsWithin: scopeBlock rootNode: rootNode]!

Item was removed:
- ----- Method: RegenerationPreparingVisitor>>visitBlockNode: (in category 'visiting') -----
- visitBlockNode: aBlockNode
- 	aBlockNode cleanUpForRegeneration.
- 	super visitBlockNode: aBlockNode!

Item was removed:
- ----- Method: BlockNode>>printTemporariesOn:indent: (in category 'printing') -----
- printTemporariesOn: aStream indent: level
- 
- 	(temporaries == nil or: [temporaries size = 0])
- 		ifFalse: 
- 			[aStream nextPut: $|.
- 			temporaries do: 
- 				[:arg | 
- 				aStream
- 					space;
- 					withStyleFor: #temporaryVariable
- 						do: [aStream nextPutAll: arg key]].
- 			aStream nextPutAll: ' | '.
- 			"If >0 args and >1 statement, put all statements on separate lines"
- 			statements size > 1 ifTrue: [aStream crtab: level]]!

Item was removed:
- ----- Method: Compiler class>>closureDecompilerClass (in category 'accessing') -----
- closureDecompilerClass
- 	^self error: 'not installed'.!

Item was removed:
- ----- Method: ParseNode>>ifOptimizedBlockHoistTempsInto: (in category 'code generation (closures)') -----
- ifOptimizedBlockHoistTempsInto: scopeBlock "<BlockNode>" 
- 	"This is a No-op for all nodes except non-optimized BlockNodes."
- 	^self!

Item was removed:
- ----- Method: BytecodeAgnosticMethodNode>>copiedValuesWithinBlockExtent: (in category 'code generation (closures)') -----
- copiedValuesWithinBlockExtent: anInterval 
- 	^((localsPool select:
- 		[:temp|
- 		 temp isReferencedWithinBlockExtent: anInterval]) collect:
- 			[:temp|
- 			temp isRemote ifTrue: [temp remoteNode] ifFalse: [temp]]) asSortedCollection:
- 				[:t1 :t2 |
- 				t1 index < t2 index]!

Item was removed:
- ----- Method: AssignmentNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>"  rootNode: rootNode "<MethodNode>"
- 	"N.B.  since assigment happens :=after:= the value is evaluated the value is sent the message :=first:=."
- 	value analyseTempsWithin: scopeBlock rootNode: rootNode.
- 	variable beingAssignedToAnalyseTempsWithin: scopeBlock rootNode: rootNode!

Item was removed:
- Object subclass: #PrimitiveNode
- 	instanceVariableNames: 'primitiveNum spec'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Compiler-ParseNodes'!
- 
- !PrimitiveNode commentStamp: 'ajh 3/24/2003 21:35' prior: 0!
- I represent a primitive.  I am more than just a number if I am a named primitive.
- 
- Structure:
- 
-  num	<Integer>	Primitive number.
-  spec	<Object>		Stored in first literal when num is 117 or 120.
- !

Item was removed:
- ----- Method: Compiler class>>closureParserClass (in category 'accessing') -----
- closureParserClass
- 	^self error: 'not installed'.!

Item was removed:
- ----- Method: BytecodeAgnosticMethodNode>>prepareForRegeneration (in category 'debugger support') -----
- prepareForRegeneration
- 	"Closure methods need to remove any remote temps prior to being regenerated."
- 	(temporaries notEmpty and: [temporaries last isIndirectTempVector]) ifTrue:
- 		[temporaries := temporaries allButLast].
- 	self accept: RegenerationPreparingVisitor new!

Item was removed:
- ----- Method: PrimitiveNode>>num: (in category 'as yet unclassified') -----
- num: n
- 
- 	primitiveNum := n!

Item was removed:
- ----- Method: VariableNode>>beingAssignedToAnalyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- beingAssignedToAnalyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	"No-op overridden by TempVariableNode"!

Item was removed:
- ----- Method: Parser>>properties (in category 'pragmas') -----
- properties
- 	^ properties ifNil: [ properties := MethodProperties new ]!

Item was removed:
- ----- Method: PrimitiveNode>>spec (in category 'as yet unclassified') -----
- spec
- 
- 	^ spec!

Item was removed:
- ParseNodeVisitor subclass: #RegenerationPreparingVisitor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Compiler-Support'!
- 
- !RegenerationPreparingVisitor commentStamp: '<historical>' prior: 0!
- I arrange that BlockNodes clean out any remote temps prior to being regenerated.!

Item was removed:
- ----- Method: TempVariableNode>>beingAssignedToAnalyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- beingAssignedToAnalyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	self addWriteWithin: scopeBlock at: rootNode locationCounter!

Item was removed:
- ----- Method: BytecodeAgnosticMethodNode>>blockExtentsToTempRefs (in category 'debugger support') -----
- blockExtentsToTempRefs
- 	| blockExtentsToTempRefs methNode |
- 	blockExtentsToTempRefs := encoder blockExtentsToTempRefs.
- 	blockExtentsToTempRefs ifNil:
- 		[methNode := sourceText
- 					ifNil: "No source, use decompile string as source to map from"
- 						[self parserClass new
- 							encoderClass: encoder class;
- 							parse: self decompileString
- 							class: self methodClass]
- 					ifNotNil: [self prepareForRegeneration.
- 							 self].
- 		methNode generate: #(0 0 0 0).  "set bytecodes to map to"
- 		 blockExtentsToTempRefs := methNode encoder blockExtentsToTempRefs].
- 	^blockExtentsToTempRefs!

Item was removed:
- ----- Method: TempNumberNormalizingVisitor>>visitBlockNode: (in category 'visiting') -----
- visitBlockNode: aBlockNode
- 	aBlockNode arguments do:
- 		[:tempNode|
- 		self renumberTemp: tempNode].
- 	aBlockNode temporaries do:
- 		[:tempNode|
- 		(tempNode scope >= 0 or: [tempNode isIndirectTempVector]) ifTrue:
- 			[self renumberTemp: tempNode]].
- 	super visitBlockNode: aBlockNode!

Item was removed:
- ----- Method: PrimitiveNode>>printOn: (in category 'as yet unclassified') -----
- printOn: aStream
- 
- 	aStream nextPutAll: 'primitive '; print: primitiveNum!

Item was removed:
- ----- Method: LeafNode>>analyseTempsWithin:rootNode: (in category 'code generation (closures)') -----
- analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
- 	"This is a no-op except in TempVariableNode"
- 	^self!

Item was removed:
- ----- Method: TempNumberNormalizingVisitor>>renumberTemp: (in category 'private') -----
- renumberTemp: tempNode
- 	| name newName |
- 	tempNode isIndirectTempVector ifTrue:
- 		[tempNode remoteTemps do:
- 			[:remoteTempNode| self renumberTemp: remoteTempNode].
- 		 ^self].
- 	(temps includes: tempNode) ifTrue: [^self].
- 	name := tempNode key.
- 	name size >= 2 ifFalse: [^self].
- 	name first = $t ifFalse: [^self].
- 	2 to: name size do:
- 		[:i|
- 		(name at: i) isDigit ifFalse: [^self]].
- 	newName := 't', (count := count + 1) printString.
- 	tempNode name: newName key: newName code: tempNode code.
- 	temps add: tempNode
- 	!

Item was removed:
- ParseNodeVisitor subclass: #TempNumberNormalizingVisitor
- 	instanceVariableNames: 'count temps'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Compiler-Support'!

Item was removed:
- ----- Method: MethodNode>>prepareForRegeneration (in category 'converting') -----
- prepareForRegeneration
- 	"Nothing to do for vanilla nodes."!

Item was removed:
- ----- Method: BlockNode>>ifOptimizedBlockHoistTempsInto: (in category 'code generation (closures)') -----
- ifOptimizedBlockHoistTempsInto: scopeBlock "<BlockNode>"
- 	"This is a No-op for all nodes except non-optimized BlockNodes."
- 	"Let's assume the special > 0 guard in MessageNode>>analyseTempsWithin:forValue:encoder: is correct.
- 	 Then we can simply hoist our temps up."
- 	self assert: (arguments isNil or: [arguments size <= 1]).
- 	(arguments notNil and: [arguments notEmpty]) ifTrue:
- 		[scopeBlock addHoistedTemps: arguments.
- 		arguments := #()].
- 	temporaries notEmpty ifTrue:
- 		[scopeBlock addHoistedTemps: temporaries.
- 		temporaries := #()]!




More information about the Squeak-dev mailing list