[Vm-dev] VM Maker: VMMaker.oscog-eem.1850.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 28 02:58:21 UTC 2016


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1850.mcz

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

Name: VMMaker.oscog-eem.1850
Author: eem
Time: 27 April 2016, 7:56:19.331347 pm
UUID: 5a13ad57-d069-44d3-b7c3-855c926f66ad
Ancestors: VMMaker.oscog-eem.1849

In 1850, Harriet Tubman becomes an official conductor of the Underground Railroad in the United States. The Potato Famine is ongoing.

Partially fix inlining of returning ifs.  inlineCodeOrNilForStatement:in: is wrong to assume that a send is never a direct return; it is if it is in a returning if.  So refactor it to inlineCodeOrNilForStatement:returningNodes:in: and have its caller tryToInlineMethodsIn: compute the set of returning nodes appropriately.  This could all be cleaned up somewhat but better to get it working first.  Ficxing this bug then uncovers another in exitVar:label:. exitVar:label: uses replaceNodesIn: to replace ^exprs with exitVar := expr. goto exitLabel, but replaceNodesIn: is strictly top-down, so any replacement for ^expr ifTrue: [...^fu...] ifFalse: [...^bar...]
			 will prevent replacement of either ^fu or ^bar. The corollary is that ^expr ifTrue: [foo] ifFalse: [^bar]
			 must be transformed into expr ifTrue: [^foo] ifFalse: [^bar].


This isn't finished yet; e.g.

	SpurMemoryManager>>firstFixedFieldOfMaybeImmediate: oop
		"for the message send breakpoint; selectors can be immediates."
		<inline: false>
		^(self isImmediate: oop)
			ifTrue: [oop asVoidPointer]
			ifFalse: [self firstFixedField: oop]
	
is mistranslated as

	static void * NoDbgRegParms
	firstFixedFieldOfMaybeImmediate(sqInt oop)
	{
	    return (oop & (tagMask())
	        ? ((void *)oop)
	        : (/* begin firstFixedField: */
	            return pointerForOop(oop + BaseHeaderSize)));
	}

but it's close enough, given that the generated code from the previous version is wrong yet compiles silently.  This versiomn correctly translates e.g. inlines of positiveMachineIntegerFor: and inlines of positive32BitIntegerFor: into it.  Hopefully we'll fix the remaining issues PDQ.

Change statement list printing to use KB style I can't read anything else, forgive me).

=============== Diff against VMMaker.oscog-eem.1849 ===============

Item was added:
+ ----- Method: TMethod>>deny: (in category 'error handling') -----
+ deny: aBooleanOrBlock
+ 	<doNotGenerate>
+ 	aBooleanOrBlock value ifTrue: [AssertionFailure signal: 'Assertion failed']!

Item was changed:
  ----- Method: TMethod>>exitVar:label: (in category 'inlining') -----
  exitVar: exitVar label: exitLabel
  	"Replace each return statement in this method with an assignment to the
  	 exit variable followed by either a return or a goto to the given label.
  	 Answer if a goto was generated."
  	"Optimization: If exitVar is nil, the return value of the inlined method is not being used, so don't add the assignment statement."
  
+ 	| labelUsed map elisions eliminateReturnSelfs |
- 	| labelUsed map eliminateReturnSelfs |
  	labelUsed := false.
  	map := Dictionary new.
