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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 24 10:01:16 UTC 2015


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

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

Name: VMMaker.oscog-cb.1252
Author: cb
Time: 24 April 2015, 11:59:54.377 am
UUID: 020130de-cdca-49ec-8f3f-2fa2d3d110d2
Ancestors: VMMaker.oscog-eem.1251

In order to fix the SistaCogit (still crashing somehow), I refactored the #== code which was duplicated three times between the Stack v3 / Stack Spur / Sista Spur cogits, mainly by creating 2 smaller methods which are now called by the 3 duplicated methods.

I introduced: #extractMaybeBranchDescriptorInto: so I don't need to duplicate the code that fetch the branch descriptor in #== and comparison.

Removed a useless allocateCallReg in genStorePop:RemoteTemp:At: because the call reg are saved in the trampoline.

Removed a duplicated self assert: needsFrame in genStorePop: popBoolean LiteralVariable: litVarIndex (Eliot moved it to the beginning of the method).

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

Item was added:
+ ----- Method: CogObjectRepresentation>>genEnsureOopInRegNotForwarded:scratchReg:jumpBackTo: (in category 'compile abstract instructions') -----
+ genEnsureOopInRegNotForwarded: reg scratchReg: scratch jumpBackTo: instruction
+ 	"Make sure that the oop in reg is not forwarded.  By default there is
+ 	 nothing to do.  Subclasses for memory managers that forward will override."
+ 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genDirectEqualsEqualsNoBranchArg:rcvr:argReg:rcvrReg: (in category 'bytecode generators') -----
- genDirectEqualsEqualsNoBranchArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg
- 	<inline: true>
- 	| label jumpEqual jumpNotEqual |
- 	label := self Label.
- 	self genEqualsEqualsComparisonArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: 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 removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genEqualsEqualsComparisonArg:rcvr:argReg:rcvrReg: (in category 'bytecode generators') -----
- genEqualsEqualsComparisonArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg
- 	<inline: true>
- 	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 ] ].	 !

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
- 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst
  	  counterAddress countTripped counterReg |
  	<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])].
  
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 	
- 	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 allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg). "Use this as the count reg, can't conflict with the registers for the arg and the receiver"
  	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"
  
  	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 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 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 label counterReg fixup
- 	| 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].
  	
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
- 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue:
- 		[self ssFlushTo: simStackPtr - 2].
  	
  	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 ].
- 	"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 allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
- 					 self ssTop popToReg: argReg.
- 					 (self ssValue:1) popToReg: rcvrReg]
- 				ifFalse:
- 					[argReg := self allocateRegForStackTopEntry.
- 					 self ssTop popToReg: argReg]]
- 		ifFalse:
- 			[self assert: unforwardRcvr.
- 			 rcvrReg := self allocateRegForStackEntryAt: 1.
- 			 (self ssValue:1) popToReg: rcvrReg].
  		
  	argReg ifNotNil: [ regMask := self registerMaskFor: argReg ].
  	rcvrReg ifNotNil: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
  	
- 	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 genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
- 		[^ self genDirectEqualsEqualsNoBranchArg: 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 allocateRegNotConflictingWith: 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 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 genEqualsEqualsComparisonArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg.
  	
  	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. 
  	
  	"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: fixup.
  	
  	countTripped jmpTarget: self Label.
  	
  	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
+ 	self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
- 	self genDirectEqualsEqualsNoBranchArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg.
  	^ 0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>allocateEqualsEqualsRegistersArgNeedsReg:rcvrNeedsReg:into: (in category 'bytecode generator support') -----
+ allocateEqualsEqualsRegistersArgNeedsReg: argNeedsReg rcvrNeedsReg: rcvrNeedsReg into: binaryBlock
+ 	<inline: true>
+ 	| argReg rcvrReg |
+ 	self assert: (argNeedsReg or: [rcvrNeedsReg]).
+ 	argNeedsReg
+ 		ifTrue: 
+ 			[rcvrNeedsReg
+ 				ifTrue:
+ 					[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
+ 					 self ssTop popToReg: argReg.
+ 					 (self ssValue: 1) popToReg: rcvrReg]
+ 				ifFalse:
+ 					[argReg := self allocateRegForStackTopEntry.
+ 					 self ssTop popToReg: argReg]]
+ 		ifFalse:
+ 			[self assert: rcvrNeedsReg.
+ 			rcvrReg := self allocateRegForStackEntryAt: 1.
+ 			(self ssValue:1) popToReg: rcvrReg].
+ 		
+ 	self assert: (argNeedsReg not or: [argReg notNil]).
+ 	self assert: (rcvrNeedsReg not or: [rcvrReg notNil]).
+ 	
+ 	binaryBlock value: rcvrReg value: argReg.!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>extractMaybeBranchDescriptorInto: (in category 'bytecode generator support') -----
+ extractMaybeBranchDescriptorInto: fourArgBlock
+ 	"Looks one instruction ahead of the current bytecodePC and answers its bytecode descriptor and its pc.
+ 	If the instruction found is a branch, also answers the pc after the branch and the pc targetted by the branch"
+ 	| primDescriptor nextPC nExts branchDescriptor targetBytecodePC postBranchPC |
+ 	<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].
+ 
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse: 
+ 		[ ^ fourArgBlock value: branchDescriptor value: nextPC value: 0 value: 0 ].
+ 	
+ 	targetBytecodePC := nextPC
+ 							+ branchDescriptor numBytes
+ 							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
+ 	postBranchPC := nextPC + branchDescriptor numBytes.
+ 	
+ 	fourArgBlock value: branchDescriptor value: nextPC value: postBranchPC value: targetBytecodePC!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') -----
  genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg
  	"Inlined comparison. opTrue = jump for true and opFalse = jump for false"
