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

commits at source.squeak.org commits at source.squeak.org
Thu Jul 2 16:42:37 UTC 2015


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

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

Name: VMMaker.oscog-eem.1404
Author: eem
Time: 2 July 2015, 9:40:01.397 am
UUID: b73d0e90-367a-4575-8a29-87bbc81e4715
Ancestors: VMMaker.oscog-eem.1403

Fix merging of properties for super expansions.  The old code would merge properties before renaming variables for inlining the super expansion, and forget to rename variable names in properties.  The new code renames variables in properties as well as in the parse tree of copy to be inlined, and merges properties after renaming.

Use super genSpecialSelectorEqualsEqualsWithForwarders in SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders now that super expansion is fixed and nuke the indirection method.

Fix SpurMemoryManager>>initializeWithOptions: to copy the options dictionary to its subclasses and all ancilliary classes.  Fixes eg. in-image compilation now that maxOldSpaceSize is settable via options.

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

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
  	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpEqual type: #'AbstractInstruction *'>
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  
+ 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
+ 		[^super genSpecialSelectorEqualsEqualsWithForwarders].
- 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [ ^ self genSpecialSelectorEqualsEqualsWithForwardersWithoutCounters ].
  
  	regMask := 0.
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  	
  	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
  	register so the forwarder check can jump back to the comparison after unforwarding the constant.
  	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
  	(machine code will use operations on constants)."
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
  		rcvrNeedsReg: unforwardRcvr 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  		
  	argReg ifNotNil: [ regMask := self registerMaskFor: argReg ].
  	rcvrReg ifNotNil: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
  	
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
  	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
  	
  	counterReg := self allocateRegNotConflictingWith: regMask.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  	
  	self assert: (unforwardArg or: [ unforwardRcvr ]).
  	
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	
  	self ssPop: 2.
  	
  	branchDescriptor isBranchTrue 
  		ifTrue: 
  			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
  			self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. ]
  		ifFalse: 
  			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
  			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. ].
  	
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	self Jump: fixup.
  	
  	countTripped jmpTarget: self Label.
  	
  	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
  	self ssPop: -2. 
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2. 
  	
  	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
  	We therefore directly assign the result to TempReg to save one move instruction"
  	jumpEqual := self JumpZero: 0.
  	self genMoveFalseR: TempReg.
  	jumpNotEqual := self Jump: 0.
  	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
  	jumpNotEqual jmpTarget: self Label.
  	self ssPushRegister: TempReg.
  	
  	(self fixupAt: nextPC - initialPC) targetInstruction = 0 ifTrue: [ branchReachedOnlyForCounterTrip := true ].
  	
  	^ 0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwardersWithoutCounters (in category 'bytecode generators') -----
- genSpecialSelectorEqualsEqualsWithForwardersWithoutCounters
- 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
- 	^ super genSpecialSelectorEqualsEqualsWithForwarders!

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
  	"SpurMemoryManager initializeWithOptions: Dictionary new"
  
