[Pkg] The Trunk: Compiler-eem.172.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 31 19:45:43 UTC 2010


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

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

Name: Compiler-eem.172
Author: eem
Time: 31 August 2010, 12:45:25.496 pm
UUID: cbf01579-162b-43d4-ab9e-1099261e3570
Ancestors: Compiler-nice.170

Fix decompilation/pretty-print of expr ifNotNil: [:var| which used to
be rendered as (var := expr) ifNotNil: [:var|.

=============== Diff against Compiler-nice.170 ===============

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitMessageNodeInCascade: (in category 'visiting') -----
  visitMessageNodeInCascade: aMessageNodeInCascade
+ 	(theSelectBlock isNil or: [theSelectBlock value: aMessageNodeInCascade]) ifFalse:
+ 		[^nil].
  	theBlock value: aMessageNodeInCascade.
  	^super visitMessageNodeInCascade: aMessageNodeInCascade!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitAssignmentNode: (in category 'visiting') -----
  visitAssignmentNode: anAssignmentNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: anAssignmentNode]) ifFalse:
+ 		[^nil].
  	theBlock value: anAssignmentNode.
  	^super visitAssignmentNode: anAssignmentNode!

Item was changed:
  ----- Method: BlockNode>>arguments (in category 'accessing') -----
  arguments
+ 	^arguments ifNil: [#()]!
- 	^arguments!

Item was added:
+ ----- Method: MethodNode>>preen (in category 'converting') -----
+ preen
+ 	"Preen for pretty-printing and/or decompilation.
+ 	 i.e. post-process to cover up for inadequacies in both algorithms.
+ 	 Currently one case, hiding the assignment to the arg of an inlined block arg to ifNotNil:,
+ 		(var := expr) ifNil: [...] ifNotNil: [...]    =>    expr ifNil: [...] ifNotNil: [:var| ...]."
+ 
+ 	self preenLocalIfNotNilArg!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitMessageNode: (in category 'visiting') -----
  visitMessageNode: aMessageNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aMessageNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aMessageNode.
  	^super visitMessageNode: aMessageNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitInstanceVariableNode: (in category 'visiting') -----
  visitInstanceVariableNode: anInstanceVariableNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: anInstanceVariableNode]) ifFalse:
+ 		[^nil].
  	theBlock value: anInstanceVariableNode.
  	^super visitInstanceVariableNode: anInstanceVariableNode!

Item was added:
+ ----- Method: ParseNodeEnumerator class>>ofBlock:select: (in category 'instance creation') -----
+ ofBlock: aBlock select: selectBlock
+ 	^self new ofBlock: aBlock select: selectBlock!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitSelectorNode: (in category 'visiting') -----
  visitSelectorNode: aSelectorNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aSelectorNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aSelectorNode.
  	^super visitSelectorNode: aSelectorNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitFutureNode: (in category 'visiting') -----
  visitFutureNode: aFutureNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aFutureNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aFutureNode.
  	^super visitFutureNode: aFutureNode!

Item was changed:
  ----- Method: Compiler>>format:noPattern:ifFail: (in category 'private') -----
  format: aStream noPattern: noPattern ifFail: failBlock
+ 	^(self parser
- 	^self parser
  		parse: aStream
  		class: class
  		noPattern: noPattern
  		context: context
  		notifying: requestor
+ 		ifFail: [^failBlock value]) preen!
- 		ifFail: [^failBlock value]!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitTempVariableNode: (in category 'visiting') -----
  visitTempVariableNode: aTempVariableNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aTempVariableNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aTempVariableNode.
  	^super visitTempVariableNode: aTempVariableNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitCascadeNode: (in category 'visiting') -----
  visitCascadeNode: aCascadeNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aCascadeNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aCascadeNode.
  	^super visitCascadeNode: aCascadeNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitCommentNode: (in category 'visiting') -----
  visitCommentNode: aCommentNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aCommentNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aCommentNode.
  	^super visitCommentNode: aCommentNode!

Item was added:
+ ----- Method: ParseNode>>isOnlySubnodeOf:in: (in category 'testing') -----
+ isOnlySubnodeOf: aSubtree "<ParseNode>" in: aParseTree "<ParseNode>"
+ 	"Answer if the receiver only occurs within aSubtree of aParseTree, not in the rest of aParseTree.
+ 	 Assumes that aSubtree is in fact a subnode of aParseTree."
+ 	| isSubnode |
+ 	isSubnode := false.
+ 	aSubtree accept: (ParseNodeEnumerator
+ 							ofBlock: [:node| node == self ifTrue: [isSubnode := true]]).
+ 	isSubnode ifFalse:
+ 		[^false].
+ 	aParseTree accept: (ParseNodeEnumerator
+ 							ofBlock: [:node| node == self ifTrue: [^false]]
+ 							select: [:node| node ~= aSubtree]).
+ 	^true!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitBlockNode: (in category 'visiting') -----
  visitBlockNode: aBlockNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aBlockNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aBlockNode.
  	^super visitBlockNode: aBlockNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitBraceNode: (in category 'visiting') -----
  visitBraceNode: aBraceNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aBraceNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aBraceNode.
  	^super visitBraceNode: aBraceNode!

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