+ 	| nextPC branchDescriptor targetBytecodePC postBranchPC |	
+ 		
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 	
- 	| nextPC branchDescriptor nExts |	
- 	nextPC := bytecodePC + 3.
- 	nExts := 0.	
- 	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
- 	 branchDescriptor isExtension] whileTrue:
- 		[nExts := nExts + 1.
- 	 	 nextPC := nextPC + branchDescriptor numBytes].
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])
  		ifTrue: "This is the path where the inlined comparison is followed immediately by a branch"
+ 			[ (self fixupAt: nextPC - initialPC) targetInstruction = 0
- 			[| targetBytecodePC postBranchPC |
- 			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 gen: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse])
  				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. 
  			deadCode ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC) ] ]
  		ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch"
  			[| condJump jump |
  			condJump := self gen: opTrue operand: 0.
  			self genMoveFalseR: destReg.
  	 		jump := self Jump: 0.
  			condJump jmpTarget: (self genMoveTrueR: destReg).
  			jump jmpTarget: self Label].
  	^ 0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genEqualsEqualsComparisonArgIsConstant:rcvrIsConstant:argReg:rcvrReg: (in category 'bytecode generator support') -----
+ genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg
+ 	"Generates the Cmp instruction for #==. The instruction is different if one of the operands is a constant.
+ 	In the case of the v3 memory manager, the constant could be annotable." 
+ 	<inline: true>
+ 	argIsConstant 
+ 		ifTrue: [ self genCompConstant: self ssTop constant R: rcvrReg ]
+ 		ifFalse: [ rcvrIsConstant
+ 			ifTrue: [ self genCompConstant: (self ssValue: 1) constant R: argReg ]
+ 			ifFalse: [ self CmpR: argReg R: rcvrReg ] ].!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genEqualsEqualsForwarderChecksArg:rcvr:argReg:rcvrReg:label:fixup:canBeDead: (in category 'bytecode generator support') -----
+ genEqualsEqualsForwarderChecksArg: unforwardArg rcvr: unforwardRcvr argReg: argReg rcvrReg: rcvrReg label: label fixup: fixup canBeDead: canBeDead
+ 	"This code generates the forwarders checks if #== is followed by a branch. The forwarders checks need to jump back to the comparison (label) if
+ 	a forwarder is found, else jump forward to the correct place, the postBranch or branch target (fixup), if this is the last forwarder check, or jump to 
+ 	the next forwarder checkif there are 2, or just fall through if it needs to jump to the postBranch and that the branch is dead code"
+ 	<inline: true>
+ 	unforwardArg ifTrue: [ (canBeDead or: [ unforwardRcvr ]) 
+ 		ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
+ 		ifFalse: [ objectRepresentation 
+ 			genEnsureOopInRegNotForwarded: argReg 
+ 			scratchReg: TempReg 
+ 			ifForwarder: label
+ 			ifNotForwarder: fixup ] ].
+ 	unforwardRcvr ifTrue: [ canBeDead 
+ 		ifTrue: [objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg jumpBackTo: label ]
+ 		ifFalse: [objectRepresentation 
+ 			genEnsureOopInRegNotForwarded: rcvrReg 
+ 			scratchReg: TempReg 
+ 			ifForwarder: label
+ 			ifNotForwarder: fixup ] ]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genEqualsEqualsNoBranchArgIsConstant:rcvrIsConstant:argReg:rcvrReg: (in category 'bytecode generator support') -----
+ genEqualsEqualsNoBranchArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg
+ 	"Generates the machine code for #== in the case where the instruction is not followed by a branch"
+ 	<var: #jumpEqual type: #'AbstractInstruction *'>
+ 	<var: #jumpNotEqual type: #'AbstractInstruction *'>
+ 	| label jumpEqual jumpNotEqual |
+ 	label := self Label.
+ 	self genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
+ 	self ssPop: 2.
+ 	jumpEqual := self JumpZero: 0.
+ 	 argIsConstant ifFalse: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ].
+ 	 rcvrIsConstant ifFalse: [ 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: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
+ 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
- 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	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)].
  
  	(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])].
  
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 
- 	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.
  	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 Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1
  		sendTable: ordinarySendTrampolines.!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
