[squeak-dev] The Trunk: Compiler-eem.360.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 24 19:17:33 UTC 2017


Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.360.mcz

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

Name: Compiler-eem.360
Author: eem
Time: 24 December 2017, 11:17:18.883597 am
UUID: 28fc60ef-5fe3-4e38-a15c-e266f8aa3f72
Ancestors: Compiler-mt.359

Fix the Decompiler to remove the nil node that it mistakenly generates following a returning if with a nil else.  As a side-effect provide ParseNode>>nodesWithPreceedingStatementsDo:.

Recategorize the BlockNode>>statements accessors.

Fix a typo.  Remove a trio of methods that are now in EToys.

=============== Diff against Compiler-mt.359 ===============

Item was changed:
+ ----- Method: BlockNode>>statements (in category 'accessing') -----
- ----- Method: BlockNode>>statements (in category 'equation translation') -----
  statements
  	^statements!

Item was changed:
+ ----- Method: BlockNode>>statements: (in category 'accessing') -----
- ----- Method: BlockNode>>statements: (in category 'equation translation') -----
  statements: val
  	statements := val!

Item was removed:
- ----- Method: MessageNode>>morphFromKeywords:arguments:on:indent: (in category 'tiles') -----
- morphFromKeywords: key arguments: args on: parent indent: ignored
- 
- 	^parent
- 		messageNode: self 
- 		receiver: receiver 
- 		selector: selector 
- 		keywords: key 
- 		arguments: args
- !

Item was added:
+ ----- Method: MethodNode>>preenNilNodeFollowingNilIfNode: (in category 'converting-private') -----
+ preenNilNodeFollowingNilIfNode: aNilIfMessageNode
+ 	self nodesDo:
+ 		[:node| | statements indices |
+ 		 (node isBlockNode
+ 		  and: [(statements := node statements) includes: aNilIfMessageNode]) ifTrue:
+ 			[indices := (2 to: statements size) reject:
+ 							[:i|
+ 							(statements at: i) == NodeNil
+ 							and: [(statements at: i - 1) isNilIf]].
+ 			 node statements: (({1}, indices) collect: [:i| statements at: i])]]!

Item was changed:
  ----- Method: MethodNode>>preenTempsConflictingWithBlockNode: (in category 'converting-private') -----
  preenTempsConflictingWithBlockNode: temps
+ 	"Push temps that conflict with other blocks down into their narrowest enclosing block scope."
- 	"Push temps that conflict with other bocks down into their narrowest enclosing block scope."
  	temps do:
  		[:tempVar|
  		(self accept: (NarrowerVariableScopeFinder new ofVariable: tempVar)) ifNotNil:
  			[:enclosingScope |
  			 self assert: enclosingScope isBlockNode.
  			 self nodesDo:
  				[:node|
  				 ((node == self or: [node isBlockNode])
  				  and: [node temporaries includes: tempVar]) ifTrue:
  					[node temporaries: (node temporaries copyWithout: tempVar)]].
  			 enclosingScope temporaries: enclosingScope temporaries, { tempVar }]]!

Item was changed:
  ----- Method: MethodNode>>preenableNodes (in category 'converting-private') -----
  preenableNodes
  	"Answer a Dictionary from node or sequence of nodes to preen method selector for nodes
  	 in the tree that require post-processing after either a format or a decompile.  Such issues
  	 are the variable for an ifNotNil: which is local to the ifNotNil: block but, due to the inlining
  	 of ifNotNil: appears to be declared at the outer level, and, similarly, a temporary variable
  	 that conflicts with one of the same name in a block when, were the variable declared
  	 local to some inlined block it would no longer conflict.  The resulting dictionary is used to
  	 perform the value with the key (node or array) as argument to preen the tree."
  
  	| preenableNodes priorBlocks priorVariables |
  	preenableNodes := Dictionary new.
  	priorBlocks := OrderedCollection new.
  	priorVariables := Set new.
