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

commits at source.squeak.org commits at source.squeak.org
Mon Jul 25 20:44:32 UTC 2022


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

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

Name: VMMaker.oscog-eem.3219
Author: eem
Time: 25 July 2022, 1:44:22.899662 pm
UUID: e81f0074-fa4b-408c-b554-79542c7ff944
Ancestors: VMMaker.oscog-eem.3218

Fix accessor depth calculation for SmartSyntaxInterpreterPlugins.  The scheme still doesn't follow at: chains thropugh derived pointers starting with firstIndexableField: biut it's good enough, and a big step up form assuming the accessor depths of primitives in all such plugins is 0.

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

Item was changed:
  ----- Method: CCodeGenerator>>accessorsAndAssignmentsForMethod:actuals:depth:interpreterClass:into: (in category 'spur primitive compilation') -----
  accessorsAndAssignmentsForMethod: method actuals: actualParameters depth: depth interpreterClass: interpreterClass into: aTrinaryBlock
  	"Evaluate aTrinaryBlock with the root accessor sends, accessor sends and assignments in the method."
  	| accessors assignments roots |
  	accessors := Set new.
  	assignments := Set new.
  	roots := Set new.
+ 	actualParameters with: method argsForAccessorChainComputation do:
- 	actualParameters with: method args do:
  		[:actual :argName|
  		 (actual isVariable or: [actual isSend]) ifTrue:
  			[(actual isSend and: [self isStackAccessor: actual selector given: interpreterClass]) ifTrue:
  				[roots add: actual].
  			assignments add: (TAssignmentNode new
  									setVariable: (TVariableNode new setName: argName)
  									expression: actual)]].
  	method parseTree nodesDo:
  		[:node|
  		node isSend ifTrue:
  			[(self isStackAccessor: node selector given: interpreterClass) ifTrue:
  				[roots add: node].
  			 (self isObjectAccessor: node selector given: interpreterClass) ifTrue:
  				[accessors add: node].
  			 (self accessorDepthDeterminationFollowsSelfSends
  			  and: [node receiver isVariable
  			  and: [node receiver name = 'self'
  			  and: [roots isEmpty
  				or: [node args anySatisfy:
  					[:arg|
  					 (roots includes: arg)
  					 or: [(accessors includes: arg)
  					 or: [assignments anySatisfy: [:assignment| assignment variable isSameAs: arg]]]]]]]]) ifTrue:
  				[self accessorsAndAssignmentsForSubMethodNamed: node selector
  					actuals: node args
  					depth: depth + 1
  					interpreterClass: interpreterClass
  					into: [:subRoots :subAccessors :subAssignments|
  						(subRoots isEmpty and: [subAccessors isEmpty and: [subAssignments isEmpty]]) ifFalse:
  							[roots addAll: subRoots.
  							 accessors add: node.
  							 accessors addAll: subAccessors.
  							 assignments addAll: subAssignments]]]].
  		(node isAssignment
  		 and: [(node expression isSend and: [SpurMemoryManager isTerminalObjectAccessor: node expression selector]) not
  		 and: [(roots includes: node expression)
  			or: [(accessors includes: node expression)
  			or: [node expression isVariable and: [node expression name ~= 'nil']]]]]) ifTrue:
  			[assignments add: node]].
  	^aTrinaryBlock
  		value: roots
  		value: accessors
  		value: assignments!

Item was changed:
  ----- Method: CCodeGenerator>>depthOfAccessor:for: (in category 'spur primitive compilation') -----
  depthOfAccessor: accessor for: chainVariableOrNil
  	"Compute the accessor depth for a send.  This is potentially greater than one for a nested access
  	 such as self fetchPointer: i ofObject: (self fetchPointer: j ofObject: (self fetchPointer: k ofObject: var)).
  	 If chainVariableOrNil is not nil then an access is only meaningful if it is an access of chainVariableOrNil."
  
  	| keywords accessIndex objectAccessed |
  	accessor isSend ifFalse:
  		[^0].
  	(StackInterpreter isStackAccessor: accessor selector) ifTrue:
  		[^1].