+ 	| nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
+ 	unforwardArg  rcvrReg postBranchPC label fixup |
- 	| 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 *'>
  	
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
- 	primDescriptor := self generatorAt: byte0.
  
+ 	"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) and does not generate forwarder checks."
- 	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.
  
+ 	self 
+ 		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
+ 		rcvrNeedsReg: unforwardRcvr 
+ 		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
- 	"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 allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
- 					 self ssTop popToReg: argReg.
- 					 (self ssValue:1) popToReg: rcvrReg]
- 				ifFalse:
- 					[argReg := self allocateRegForStackTopEntry.
- 					 self ssTop popToReg: argReg]]
- 		ifFalse:
- 			[self assert: unforwardRcvr.
- 			 rcvrReg := self allocateRegForStackEntryAt: 1.
- 			 (self ssValue:1) popToReg: rcvrReg].
  
+ 	"If not followed by a branch, resolve to true or false."
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
+ 		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
- 	label := self Label.
  	
+ 	"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.
- 	"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.
+ 		self 
+ 			genEqualsEqualsForwarderChecksArg: unforwardArg 
+ 			rcvr: unforwardRcvr 
+ 			argReg: argReg 
+ 			rcvrReg: rcvrReg 
+ 			label: label 
+ 			fixup: fixup 
+ 			canBeDead: deadCode ].
- 		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.
+ 		self 
+ 			genEqualsEqualsForwarderChecksArg: unforwardArg 
+ 			rcvr: unforwardRcvr 
+ 			argReg: argReg 
+ 			rcvrReg: rcvrReg 
+ 			label: label 
+ 			fixup: fixup 
+ 			canBeDead: false].
- 		unforwardArg ifTrue: [ unforwardRcvr 
- 			ifFalse: [objectRepresentation 
- 				genEnsureOopInRegNotForwarded: argReg 
- 				scratchReg: TempReg 
- 				ifForwarder: label
- 				ifNotForwarder: fixup ]
- 			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ] ].
- 		unforwardRcvr ifTrue: 
- 			[ objectRepresentation 
- 				genEnsureOopInRegNotForwarded: rcvrReg 
- 				scratchReg: TempReg 
- 				ifForwarder: label
- 				ifNotForwarder: fixup ].
- 		"Not reached"].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:LiteralVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
  	| topReg assocReg association |
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the literal store, unless we we smart enough to realise that ReceiverResultReg
  	 was unused after the literal variable store, unlikely given that methods
  	 return self by default."
  	self assert: needsFrame.
  	"N.B.  No need to check the stack for references because we generate code for
  	 literal variable loads that stores the result in a register, deferring only the register push."
  	association := self getLiteral: litVarIndex.
  	
  	"Avoid store check for immediate values"
+ 	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
- 	(objectRepresentation isUnannotatableConstant: self ssTop) 
- 		ifTrue:
  			[ assocReg := self allocateAnyReg.
  			self genMoveConstant: association R: assocReg.
  			 objectRepresentation
  				genEnsureObjInRegNotForwarded: assocReg
  				scratchReg: TempReg.
  			self ssStorePop: popBoolean toReg: TempReg.
  			 traceStores > 0 ifTrue:
  				[ assocReg = ReceiverResultReg ifFalse: 
  					[ self ssAllocateRequiredReg: ReceiverResultReg.
  					optStatus isReceiverResultRegLive: false.
  					self MoveR: assocReg R: ReceiverResultReg ].
  				self CallRT: ceTraceStoreTrampoline].
  			 ^objectRepresentation
  				genStoreImmediateInSourceReg: TempReg
  				slotIndex: ValueIndex
+ 				destReg: assocReg ].
- 				destReg: assocReg ]
- 			ifFalse: [ self assert: needsFrame. "because ReceiverResult reg is used for storeCheckTrampoline" ].
  		
