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

commits at source.squeak.org commits at source.squeak.org
Sat Apr 18 01:38:59 UTC 2015


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

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

Name: VMMaker.oscog-cb.1214
Author: cb
Time: 17 April 2015, 6:37:18.871 pm
UUID: 9a0055bc-76f8-4dd5-bf2f-08e553c83141
Ancestors: VMMaker.oscog-eem.1213

- Change the code generation of == for sistaCogit
- change the coutner reg to be allocated instead of being a fixed abstract reg
- fix a C code gen bug in code gen of #==
- fix a bug in #== where the arg was not unforwarded

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

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>genDirectEqualsEqualsArg:rcvr:argReg:rcvrReg: (in category 'bytecode generators') -----
+ genDirectEqualsEqualsArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg
+ 	<inline: true>
+ 	| label jumpEqual jumpNotEqual |
+ 	label := self label.
+ 	unforwardArg 
+ 		ifFalse: [ self CmpCq: self ssTop constant R: rcvrReg ]
+ 		ifTrue: [ unforwardRcvr
+ 			ifFalse: [ self CmpCq: (self ssValue: 1) constant R: argReg ]
+ 			ifTrue: [ self CmpR: argReg R: rcvrReg ] ].	 
+ 	self ssPop: 2.
+ 	jumpEqual := self JumpZero: 0.
+ 	 unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ].
+ 	 unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ].
+ 	 self genMoveFalseR: rcvrReg.
+ 	 jumpNotEqual := self Jump: 0.
+ 	 jumpEqual jmpTarget: (self genMoveTrueR: rcvrReg).
+ 	 jumpNotEqual jmpTarget: self Label.
+ 	 self ssPushRegister: rcvrReg.
+ 	 ^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
  	 so that scanning for send and branch data is simplified and that branch data is correct."
  	<inline: false>
+ 	| desc ok counterAddress countTripped retry counterReg |
- 	| desc ok counterAddress countTripped retry |
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
  
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	desc popToReg: TempReg.
  
+ 	counterReg := self allocateRegisterNotConflictingWith: 0.
- 	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
  	counterIndex := counterIndex + 1.
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: objectMemory wordSize = CounterBytes.
+ 	retry := self MoveAw: counterAddress R: counterReg.
+ 	self SubCq: 16r10000 R: counterReg. "Count executed"
- 	retry := self MoveAw: counterAddress R: SendNumArgsReg.
- 	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  	countTripped := self JumpCarry: 0.
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
+ 	self SubCq: 1 R: counterReg. "Count untaken"
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
- 	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
+ 	self MoveCq: 0 R: counterReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."
- 	self MoveCq: 0 R: SendNumArgsReg. "if SendNumArgsReg is 0 this is a mustBeBoolean, not a counter trip."
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
  	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
  	 trampoline will return directly to machine code, returning the boolean.  So the code should
  	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
  	self annotateBytecode: self Label.
  	self Jump: retry.
  	ok jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"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 primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst
+ 	  counterAddress countTripped counterReg |
- 	  counterAddress countTripped |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genSpecialSelectorComparison ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
  		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  		 self annotateBytecodeIfAnnotated: self ssTop.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
+ 	counterReg := self allocateRegisterNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg). "Use this as the count reg, can't conflict with the registers for the arg and the receiver"
+ 	self ssAllocateRequiredReg: counterReg. "Use this as the count reg."
- 	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: objectMemory wordSize = CounterBytes.
+ 	self MoveAw: counterAddress R: counterReg.
+ 	self SubCq: 16r10000 R: counterReg. "Count executed"
- 	self MoveAw: counterAddress R: SendNumArgsReg.
- 	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ 	self SubCq: 1 R: counterReg. "Count untaken"
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
- 	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1
  		sendTable: ordinarySendTrampolines!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