+ 	{self}, (self ancilliaryClasses: optionsDictionary) do:
+ 		[:aSuperclass|
+ 		 aSuperclass withAllSubclasses do:
+ 			[:class| class initializationOptions: optionsDictionary]].
+ 
  	super initializeWithOptions: optionsDictionary.
  	self initialize.
  	self initBytesPerWord: (self == SpurMemoryManager
  								ifTrue: [optionsDictionary at: #BytesPerWord ifAbsent: [4]]
  								ifFalse: [self wordSize]).
  
  	self initializeObjectHeaderConstants. "Initializes BaseHeaderSize so do early"
  	self initializeSpurObjectRepresentationConstants.
  	self initializeSpecialObjectIndices.
  	self initializeCompactClassIndices.
  	self initializePrimitiveErrorCodes.
  
  	SpurGenerationScavenger initialize!

Item was changed:
  ----- Method: TMethod>>renameVariablesUsing: (in category 'inlining support') -----
  renameVariablesUsing: aDictionary
  	"Rename all variables according to old->new mappings of the given dictionary."
  
+ 	| newDecls newProperties |
- 	| newDecls |
  	"map args and locals"
  	args := args collect: [ :arg | aDictionary at: arg ifAbsent: [ arg ]].
  	locals := locals collect: [ :v | aDictionary at: v ifAbsent: [ v ]].
  
  	"map declarations"
  	newDecls := declarations species new.
  	declarations keysAndValuesDo:
  		[:oldName :decl|
  		(aDictionary at: oldName ifAbsent: nil)
  			ifNotNil:
  				[:newName| | index |
  				index := decl indexOfWord: oldName.
  				 newDecls
  					at: newName
  					put: (index ~= 0
  							ifTrue: [decl copyReplaceFrom: index to: index + oldName size - 1 with: newName]
  							ifFalse: [decl])]
  			ifNil: [newDecls at: oldName put: decl]].
  	self newDeclarations: newDecls.
  
+ 	newProperties := properties copy.
+ 	newProperties pragmas do:
+ 		[:pragma| | mappedArgs |
+ 		mappedArgs := pragma arguments collect: [:arg| arg isString ifTrue: [aDictionary at: arg ifAbsent: arg] ifFalse: [arg]].
+ 		mappedArgs ~= pragma arguments ifTrue:
+ 			[pragma setArguments: mappedArgs]].
+ 	self properties: newProperties.
+ 
  	"map variable names in parse tree"
  	parseTree nodesDo:
  		[ :node |
  		(node isVariable
  		and: [aDictionary includesKey: node name]) ifTrue:
  			[node setName: (aDictionary at: node name)].
  		(node isStmtList and: [node args size > 0]) ifTrue:
  			[node setArguments: (node args collect: [ :arg | aDictionary at: arg ifAbsent: [ arg ]])]]!

Item was changed:
  ----- Method: TMethod>>superExpansionNodeFor:args: (in category 'inlining') -----
  superExpansionNodeFor: aSelector args: argumentNodes
  	"Answer the expansion of a super send.  Merge the super expansion's
  	 locals, properties and comment into this method's properties."
  	(definingClass superclass lookupSelector: aSelector)
  		ifNil: [self error: 'superclass does not define super method']
  		ifNotNil:
  			[:superMethod| | superTMethod commonVars varMap |
  			superTMethod := superMethod methodNode asTranslationMethodOfClass: self class.
  			((argumentNodes allSatisfy: [:parseNode| parseNode isVariableNode])
  			and: [(argumentNodes asOrderedCollection collect: [:parseNode| parseNode key]) = superTMethod args]) ifFalse:
  				[self error: definingClass name, '>>',selector, ' args ~= ',
  							superTMethod definingClass name, '>>', aSelector,
  							(String with: $. with: Character cr),
  							'For super expansions to be translated correctly each argument must be a variable with the same name as the corresponding argument in the super method.'].
- 			self mergePropertiesOfSuperMethod: superTMethod.
  			(commonVars := superTMethod locals intersection: self locals) notEmpty ifTrue:
  				[varMap := Dictionary new.
  				 commonVars do:
  					[:k| varMap at: k put: (superTMethod unusedNamePrefixedBy: k avoiding: self allLocals)].
  				 superTMethod renameVariablesUsing: varMap].
+ 			self mergePropertiesOfSuperMethod: superTMethod.
  			self assert: (superTMethod locals allSatisfy: [:var| (self locals includes: var) not]).
  			locals addAll: superTMethod locals.
  			superTMethod declarations keysAndValuesDo:
  				[:var :decl|
  				self declarationAt: var put: decl].
  			superTMethod comment ifNotNil:
  				[:superComment|
  				comment := comment
  								ifNil: [superComment]
  								ifNotNil: [superComment, comment]].
  			superTMethod extraVariableNumber ifNotNil:
  				[:scvn|
  				extraVariableNumber := extraVariableNumber ifNil: [scvn] ifNotNil: [:cvn| cvn + scvn]].
  			superTMethod elideAnyFinalReturn.
  			^superTMethod parseTree]!



More information about the Vm-dev mailing list