- 		
  	topReg := self allocateRegForStackTopEntryNotConflictingWith: (self registerMaskFor: ReceiverResultReg).
  	self ssStorePop: popBoolean toReg: topReg.
  	optStatus isReceiverResultRegLive: false.
  	self ssAllocateCallReg: ReceiverResultReg. "for ceStoreCheck call in genStoreSourceReg: has to be ReceiverResultReg"
  	self genMoveConstant: association R: ReceiverResultReg.
  	objectRepresentation genEnsureObjInRegNotForwarded: ReceiverResultReg scratchReg: TempReg.
  	traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: ValueIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:RemoteTemp:At: (in category 'bytecode generator support') -----
  genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex
  	<inline: false>
  	| topReg topSpilled tempVectReg |
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the temote temp store, unless we we smart enough to realise that
  	 ReceiverResultReg was unused after the literal variable store, unlikely given
  	 that methods return self by default."
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
  	"N.B.  No need to check the stack for references because we generate code for
  	 remote temp loads that stores the result in a register, deferring only the register push."
  	"Avoid store check for immediate values"
  	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
  		[ tempVectReg := self allocateAnyReg.
  		 self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: tempVectReg.
  		 self ssStorePop: popBoolean toReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[ tempVectReg = ReceiverResultReg ifFalse: 
  					[ self ssAllocateRequiredReg: ReceiverResultReg.
  					optStatus isReceiverResultRegLive: false.
  					self MoveR: tempVectReg R: ReceiverResultReg ].
  			self CallRT: ceTraceStoreTrampoline].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: slotIndex
  			destReg: tempVectReg].
  	topReg := self allocateRegForStackTopEntryNotConflictingWith: (self registerMaskFor: ReceiverResultReg).
- 	self ssPop: 1.
- 	"for the ceStoreCheck call in genStoreSourceReg:... below"
- 	self ssAllocateCallReg: topReg and: ReceiverResultReg.
- 	self ssPush: 1.
  	topSpilled := self ssTop spilled.
  	self ssStorePop: (popBoolean or: [topSpilled]) toReg: topReg.
  	popBoolean ifFalse:
  		[topSpilled ifFalse: [self ssPop: 1].
  		 self ssPushRegister: topReg].
  	self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg.
  	 traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genVanillaSpecialSelectorEqualsEquals
+ 	| nextPC postBranchPC targetBytecodePC branchDescriptor
+ 	  rcvrReg argReg argIsConstant rcvrIsConstant  |
- 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
- 	  jumpEqual jumpNotEqual rcvrReg argReg argIsConstant rcvrIsConstant  |
- 	<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].
- 
- 	"Don't use ReceiverResultReg for receiver to keep ReceiverResultReg live.
- 	 Optimize e.g. rcvr == nil, the common case for ifNil: et al."
  	
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 	
  	argIsConstant := self ssTop type = SSConstant.
+ 	"they can't be both constants because we do not have instructions manipulating two constants, 
+ 	if this is the case, which can happen due to annotable constants that can be moved in memory 
+ 	with become and therefore can't resolve #== at compilation time, still write the rcvr into a 
+ 	register as if it was not a constant. It's uncommon anyway."
+ 	rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant]. 
- 	rcvrIsConstant := argIsConstant and: [ (self ssValue:1) type = SSConstant ].
  	
+ 	self 
+ 		allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not 
+ 		rcvrNeedsReg: rcvrIsConstant not 
+ 		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
- 	argIsConstant
- 		ifFalse: 
- 			[rcvrIsConstant
- 				ifFalse:
- 					[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
- 					 self ssTop popToReg: argReg.
- 					 (self ssValue:1) popToReg: rcvrReg]
- 				ifTrue:
- 					[argReg := self allocateRegForStackTopEntry.
- 					 self ssTop popToReg: argReg]]
- 		ifTrue:
- 			[self assert: rcvrIsConstant not.
- 			 rcvrReg := self allocateRegForStackEntryAt: 1.
- 			 (self ssValue:1) popToReg: rcvrReg].
  	
- 	argIsConstant 
- 		ifTrue: [ self genCompConstant: self ssTop constant R: rcvrReg ]
- 		ifFalse: [ rcvrIsConstant
- 			ifTrue: [ self genCompConstant: (self ssValue: 1) constant R: argReg ]
- 			ifFalse: [ 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:
+ 		[ ^ self genEqualsEqualsNoBranchArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg].
+ 	
+ 	"If branching the stack must be flushed for the merge"
+ 	self ssFlushTo: simStackPtr - 2.
+ 	
+ 	self genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
+ 	self ssPop: 2.
- 		[jumpNotEqual := self JumpNonZero: 0.
- 		 self genMoveTrueR: rcvrReg.
- 		 jumpEqual := self Jump: 0.
- 		 jumpNotEqual jmpTarget: (self genMoveFalseR: rcvrReg).
- 		 jumpEqual 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 gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  		deadCode ifFalse: [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)].
  	^0!



More information about the Vm-dev mailing list