- genSpecialSelectorEqualsEquals
- 	"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 primDescriptor branchDescriptor nExts
- 	  counterAddress countTripped unforwardArg unforwardRcvr |
- 	<var: #countTripped type: #'AbstractInstruction *'>
- 	<var: #primDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
- 
- 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [ ^ super genSpecialSelectorEqualsEquals ].
- 
- 	self ssFlushTo: simStackPtr - 2.
- 	primDescriptor := self generatorAt: byte0.
- 
- 	nextPC := bytecodePC + primDescriptor numBytes.
- 	nExts := 0.
- 	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
- 	 branchDescriptor isExtension] whileTrue:
- 		[nExts := nExts + 1.
- 		 nextPC := nextPC + branchDescriptor numBytes].
- 	"Only interested in inlining if followed by a conditional branch."
- 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
- 		[^self genSpecialSelectorSend].
- 
- 	targetBytecodePC := nextPC
- 							+ branchDescriptor numBytes
- 							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
- 	postBranchPC := nextPC + branchDescriptor numBytes.
- 	unforwardRcvr := (self ssValue: 1) type ~= SSConstant
- 						or: [objectRepresentation shouldAnnotateObjectReference: (self ssValue: 1) constant].
- 	unforwardArg := self ssTop type ~= SSConstant
- 						or: [objectRepresentation shouldAnnotateObjectReference: self ssTop constant].
- 	self marshallSendArguments: 1.
- 
- 	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
- 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
- 	self flag: 'will need to use MoveAw32:R: if 64 bits'.
- 	self assert: objectMemory wordSize = CounterBytes.
- 	self MoveAw: counterAddress R: SendNumArgsReg.
- 	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
- 	"If counter trips simply abort the inlined comparison and send continuing to the following
- 	 branch *without* writing back.  A double decrement will not trip the second time."
- 	countTripped := self JumpCarry: 0.
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	unforwardRcvr ifTrue:
- 		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
- 	unforwardArg ifTrue:
- 		[objectRepresentation genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg].
- 	self CmpR: Arg0Reg R: ReceiverResultReg.
- 	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
- 	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
- 	self gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
- 		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
- 	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
- 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
- 	countTripped jmpTarget: self Label.
- 	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
- 		numArgs: 1
- 		sendTable: ordinarySendTrampolines!

