[Vm-dev] VM Maker: VMMaker.oscog-cb.1373.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jun 22 14:22:12 UTC 2015


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

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

Name: VMMaker.oscog-cb.1373
Author: cb
Time: 22 June 2015, 4:20:40.643 pm
UUID: 4994d85f-07d9-481a-8ab9-68ccfd589507
Ancestors: VMMaker.oscog-rmacnak.1372

slighlty change the code generation of #== in sista Jit to decrease the estimate size of abstract opcodes. We now need 11 in the sista Jit instead of 10 in the regular jit due to the counter logic, but it remains reasonable on the contrary to the previous value of 14.

=============== Diff against VMMaker.oscog-rmacnak.1372 ===============

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>estimateOfAbstractOpcodesPerBytecodes (in category 'accessing') -----
  estimateOfAbstractOpcodesPerBytecodes
  	"Due to the counter logic, the estimation is higher"
  	<inline: true>
+ 	^ 11!
- 	self flag: 'we could fix that when #== generates less instructions'.
- 	^ 14!

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 resultReg jumpEqual jumpNotEqual
- 	| nextPC postBranchPC targetBytecodePC branchDescriptor label counterReg fixup
  	  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: [ ^ 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].
  	
+ 	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 ]).
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
- 	label := self Label.
- 	
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	
+ 	self ssPop: 2.
+ 	
- 	self ssPop: 2. "pop by 2 temporarily  for the fixups"
  	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. ].
- 	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label  ].
- 	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ].
- 	self ssPop: -2. 
  	
  	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. 
+ 		
+ 	resultReg := rcvrReg ifNil: [ argReg ].
+ 	jumpEqual := self JumpZero: 0.
+ 	self genMoveFalseR: resultReg.
+ 	jumpNotEqual := self Jump: 0.
+ 	jumpEqual jmpTarget: (self genMoveTrueR: resultReg).
+ 	jumpNotEqual jmpTarget: self Label.
+ 	self ssPushRegister: resultReg.
- 	self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	
  	(self fixupAt: nextPC - initialPC) targetInstruction = 0 ifTrue: [ branchReachedOnlyForCounterTrip := true ].
  	
  	^ 0!



More information about the Vm-dev mailing list