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

commits at source.squeak.org commits at source.squeak.org
Fri Nov 14 03:43:43 UTC 2014


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

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

Name: VMMaker.oscog-eem.929
Author: eem
Time: 13 November 2014, 7:39:51.258 pm
UUID: 03ec1944-f1e5-4f50-a4b7-7a73a8d9b42f
Ancestors: VMMaker.oscog-eem.928

More tweaking to get the same inlining behaviour as
before the constant to send putch for ShiftForWord.

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

Item was changed:
  ----- Method: CCodeGenerator>>mostBasicConstantSelectors (in category 'accessing') -----
  mostBasicConstantSelectors
  	"c.f. VMBasicConstants class>>#mostBasicConstantNames"
+ 	^#(baseHeaderSize bytesPerOop bytesPerWord shiftForWord wordSize)!
- 	^#(baseHeaderSize bytesPerOop bytesPerWord wordSize)!

Item was changed:
  ----- Method: TMethod>>isNode:substitutableFor:inMethod:in: (in category 'inlining') -----
  isNode: aNode substitutableFor: argName inMethod: targetMeth in: aCodeGen
  	"Answer if the given parameter node may be substituted directly into the body of
  	 the method during inlining, instead of being bound to the actual parameter variable.
  	 We allow a constant, a local variable, or a formal parameter, or simple expressions
  	 involving only these to to be directly substituted. Note that global variables cannot
  	 be subsituted into methods with possible side effects (i.e., methods that may assign
  	 to global variables) because the inlined method might depend on having the value of
  	 the global variable captured when it is passed in as an argument."
  
  	| madeNonTrivialCall count constantExpression usageCount |
  	aNode isConstant ifTrue: [^true].
  
  	aNode isVariable ifTrue:
  		[((locals includes: aNode name)
  		 or: [(args includes: aNode name)
  		 or: [#('self' 'true' 'false' 'nil') includes: aNode name]]) ifTrue: [^true].
  		"We can substitute any variable provided it is only read in the method being inlined,
  		 and if it is not read after any non-trivial call (which may update the variable)."
  		madeNonTrivialCall := false.
  		(targetMeth isComplete
  		 and: [targetMeth parseTree
  				noneSatisfy:
  					[:node|
  					 (node isSend
  					  and: [(aCodeGen isBuiltinSelector: node selector) not]) ifTrue:
  						[madeNonTrivialCall := true].
  					 (madeNonTrivialCall and: [node isVariable and: [node name = argName]])
  					 or: [node isAssignment
  						  and: [node variable name = argName]]]
  				unless:
  					[:node|
  					node isSend and: [aCodeGen isAssertSelector: node selector]]]) ifTrue:
  			[^true].
  		^targetMeth maySubstituteGlobal: aNode name in: aCodeGen].
  
  	"For now allow literal blocks to be substituted.  They better be accessed only
  	 with value[:value:*] messages though!!"
  	aNode isStmtList ifTrue: [^true].
  
  	count := 0.
  	constantExpression := true.
  	"scan expression tree; must contain only constants, builtin ops, and inlineable vars"
  	aNode nodesDo:
  		[:node|
  		node isConstant
  			ifTrue: [] ifFalse:
  		[node isSend
  			ifTrue:
+ 				[((aCodeGen mostBasicConstantSelectors includes: node selector)
+ 				  or: [node isBuiltinOperator]) ifFalse: [^false].
- 				[node isBuiltinOperator ifFalse: [^false].
  				 count := count + 1] ifFalse:
  		[node isVariable ifTrue:
+ 			[(aCodeGen isNonArgumentImplicitReceiverVariableName: node name) ifFalse:
+ 				[constantExpression := false.
+ 				((locals includes: node name)
+ 				 or: [(args includes: node name)
+ 				 or: [(#('self' 'true' 'false' 'nil') includes: node name)
+ 				 or: [targetMeth maySubstituteGlobal: node name in: aCodeGen]]]) ifFalse: [^false]]] ifFalse:
- 			[constantExpression := false.
- 			((locals includes: node name) or:
- 			 [(args includes: node name) or:
- 			 [(#('self' 'true' 'false' 'nil') includes: node name) or:
- 			 [targetMeth maySubstituteGlobal: node name in: aCodeGen]]]) ifFalse: [^false]] ifFalse:
  		[^false]]]].
  	"inline constant expressions"
  	constantExpression ifNil: [^true].
  
  	"scan target to find usage count"
  	usageCount := 0.
  	targetMeth parseTree nodesDo:
  		[:node|
  		(node isVariable and: [node name = argName]) ifTrue:
  			[usageCount := usageCount + 1]].
  	"Now only inline expressions if they are used only once or are simple
  	 w.r.t. the usage count; a heuristic that seems to work well enough."
  	^usageCount = 1 or: [count <= usageCount]!

Item was changed:
  ----- Method: TSendNode>>bindVariableUsesIn:andConstantFoldIf:in: (in category 'transformations') -----
  bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen
  	"Answer either the receiver, if it contains no references to the given variables, or a new node with the given variables rebound.
  	 Attempt to constant-fold and answer a constant node commented with the original expression.
  	 Commenting with the original expression is important because it allows us to detect shared cases.
  	 e.g. currentBytecode bitAnd: 15 is the same in case 1 and case 17, but '1 /* 1 bitAnd: 15 */' differs
  	 from '1 /* 17 bitAnd: 15 */', whereas '1 /* currentBytecode bitAnd: 15 */' doesn't change."
  	| newReceiver newArguments |
+ 	"Constant-fold shiftForWord, but not BytesPerWord"
+ 	((codeGen mostBasicConstantSelectors includes: selector)
+ 	 and: [(codeGen isBuiltinSelector: selector) not]) ifTrue:
+ 		[codeGen isConstantNode: self valueInto:
+ 			[:val|
+ 			 ^TConstantNode new
+ 				setValue: val;
+ 				yourself]].
  	newReceiver := receiver bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen.
  	newArguments := arguments collect: [:a| a bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen].
  	(newReceiver = receiver
  	 and: [newArguments = arguments]) ifTrue:
  		[^self].
  	(constantFold
  	 and: [newReceiver isConstant and: [newReceiver value isInteger]
  	 and: [(newArguments allSatisfy: [:ea| ea isConstant and: [ea value isInteger]])
  	 and: [codeGen isBuiltinSelector: selector]]]) ifTrue:
  		[| value |
  		value := [newReceiver value perform: selector withArguments: (newArguments collect: [:ea| ea value])]
  					on: Error
  					do: [:ea| nil].
  		 (value isInteger
  		 or: [value == true
  		 or: [value == false]]) ifTrue:
  			[^TConstantNode new
  				setValue: value;
  				"We assume Message prints its keywords and arguments interleaved.
  				 e.g. that (Message selector: #between:and: arguments: #(0 1)) printString = 'between: 0 and: 1'"
  				comment: (receiver isLeaf
  								ifTrue: [receiver printString]
  								ifFalse: ['(', receiver printString, ')']),
  							' ',
  							(Message selector: selector arguments: (arguments collect: [:ea| ea value])) printString;
  				yourself]].
  	^self shallowCopy
  		receiver: newReceiver;
  		arguments: newArguments;
  		yourself
  		!



More information about the Vm-dev mailing list