+ 	elisions := Set new.
  	"Conceivably one might ^self from a struct class and mean it.  In most cases though
  	 ^self means `get me outta here, fast'.  So unless this method is from a VMStruct class,
  	 elide any ^self's"
  	eliminateReturnSelfs := ((definingClass inheritsFrom: VMClass) and: [definingClass isStructClass]) not
  							  and: [returnType = #void or: [returnType = #sqInt]].
  	parseTree nodesDo:
  		[:node | | replacement |
  		node isReturn ifTrue:
+ 			[self transformReturnSubExpression: node
+ 				toAssignmentOf: exitVar
+ 				andGoto: exitLabel
+ 				unless: eliminateReturnSelfs
+ 				into: [:rep :labelWasUsed|
+ 					replacement := rep.
+ 					labelWasUsed ifTrue: [labelUsed := true]].
+ 			"replaceNodesIn: is strictly top-down, so any replacement for ^expr ifTrue: [...^fu...] ifFalse: [...^bar...]
+ 			 will prevent replacement of either ^fu or ^bar. The corollary is that ^expr ifTrue: [foo] ifFalse: [^bar]
+ 			 must be transformed into expr ifTrue: [^foo] ifFalse: [^bar]"
+ 			(node expression isConditionalSend
+ 			 and: [node expression hasExplicitReturn])
+ 				ifTrue:
+ 					[elisions add: node.
+ 					 (node expression args reject: [:arg| arg endsWithReturn]) do:
+ 						[:nodeNeedingReturn|
+ 						 self transformReturnSubExpression: nodeNeedingReturn statements last
+ 							toAssignmentOf: exitVar
+ 							andGoto: exitLabel
+ 							unless: eliminateReturnSelfs
+ 							into: [:rep :labelWasUsed|
+ 								replacement := rep.
+ 								labelWasUsed ifTrue: [labelUsed := true]].
+ 						 map
+ 							at: nodeNeedingReturn statements last
+ 							put: replacement]]
+ 				ifFalse:
+ 					[map
+ 						at: node
+ 						put: (replacement ifNil:
+ 								[TLabeledCommentNode new setComment: 'return ', node expression printString])]]].
+ 	map isEmpty ifTrue:
+ 		[self deny: labelUsed.
+ 		 ^false].
+ 	"Now do a top-down replacement for all returns that should be mapped to assignments and gotos"
- 			[replacement := (node expression isVariable "Eliminate ^self's"
- 							   and: [node expression name = 'self'
- 							   and: [eliminateReturnSelfs]])
- 								ifTrue: [nil]
- 								ifFalse:
- 									[exitVar
- 										ifNil: [node expression]
- 										ifNotNil: [TAssignmentNode new
- 													setVariable: (TVariableNode new setName: exitVar)
- 													expression: node expression]].
- 			 node ~~ parseTree statements last ifTrue:
- 				[replacement := replacement
- 									ifNil: [TGoToNode new setLabel: exitLabel; yourself]
- 									ifNotNil:
- 										[TStmtListNode new
- 											setArguments: #()
- 											statements: {replacement.
- 														  TGoToNode new setLabel: exitLabel; yourself};
- 											yourself].
- 				 labelUsed := true].
- 			map
- 				at: node
- 				put: (replacement ifNil:
- 						[TLabeledCommentNode new setComment: 'return ', node expression printString])]].
  	parseTree replaceNodesIn: map.
+ 	"Now it is safe to eliminate the returning ifs..."
+ 	elisions isEmpty ifFalse:
+ 		[| elisionMap |
+ 		 elisionMap := Dictionary new.
+ 		 elisions do: [:returnNode| elisionMap at: returnNode put: returnNode expression].
+ 		 parseTree replaceNodesIn: elisionMap].
+ 	"Afterwards all returns should be gone."
+ 	self deny: parseTree hasExplicitReturn.
  	"Now flatten any new statement lists..."
  	parseTree nodesDo:
  		[:node| | list |
  		(node isStmtList
  		 and: [node statements notEmpty
  		 and: [node statements last isStmtList]]) ifTrue:
  			[list := node statements last statements.
  			 node statements removeLast; addAllLast: list]].
  	^labelUsed!

Item was removed:
- ----- Method: TMethod>>inlineCodeOrNilForStatement:in: (in category 'inlining') -----
- inlineCodeOrNilForStatement: aNode in: aCodeGen
- 	"If the given statement node can be inlined, answer the statements that replace it. Otherwise, answer nil."
- 
- 	| stmts |
- 	aNode isReturn ifTrue:
- 		[(self inlineableSend: aNode expression in: aCodeGen) ifTrue:
- 			[stmts := self inlineSend: aNode expression
- 				directReturn: true exitVar: nil in: aCodeGen.
- 			^stmts]].
- 	(aNode isAssignment and: [aNode expression isSend])  ifTrue:
- 		[(self inlineableSend: aNode expression in: aCodeGen) ifTrue:
- 			[^self inlineSend: aNode expression
- 				directReturn: false exitVar: aNode variable name in: aCodeGen]].
- 	aNode isSend ifTrue:
- 		[(self inlineableSend: aNode in: aCodeGen) ifTrue:
- 			[^self inlineSend: aNode
- 				directReturn: false exitVar: nil in: aCodeGen]].
- 	^nil!

Item was added:
+ ----- Method: TMethod>>inlineCodeOrNilForStatement:returningNodes:in: (in category 'inlining') -----
+ inlineCodeOrNilForStatement: aNode returningNodes: returningNodes in: aCodeGen
+ 	"If the given statement node can be inlined, answer the statements that replace it. Otherwise, answer nil."
+ 
+ 	| stmts |
+ 	aNode isReturn ifTrue:
+ 		[(self inlineableSend: aNode expression in: aCodeGen) ifTrue:
+ 			[stmts := self inlineSend: aNode expression
+ 							directReturn: true exitVar: nil in: aCodeGen.
+ 			^stmts]].
+ 	(aNode isAssignment and: [aNode expression isSend])  ifTrue:
+ 		[(self inlineableSend: aNode expression in: aCodeGen) ifTrue:
+ 			[^self inlineSend: aNode expression
+ 					directReturn: false exitVar: aNode variable name in: aCodeGen]].
+ 	aNode isSend ifTrue:
+ 		[(self inlineableSend: aNode in: aCodeGen) ifTrue:
+ 			[^self inlineSend: aNode
+ 					directReturn: (returningNodes includes: aNode) exitVar: nil in: aCodeGen]].
+ 	^nil!

Item was added:
+ ----- Method: TMethod>>transformReturnSubExpression:toAssignmentOf:andGoto:unless:into: (in category 'inlining') -----
+ transformReturnSubExpression: node toAssignmentOf: exitVar andGoto: exitLabel unless: eliminateReturnSelfs into: aBinaryBlock
+ 	| expr replacement |
+ 	expr := node isReturn ifTrue: [node expression] ifFalse: [node].
+ 	replacement := (expr isVariable "Eliminate ^self's"
+ 					   and: [expr name = 'self'
+ 					   and: [eliminateReturnSelfs]])
+ 						ifTrue: [nil]
+ 						ifFalse:
+ 							[exitVar
+ 								ifNil: [expr]
+ 								ifNotNil: [TAssignmentNode new
+ 											setVariable: (TVariableNode new setName: exitVar)
+ 											expression: expr]].
+ 	 node == parseTree statements last
+ 		ifTrue:
+ 			[aBinaryBlock value: replacement value: false]
+ 		ifFalse:
+ 			[replacement := replacement
+ 								ifNil: [TGoToNode new setLabel: exitLabel; yourself]
+ 								ifNotNil:
+ 									[TStmtListNode new
+ 										setArguments: #()
+ 										statements: {replacement.
+ 													  TGoToNode new setLabel: exitLabel; yourself};
+ 										yourself].
+ 			 aBinaryBlock value: replacement value: true]!

Item was changed:
  ----- Method: TMethod>>tryToInlineMethodsIn: (in category 'inlining') -----
  tryToInlineMethodsIn: aCodeGen
  	"Expand any (complete) inline methods called by this method. Set the complete bit when all inlining has been done. Return true if something was inlined."
  
+ 	| stmtLists didSomething newStatements sendsToInline returningNodes |
- 	| stmtLists didSomething newStatements sendsToInline |
  	self definedAsMacro ifTrue:
  		[complete := true.
  		 ^false].
  	didSomething := false.
  	sendsToInline := Dictionary new: 100.
  	parseTree
  		nodesDo:
  			[:node|
  			(self transformConditionalAssignment: node in: aCodeGen) ifNotNil:
  				[:replacement|
  				 sendsToInline at: node put: replacement].
  			(self inlineableFunctionCall: node in: aCodeGen) ifTrue:
  				[(self inlineFunctionCall: node in: aCodeGen) ifNotNil:
  					[:replacement|
  					 sendsToInline at: node put: replacement]]]
  		unless: "Don't inline the arguments to asserts to keep the asserts readable"
  			[:node|
  			node isSend
  			and: [node selector == #cCode:inSmalltalk:
  				or: [aCodeGen isAssertSelector: node selector]]].
  
  	sendsToInline isEmpty ifFalse:
  		[didSomething := true.
  		parseTree := parseTree replaceNodesIn: sendsToInline].
  
  	didSomething ifTrue:
  		[writtenToGlobalVarsCache := nil.
  		^didSomething].
  
+ 	returningNodes := Set new.
+ 	parseTree nodesDo:
+ 		[:node|
+ 		node isReturn ifTrue:
+ 			[returningNodes add: node expression.
+ 			 node expression isConditionalSend ifTrue:
+ 				[returningNodes addAll: (node expression args collect: [:stmtList| stmtList statements last])]]].
  	stmtLists := self statementsListsForInliningIn: aCodeGen.
  	stmtLists do:
  		[:stmtList|
  		newStatements := OrderedCollection new: 100.
  		stmtList statements do:
  			[:stmt|
+ 			(self inlineCodeOrNilForStatement: stmt returningNodes: returningNodes in: aCodeGen)
- 			(self inlineCodeOrNilForStatement: stmt in: aCodeGen)
  				ifNil: [newStatements addLast: stmt]
  				ifNotNil: [:inlinedStmts|
  					didSomething := true.
  					newStatements addAllLast: inlinedStmts]].
  		stmtList setStatements: newStatements asArray].
  
  	didSomething ifTrue:
  		[writtenToGlobalVarsCache := nil.
  		^didSomething].
  
  	complete ifFalse:
  		[self checkForCompleteness: stmtLists in: aCodeGen.
  		 complete ifTrue: [ didSomething := true ]].  "marking a method complete is progress"
  	^didSomething!

Item was added:
+ ----- Method: TParseNode>>isConditionalSend (in category 'testing') -----
+ isConditionalSend
+ 	"Answer if the receiver is a send of any of the conditionals, ifTrue: ifTrue:ifFalse: et al"
+ 	^false!

Item was added:
+ ----- Method: TSendNode>>isConditionalSend (in category 'testing') -----
+ isConditionalSend
+ 	"Answer if the receiver is a send of any of the conditionals, ifTrue: ifTrue:ifFalse: et al"
+ 	^#(	ifTrue:ifFalse: ifFalse:ifTrue: ifTrue: ifFalse:
+ 		ifNil:ifNotNil: ifNotNil:ifNil: ifNil: ifNotNil) includes: selector!

Item was changed:
  ----- Method: TSendNode>>isReturningIf (in category 'testing') -----
  isReturningIf
+ 	^(#(ifTrue:ifFalse: ifFalse:ifTrue: ifNil:ifNotNil: ifNotNil:ifNil:) includes: selector)
- 	^(#(ifTrue:ifFalse: ifFalse:ifTrue:) includes: selector)
  	   and: [arguments allSatisfy: [:arg| arg endsWithReturn]]!

Item was changed:
  ----- Method: TStmtListNode>>printOn:level: (in category 'printing') -----
  printOn: aStream level: level
  
+ 	statements size > 1 ifTrue: [ aStream crtab: level + 1 ].
  	aStream nextPut: $[.
  	(arguments notNil and: [arguments notEmpty]) ifTrue:
  		[arguments do: [ :arg | aStream nextPutAll: ' :'; nextPutAll: arg].
  		 aStream nextPutAll: ' | '].
  	self printStatementsOn: aStream level: level.
  	aStream nextPut: $]!

Item was changed:
  ----- Method: TStmtListNode>>printStatementsOn:level: (in category 'printing') -----
  printStatementsOn: aStream level: level
  
+ 	statements
+ 		do: [:s| s printOn: aStream level: level]
+ 		separatedBy: [aStream nextPut: $.; crtab: level + 1]!
- 	statements size > 1 ifTrue: [ aStream crtab: level + 1 ].
- 	1 to: statements size do: [ :i |
- 		(statements at: i) printOn: aStream level: level.
- 		i = statements size ifTrue: [
- 			(statements size > 1) ifTrue: [
- 				aStream crtab: level.
- 			].
- 		] ifFalse: [
- 			aStream nextPut: $.; crtab: level + 1.
- 		].
- 	].!



More information about the Vm-dev mailing list