Item was added:
+ ----- 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 primDescriptor branchDescriptor nExts label counterReg fixup
+ 	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
+ 	<var: #fixup type: #'BytecodeFixup *'>
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #primDescriptor type: #'BytecodeDescriptor *'>
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ 
+ 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [ ^ super genSpecialSelectorEqualsEquals ].
+ 
+ 	primDescriptor := self generatorAt: byte0.
+ 	regMask := 0.
+ 
+ 	nextPC := bytecodePC + primDescriptor numBytes.
+ 	nExts := 0.
+ 	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
+ 	 branchDescriptor isExtension] whileTrue:
+ 		[nExts := nExts + 1.
+ 		 nextPC := nextPC + branchDescriptor numBytes].
+ 	
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue:
+ 		[self ssFlushTo: simStackPtr - 2].
+ 	
+ 	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
+ 	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
+ 	
+ 	"if the rcvr or the arg is an annotable constant, we need to push it to a register 
+ 	else the forwarder check can't jump back to the comparison after unforwarding the constant"
+ 	unforwardArg
+ 		ifTrue: 
+ 			[unforwardRcvr
+ 				ifTrue:
+ 					[self allocateTwoRegistersInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
+ 					 self ssTop popToReg: argReg.
+ 					 (self ssValue:1) popToReg: rcvrReg]
+ 				ifFalse:
+ 					[argReg := self allocateOneRegister.
+ 					 self ssTop popToReg: argReg]]
+ 		ifFalse:
+ 			[self assert: unforwardRcvr.
+ 			 rcvrReg := self allocateOneRegister.
+ 			 (self ssValue:1) popToReg: rcvrReg].
+ 		
+ 	argReg ifNotNil: [ regMask := self registerMaskFor: regMask ].
+ 	rcvrReg ifNotNil: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
+ 	
+ 	"Here we can use Cq because the constant does not need to be annotated"
+ 	self assert: (unforwardArg not or: [argReg notNil]).
+ 	self assert: (unforwardRcvr not or: [rcvrReg notNil]).
+ 	
+ 	"Only interested in inlining if followed by a conditional branch."
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
+ 		[^ self genDirectEqualsEqualsArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg].
+ 
+ 	targetBytecodePC := nextPC
+ 							+ branchDescriptor numBytes
+ 							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
+ 	postBranchPC := nextPC + branchDescriptor numBytes.
+ 
+ 	counterReg := self allocateRegisterNotConflictingWith: regMask. "Use this as the count reg, can't conflict with the registers for the arg and the receiver of #==."
+ 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
+ 	self flag: 'will need to use MoveAw32:R: if 64 bits'.
+ 	self assert: objectMemory wordSize = CounterBytes.
+ 	self MoveAw: counterAddress R: counterReg.
+ 	self SubCq: 16r10000 R: counterReg. "Count executed"
+ 	"If counter trips simply abort the inlined comparison and send continuing to the following
+ 	 branch *without* writing back.  A double decrement will not trip the second time."
+ 	countTripped := self JumpCarry: 0.
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
+ 	
+ 	self ssPushConstant: objectMemory trueObject. "dummy value"
+ 	self assert: (unforwardArg or: [ unforwardRcvr ]).
+ 	
+ 	label := self Label.
+ 	
+ 	branchDescriptor isBranchTrue ifTrue: 
+ 		[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
+ 		self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ 		unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label  ].
+ 		unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ] ].
+ 	branchDescriptor isBranchFalse ifTrue: 
+ 		[ 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 ] ].
+ 	
+ 	"the jump has not been taken and forwarders have been followed."
+ 	self SubCq: 1 R: counterReg. "Count untaken"
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
+ 	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
+ 	
+ 	countTripped jmpTarget: self Label.
+ 	
+ 	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
+ 	^ self genDirectEqualsEqualsArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
  	| primDescriptor nextPC nExts branchDescriptor unforwardRcvr argReg targetBytecodePC
  	unforwardArg  rcvrReg jumpNotEqual jumpEqual postBranchPC label fixup |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #jumpEqual type: #'AbstractInstruction *'>
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	
  	primDescriptor := self generatorAt: byte0.
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"If branching the stack must be flushed for the merge"
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue:
  		[self ssFlushTo: simStackPtr - 2].
  
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  
  	"if the rcvr or the arg is an annotable constant, we need to push it to a register 
  	else the forwarder check can't jump back to the comparison after unforwarding the constant"
  	unforwardArg
  		ifTrue: 
  			[unforwardRcvr
  				ifTrue:
  					[self allocateTwoRegistersInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  					 self ssTop popToReg: argReg.
  					 (self ssValue:1) popToReg: rcvrReg]
  				ifFalse:
  					[argReg := self allocateOneRegister.
  					 self ssTop popToReg: argReg]]
  		ifFalse:
  			[self assert: unforwardRcvr.
  			 rcvrReg := self allocateOneRegister.
  			 (self ssValue:1) popToReg: rcvrReg].
  
  	label := self Label.
  	
  	"Here we can use Cq because the constant does not need to be annotated"
  	self assert: (unforwardArg not or: [argReg notNil]).
  	self assert: (unforwardRcvr not or: [rcvrReg notNil]).
  	unforwardArg 
  		ifFalse: [ self CmpCq: self ssTop constant R: rcvrReg ]
  		ifTrue: [ unforwardRcvr
  			ifFalse: [ self CmpCq: (self ssValue: 1) constant R: argReg ]
  			ifTrue: [ self CmpR: argReg R: rcvrReg ] ].
  			 
  	self ssPop: 2.
  
  	"If not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[jumpEqual := self JumpZero: 0.
  		 unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ].
  		 unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ].
  		 self genMoveFalseR: rcvrReg.
  		 jumpNotEqual := self Jump: 0.
  		 jumpEqual jmpTarget: (self genMoveTrueR: rcvrReg).
  		 jumpNotEqual jmpTarget: self Label.
  		 self ssPushRegister: rcvrReg.
  		 ^0].
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	(self fixupAt: nextPC - initialPC) targetInstruction = 0
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
  			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  
  	self assert: (unforwardArg or: [ unforwardRcvr ]).
  	branchDescriptor isBranchTrue ifTrue: 
  		[ deadCode ifFalse: [ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC ].
  		self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  		unforwardArg ifTrue: [ (deadCode or: [ unforwardRcvr ]) 
  			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
  			ifFalse: [ objectRepresentation 
  				genEnsureOopInRegNotForwarded: argReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ] ].
  		unforwardRcvr ifTrue: [ deadCode 
  			ifTrue: [objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ]
  			ifFalse: [objectRepresentation 
  				genEnsureOopInRegNotForwarded: rcvrReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ] ] ].
  	branchDescriptor isBranchFalse ifTrue: 
+ 		[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
+ 		self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
- 		[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
- 		self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  		unforwardArg ifTrue: [ unforwardRcvr 
  			ifFalse: [objectRepresentation 
  				genEnsureOopInRegNotForwarded: argReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ]
+ 			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ] ].
- 			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ] ].
  		unforwardRcvr ifTrue: 
  			[ objectRepresentation 
  				genEnsureOopInRegNotForwarded: rcvrReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ].
  		"Not reached"].
  	^0!



More information about the Vm-dev mailing list