+ 	#firstIndexableField: == accessor selector ifTrue:
+ 		[^1 + (self depthOfAccessor: accessor args first for: chainVariableOrNil)].
+ 	(#(cCoerceSimple:to: cCoerce:to:) includes: accessor selector) ifTrue:
+ 		[^self depthOfAccessor: accessor args first for: chainVariableOrNil].
  	keywords := accessor selector keywords.
  	accessIndex := keywords
  						indexOf: 'ofObject:'
  						ifAbsent:
  							[^(accessor args
  								inject: ((StackInterpreter isObjectAccessor: accessor selector)
  											ifTrue: [1]
  											ifFalse: [0])
  								into:
  									[:best :node|
  									node isSend
  										ifTrue: [best max: (self depthOfAccessor: node for: chainVariableOrNil)]
  										ifFalse: [best]])].
  	objectAccessed := accessor args at: accessIndex.
  	chainVariableOrNil ifNil:
  		[^1 + (self depthOfAccessor: objectAccessed for: chainVariableOrNil)].
  	objectAccessed isSend ifFalse:
  		[^(objectAccessed isSameAs: chainVariableOrNil)
  			ifTrue: [1]
  			ifFalse: [0]].
  	(objectAccessed anySatisfy: [:node| node isSameAs: chainVariableOrNil]) ifFalse:
  		[^0].
  	^1 + (self depthOfAccessor: objectAccessed for: chainVariableOrNil)!

Item was added:
+ ----- Method: InterpreterPlugin class>>isStackAccessor: (in category 'spur primitive compilation') -----
+ isStackAccessor: selector
+ 	^(selector beginsWith: 'stack') and: [selector endsWith: 'Value:']!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>actualsForMethod: (in category 'spur primitive compilation') -----
+ actualsForMethod: aTMethod
+ 	"Normal primitives have no arguments, but translated primitives do.
+ 	 Override to answer actuals for translated primitives."
+ 	| formalParameterNames actuals |
+ 	formalParameterNames := Set withAll: aTMethod fullArgs.
+ 	aTMethod receiver ifNotNil:
+ 		[:rcvr| formalParameterNames add: rcvr].
+ 	actuals := OrderedCollection new.
+ 	"they're all at the top level..."
+ 	aTMethod parseTree statements do:
+ 		[:node|
+ 		(node isAssignment
+ 		 and: [formalParameterNames includes: node variable name]) ifTrue:
+ 			[formalParameterNames remove: node variable name.
+ 			 actuals add: node expression]].
+ 	^actuals!

Item was added:
+ ----- Method: SmartSyntaxPluginTMethod>>argsForAccessorChainComputation (in category 'accessing') -----
+ argsForAccessorChainComputation
+ 	| argsForAccessorChainComputation |
+ 	(receiver isNil and: [parmSpecs isNil]) ifTrue:
+ 		[^super argsForAccessorChainComputation].
+ 
+ 	argsForAccessorChainComputation := OrderedCollection new.
+ 	receiver ifNotNil:
+ 		[argsForAccessorChainComputation addLast: receiver].
+ 	argsForAccessorChainComputation addAllLast: fullArgs.
+ 	^argsForAccessorChainComputation!

Item was added:
+ ----- Method: TMethod>>argsForAccessorChainComputation (in category 'accessing') -----
+ argsForAccessorChainComputation
+ 	"The arguments of this method."
+ 
+ 	^self args!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>isStackAccessor:given: (in category 'spur primitive compilation') -----
+ isStackAccessor: selector given: interpreterClass
+ 	^(interpreterClass isStackAccessor: selector)
+ 	 or: [pluginClass isStackAccessor: selector]
+ 	!



More information about the Vm-dev mailing list