+ 	self nodesWithPreceedingStatementsDo:
+ 		[:node :preceedingStatementOrNil| | variable temps |
- 	self nodesDo:
- 		[:node| | variable temps |
  		(node isMessageNode
  		and: [node macroPrinter == #printIfNilNotNil:indent:
  		and: [node receiver isMessageNode
  		and: [node receiver selector key == #==
  		and: [node receiver receiver isAssignmentNode
  		and: [(variable := node receiver receiver variable) isTemp
  		and: [variable isRemote not
  		and: [variable isOnlySubnodeOf: node in: self]]]]]]]) ifTrue:
  			[preenableNodes at: node put: #preenIfNotNilNode:.
  			 priorVariables add: variable].
  		node isBlockNode ifTrue:
  			[temps := OrderedCollection new.
  			 node temporaries do:
  				[:temp|
  				 priorBlocks do:
  					[:aBlock|
  					 aBlock temporaries do:
  						[:priorTemp|
  						 (priorVariables includes: priorTemp) ifFalse:
  							[priorTemp key = temp key ifTrue:
  								[temps addLast: priorTemp]]]]].
  			 temps isEmpty ifFalse:
  				[preenableNodes at: temps put: #preenTempsConflictingWithBlockNode:].
+ 			 priorBlocks addLast: node].
+ 		(node == NodeNil
+ 		 and: [preceedingStatementOrNil notNil
+ 		 and: [preceedingStatementOrNil isMessageNode
+ 		 and: [preceedingStatementOrNil isNilIf]]]) ifTrue:
+ 			[preenableNodes at: preceedingStatementOrNil put: #preenNilNodeFollowingNilIfNode:]].
- 			 priorBlocks addLast: node]].
  	^preenableNodes!

Item was added:
+ ----- Method: ParseNode>>nodesWithPreceedingStatementsDo: (in category 'visiting') -----
+ nodesWithPreceedingStatementsDo: aBinaryBlock
+ 	self accept: (ParseNodeWithPreceedingStatementEnumerator ofBlock: aBinaryBlock)!

Item was added:
+ ParseNodeEnumerator subclass: #ParseNodeWithPreceedingStatementEnumerator
+ 	instanceVariableNames: 'preceedingStatement'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Compiler-Support'!

Item was added:
+ ----- Method: ParseNodeWithPreceedingStatementEnumerator>>ofBlock: (in category 'initialize-release') -----
+ ofBlock: aBlock
+ 	"N.B. This enumerator visits a node before any of the node's children.
+ 	 Hence, when enumewrating statements in a block, we can ensure that
+ 	 the second argument to the block, the preceeding statement, is non-nil
+ 	 only for top-level statements in the block by nilling out preceedingStatement
+ 	 once the block is evaluated. Perhaps stronger would be to capture its value
+ 	 in a temporary and nil it before evaluating, but this is good enough."
+ 	theBlock := [:node|
+ 				aBlock value: node value: preceedingStatement.
+ 				preceedingStatement := nil]!

Item was added:
+ ----- Method: ParseNodeWithPreceedingStatementEnumerator>>ofBlock:select: (in category 'initialize-release') -----
+ ofBlock: aBlock select: aSelectBlock
+ 	self ofBlock: aBlock.
+ 	theSelectBlock := aSelectBlock!

Item was added:
+ ----- Method: ParseNodeWithPreceedingStatementEnumerator>>visitBlockNode: (in category 'visiting') -----
+ visitBlockNode: aBlockNode
+ 	| savedPreceedingStatement |
+ 	(theSelectBlock isNil or: [theSelectBlock value: aBlockNode]) ifFalse:
+ 		[^nil].
+ 	theBlock value: aBlockNode.
+ 	savedPreceedingStatement := preceedingStatement.
+ 	preceedingStatement := nil.
+ 	[aBlockNode statements do:
+ 		[:statement|
+ 		 statement accept: self.
+ 		 preceedingStatement := statement]] ensure:
+ 		[preceedingStatement := savedPreceedingStatement]!

Item was removed:
- ----- Method: VariableNode>>currentValueIn: (in category 'tiles') -----
- currentValueIn: aContext
- 
- 	aContext ifNil: [^nil].
- 	^((self variableGetterBlockIn: aContext) ifNil: [^nil]) value printString
- 	
- 
- !

Item was removed:
- ----- Method: VariableNode>>variableGetterBlockIn: (in category 'tiles') -----
- variableGetterBlockIn: aContext
- 
- 	| temps tempIndex ivars |
- 
- 	(self type = 4 and: [self key isVariableBinding]) ifTrue: [
- 		^[self key value]
- 	].
- 	aContext ifNil: [^nil].
- 	self isSelfPseudoVariable ifTrue: [^[aContext receiver]].
- 	self type = 1 ifTrue: [
- 		ivars := aContext receiver class allInstVarNames.
- 		tempIndex := ivars indexOf: self name ifAbsent: [^nil].
- 		^[aContext receiver instVarAt: tempIndex]
- 	].
- 	self type = 2 ifTrue: [
- 		temps := aContext tempNames.
- 		tempIndex := temps indexOf: self name ifAbsent: [^nil].
- 		^[aContext tempAt: tempIndex]
- 	].
- 	^nil
- !



More information about the Squeak-dev mailing list