Item was added:
+ ----- Method: MethodNode>>preenLocalIfNotNilArg (in category 'converting') -----
+ preenLocalIfNotNilArg
+ 	"Try and spot a (var := expr) ifNil: [...] ifNotNil: [...] where var is only used in the ifNotNil: block
+ 	 and convert it to expr ifNil: [...] ifNotNil: [:var| ...].  Deal both with the pretty-print case where
+ 	 the block already declares the variable and the decompile case where it does not."
+ 
+ 	| varsToHide |
+ 	varsToHide := Set new.
+ 	self nodesDo:
+ 		[:node| | variable |
+ 		(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:
+ 			[node arguments last arguments isEmpty
+ 				ifTrue: [node arguments last arguments: { variable }.
+ 						varsToHide add: variable]
+ 				ifFalse: [self assert: node arguments last arguments asArray =  { variable }].
+ 			 node receiver receiver: node receiver receiver value]].
+ 	varsToHide notEmpty ifTrue:
+ 		[self nodesDo:
+ 			[:node|
+ 			((node == self or: [node isBlockNode])
+ 			and: [node temporaries anySatisfy: [:temp| varsToHide includes: temp]]) ifTrue:
+ 				[node temporaries: (node temporaries reject: [:temp| varsToHide includes: temp])]]]!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitReturnNode: (in category 'visiting') -----
  visitReturnNode: aReturnNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aReturnNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aReturnNode.
  	^super visitReturnNode: aReturnNode!

Item was changed:
  ParseNodeVisitor subclass: #ParseNodeEnumerator
+ 	instanceVariableNames: 'theBlock theSelectBlock'
- 	instanceVariableNames: 'theBlock'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Support'!
  
+ !ParseNodeEnumerator commentStamp: 'eem 8/31/2010 11:41' prior: 0!
+ ParseNodeEnumerator implements ParseNode>>nodesDo:.  It can be used to enumerate an entire tree via
+ 	aParseNode accept: (ParseNodeEnumerator ofBlock: aBlock)
+ or selectively, excluding the node and subnodes for which selectBlock answers false, via
+ 	aParseNode accept: (ParseNodeEnumerator
+ 							ofBlock: aBlock
+ 							select: selectBlock)
+ 
+ Here's a doIt that generates and compiles the visiting methods:
+ 
- !ParseNodeEnumerator commentStamp: '<historical>' prior: 0!
  self superclass selectors do:
  	[:s|
  	self compile: (String streamContents:
  		[:str| | arg |
  		arg := 'a', (s allButFirst: 5) allButLast.
  		str nextPutAll: s, ' ', arg; crtab;
+ 			nextPutAll: '(theSelectBlock isNil or: [theSelectBlock value: '; nextPutAll: arg; nextPutAll: ']) ifFalse:'; crtab;
+ 			tab: 2; nextPutAll: '[^nil].'; crtab;
  			nextPutAll: 'theBlock value: '; nextPutAll: arg; nextPut: $.; crtab;
  			nextPutAll: '^super '; nextPutAll: s, ' ', arg])]!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitMethodNode: (in category 'visiting') -----
  visitMethodNode: aMethodNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aMethodNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aMethodNode.
  	^super visitMethodNode: aMethodNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitFieldNode: (in category 'visiting') -----
  visitFieldNode: aFieldNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aFieldNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aFieldNode.
  	^super visitFieldNode: aFieldNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitVariableNode: (in category 'visiting') -----
  visitVariableNode: aVariableNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aVariableNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aVariableNode.
  	^super visitVariableNode: aVariableNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitNewArrayNode: (in category 'visiting') -----
  visitNewArrayNode: aNewArrayNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aNewArrayNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aNewArrayNode.
  	^super visitNewArrayNode: aNewArrayNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitLiteralNode: (in category 'visiting') -----
  visitLiteralNode: aLiteralNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aLiteralNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aLiteralNode.
  	^super visitLiteralNode: aLiteralNode!

Item was changed:
  ----- Method: BlockNode>>temporaries (in category 'accessing') -----
  temporaries
+ 	^temporaries ifNil: [#()]!
- 	^temporaries!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitRemoteTempVectorNode: (in category 'visiting') -----
  visitRemoteTempVectorNode: aRemoteTempVectorNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aRemoteTempVectorNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aRemoteTempVectorNode.
  	^super visitRemoteTempVectorNode: aRemoteTempVectorNode!

Item was changed:
  ----- Method: ParseNodeEnumerator>>visitLiteralVariableNode: (in category 'visiting') -----
  visitLiteralVariableNode: aLiteralVariableNode
+ 	(theSelectBlock isNil or: [theSelectBlock value: aLiteralVariableNode]) ifFalse:
+ 		[^nil].
  	theBlock value: aLiteralVariableNode.
  	^super visitLiteralVariableNode: aLiteralVariableNode!

Item was changed:
  ----- Method: Decompiler>>decompile:in:method:using: (in category 'public access') -----
  decompile: aSelector in: aClass method: aMethod using: aConstructor
  
  	| block node |
  	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 preen!
- 	^node!

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



More information about the Packages mailing list