[Vm-dev] VM Maker: VMMaker.oscogSPC-eem.2130.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Feb 16 02:40:43 UTC 2017


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

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

Name: VMMaker.oscogSPC-eem.2130
Author: eem
Time: 15 February 2017, 6:39:48.551135 pm
UUID: 646641b5-87bf-4dcd-85da-fdcff6123193
Ancestors: VMMaker.oscogSPC-eem.2129

Cogit:
Add support for SwapR:R:Scratch:, map it to XCHGRR on x64 & x86 and use it in the nascent parallel move code in RegisterAllocatingCogit.
Fix a bug in x64's XCHGRR.
Add generation tests for x64's XCHGRR.

Have printCogMethods print totals of the number of methods & PICs in the code zone.
Fix a slip in printCogMethodsWithPrimitive:.

RegisterAllocatingCogit:
Use ensureFixupAt: not ensureNonMergeFixupAt: for the targets of branches.  I was confused.  This gets the system much farther.
Nuke the check for no code being generated in ensureFixupAt:.  We're beyond that.
Deal with merging with a constant assigned to a register.

=============== Diff against VMMaker.oscogSPC-eem.2129 ===============

Item was added:
+ ----- Method: CogAbstractInstruction>>genSwapR:R:Scratch: (in category 'abstract instructions') -----
+ genSwapR: regA R: regB Scratch: regTmp
+ 	"Generic register swap code.  Subclasses for processors that have a true exchange operation will override to use it."
+ 	| first |
+ 	<var: 'first' type: #'AbstractInstruction *'>
+ 	first :=
+ 	cogit MoveR: regA R: regTmp.
+ 	cogit MoveR: regB R: regA.
+ 	cogit MoveR: TempReg R: regB.
+ 	^first!

Item was added:
+ ----- Method: CogIA32Compiler>>genSwapR:R:Scratch: (in category 'abstract instructions') -----
+ genSwapR: regA R: regB Scratch: regTmp
+ 	^cogit gen: XCHGRR operand: regA operand: regB!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethods (in category 'printing') -----
  printCogMethods
  	<api>
  	<returnTypeC: #void>
+ 	| cogMethod nm nc no nf nu |
- 	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	nm := nc := no := nf := nu := 0.
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
  		[coInterpreter printCogMethod: cogMethod.
+ 		 cogMethod cmType
+ 			caseOf: {
+ 			[CMFree]		->	[nf := nf + 1].
+ 			[CMMethod]	->	[nm := nm + 1].
+ 			[CMClosedPIC]	->	[nc := nc + 1].
+ 			[CMOpenPIC]	->	[no:= no+ 1] }
+ 			otherwise: [nu := nu + 1].
+ 		 cogMethod := self methodAfter: cogMethod].
+ 	coInterpreter print: 'CMMethod '; printNum: nm;  print: ' CMClosedPIC '; printNum: nc;  print: ' CMOpenPIC '; printNum: no;  print: ' CMFree '; printNum: nf.
+ 	nu > 0 ifTrue:
+ 		[coInterpreter print: ' UNKNOWN '; printNum: nu].
+ 	coInterpreter print: ' total '; printNum: nm+nc+no+nf+nu; cr!
- 		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethodsWithPrimitive: (in category 'printing') -----
  printCogMethodsWithPrimitive: primIdx
  	<api>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[(cogMethod cmType = CMMethod
- 		[(cogMethod cmType ~= CMFree
  		  and: [primIdx = (coInterpreter primitiveIndexOfMethod: cogMethod methodObject
  							header: cogMethod methodHeader)]) ifTrue:
  			[coInterpreter printCogMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>isMergedWithTargetEntry: (in category 'comparing') -----
  isMergedWithTargetEntry: targetEntry
  	"The receiver is a simStackEntry at a jump to the corresponding simStackEntry at the jump's target.
  	 Answer if no merge is required for the jump."
  	<var: 'ssEntry' type: #'CogSimStackEntry *'>
  	spilled ~= targetEntry spilled ifTrue: "push or pop required"
  		[^false].
  	(liveRegister = NoReg and: [targetEntry liveRegister ~= NoReg]) ifTrue: "register load required"
  		[^false].
  	(liveRegister ~= NoReg
  	 and: [liveRegister = targetEntry liveRegister
  	 and: [type = targetEntry type
  	 and: [type = SSConstant or: [type = SSRegister and: [register = targetEntry register]]]]]) ifTrue:
  		[^true].
  	((type = SSBaseOffset or: [type == SSSpill])
  	 and: [(targetEntry type = SSBaseOffset or: [targetEntry type == SSSpill])
  	 and: [offset = targetEntry offset and: [register = targetEntry register]]]) ifTrue:
  		[^true].
+ 	"self: const =1 (16r1) (live: Extra4Reg) {172} vs reg ReceiverResultReg {127}"
+ 	"self: reg ReceiverResultReg {95} vs reg Extra5Reg {85}"
+ 	((type = SSConstant and: [targetEntry type = SSRegister and: [liveRegister ~= targetEntry registerOrNone]])
+ 	 or: [type = SSRegister and: [targetEntry type = SSRegister and: [register ~= targetEntry registerOrNone]]]) ifFalse:
+ 		[self halt: 'comment the incompatible pair please'].
- 	self halt: 'comment the incompatible pair please'.
  	^false!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileForwardsWith: (in category 'compile abstract instructions') -----
  reconcileForwardsWith: targetEntry
  	"Make the state of the receiver, a stack entry at the end of a basic block,
  	 the same as the corresponding simStackEntry at the target of a preceding
  	 jump to the beginning of the next basic block.  Make sure targetEntry
  	 reflects the state of the merged simStack; it will be installed as the current
  	 entry by restoreSimStackAtMergePoint: in mergeWithFixupIfRequired:.
  
  	 Answer if the liveRegister for the targetEntry (if any) should be deassigned;
  	 this is because if merging a non-temp with a temp that has a live register we
  	 can assign to the register, but must unassign the register from the temp,
  	 otherwise the temp will acquire the merged value without an assignment."
  	<var: #targetEntry type: #'SimStackEntry *'>
  	| targetReg |
  	(targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  		[| reg |
  		 self assert: targetEntry spilled.
  		 (self isSameEntryAs: targetEntry) ifTrue:
  			[self assert: spilled.
  			 ^false].
  		 (reg := self registerOrNone) = NoReg ifTrue: [reg := TempReg].
  		 self storeToReg: reg.
  		 spilled
  			ifTrue: [cogit MoveR: reg Mw: targetEntry offset r: targetEntry register]
  			ifFalse: [cogit PushR: reg].
  		 ^false].
  	liveRegister ~= NoReg ifTrue:
  		[liveRegister ~= targetReg ifTrue:
  			[cogit MoveR: liveRegister R: targetReg].
  		 (spilled and: [targetEntry spilled not]) ifTrue:
  			[cogit AddCq: objectRepresentation wordSize R: SPReg].
  		 ^false].
  	spilled
  		ifTrue:
  			[targetEntry spilled ifFalse:
  				[cogit PopR: targetReg. "KISS; generate the least number of instructions..."
  				 ^false]]
  		ifFalse:
  			[targetEntry spilled ifTrue:
  				[cogit SubCq: objectRepresentation wordSize R: SPReg]].
  	type caseOf: {
  		[SSBaseOffset]	-> [cogit MoveMw: offset r: register R: targetReg].
  		[SSSpill]		-> [cogit MoveMw: offset r: register R: targetReg].
  		[SSConstant]	-> [cogit genMoveConstant: constant R: targetReg].
  		[SSRegister]	-> [register ~= targetReg ifTrue:
  								[cogit MoveR: register R: targetReg]] }.
  	(targetEntry type = SSConstant
  	 and: [type ~= SSConstant or: [constant ~= targetEntry constant]]) ifTrue:
  		[targetEntry
  			register: targetReg;
  			type: SSRegister].
+ 	"If merging a constant with a constant assigned to a register, then the register must be deassigned from any temps."
+ 	^targetEntry type = SSConstant
  	"If merging a non-temp with a temp that has a live register we can assign
  	 to the register, but must unassign the register from the temp, otherwise
  	 the temp will acquire the merged value without an assignment."
+ 	 or: [targetEntry type = SSBaseOffset
+ 		  and: [targetEntry register = FPReg
+ 		  and: [(self isSameEntryAs: targetEntry) not]]]!
- 	^targetEntry type = SSBaseOffset
- 	  and: [targetEntry register = FPReg
- 	  and: [(self isSameEntryAs: targetEntry) not]]!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeXCHGRR (in category 'generate machine code') -----
  concretizeXCHGRR
  	| r1 r2 |
  	r1 := operands at: 0.
  	r2 := operands at: 1.
  	r2 = RAX ifTrue:
  		[r2 := r1. r1 := RAX].
  	r1 = RAX ifTrue:
  		[machineCode
  			at: 0 put: (self rexR: 0 x: 0 b: r2);
  			at: 1 put: 16r90 + (r2 \\ 8).
  		 ^machineCodeSize := 2].
  	machineCode
  		at: 0 put: (self rexR: r1 x: 0 b: r2);
+ 		at: 1 put: 16r87;
+ 		at: 2 put: (self mod: ModReg RM: r2 RO: r1).
- 		at: 1 put: 87;
- 		at: 2 put: (self mod: r2 RM: 0 RO: r1).
  	^machineCodeSize := 3!

Item was added:
+ ----- Method: CogX64Compiler>>genSwapR:R:Scratch: (in category 'abstract instructions') -----
+ genSwapR: regA R: regB Scratch: regTmp
+ 	^cogit gen: XCHGRR operand: regA operand: regB!

Item was added:
+ ----- Method: CogX64CompilerTests>>testXCHGRR (in category 'tests') -----
+ testXCHGRR
+ 	"CogX64CompilerTests new testXCHGRR"
+ 	| xchgrr |
+ 	xchgrr := (self concreteCompilerClass bindingOf: #XCHGRR) value.
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :sregname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :dregname| | inst len |
+ 			inst := self gen: xchgrr operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 					plainJane := self strip: str.
+ 					herIntended := dreg = 0
+ 										ifTrue: [sreg = 0 ifTrue: ['nop '] ifFalse: ['xchgq ', dregname, ', ', sregname]]
+ 										ifFalse: ['xchgq ', sregname, ', ', dregname].
+ 					self assert: herIntended equals: plainJane.
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: Cogit>>SwapR:R:Scratch: (in category 'abstract instructions') -----
+ SwapR: regA R: regB Scratch: regTmp
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^backEnd genSwapR: regA R: regB Scratch: regTmp!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>deassignRegisterForTempVar:in: (in category 'bytecode generator support') -----
  deassignRegisterForTempVar: targetEntry in: mergeSimStack
  	"If merging a non-temp with a temp that has a live register we can assign
  	 to the register, but must unassign the register from the temp, otherwise
  	 the temp will acquire the merged value without an assignment.  The targetEntry
  	 must also be transmogrified into an SSRegister entry."
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<var: #duplicateEntry type: #'SimStackEntry *'>
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	<inline: true>
  	| reg |
  	reg := targetEntry liveRegister.
+ 	self assert: ((targetEntry type = SSConstant and: [reg ~= NoReg])
+ 				or: [targetEntry type = SSBaseOffset and: [targetEntry register = FPReg]]).
+ 	targetEntry type = SSConstant
+ 		ifTrue:
+ 			[simStackPtr to: 0 by: -1 do:
+ 				[:j| | duplicateEntry |
+ 				 duplicateEntry := self simStack: mergeSimStack at: j.
+ 				 (duplicateEntry registerOrNone = reg
+ 				  and: [duplicateEntry type = SSBaseOffset or: [duplicateEntry type = SSSpill]]) ifTrue:
+ 					[duplicateEntry liveRegister: NoReg]]]
+ 		ifFalse:
+ 			[simStackPtr to: 0 by: -1 do:
+ 				[:j| | duplicateEntry |
+ 				 duplicateEntry := self simStack: mergeSimStack at: j.
+ 				 (targetEntry isSameEntryAs: duplicateEntry) ifTrue:
+ 					[duplicateEntry liveRegister: NoReg]]].
- 	self assert: (targetEntry type = SSBaseOffset and: [targetEntry register = FPReg]).
- 	simStackPtr to: 0 by: -1 do:
- 		[:j| | duplicateEntry |
- 		 duplicateEntry := self simStack: mergeSimStack at: j.
- 		 (targetEntry isSameEntryAs: duplicateEntry) ifTrue:
- 			[duplicateEntry liveRegister: NoReg]].
  	targetEntry
  		type: SSRegister;
  		register: reg!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureFixupAt: (in category 'bytecode generator support') -----
  ensureFixupAt: targetPC
  	"Make sure there's a flagged fixup at the target pc in fixups.
  	 Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction.
  	 Override to enerate stack merging code if required."
+ 	| fixup |	
- 	| fixup startOpcodeIndex |	
  	<var: #fixup type: #'BytecodeFixup *'>
  	fixup := self fixupAt:  targetPC.
  	fixup needsFixup 
  		ifTrue:
  			[fixup mergeSimStack
  				ifNil: [self setMergeSimStackOf: fixup]
+ 				ifNotNil: [self mergeCurrentSimStackWith: fixup]]
- 				ifNotNil:
- 					[startOpcodeIndex := opcodeIndex.
- 					 self mergeCurrentSimStackWith: fixup.
- 					 self deny: (startOpcodeIndex = opcodeIndex and: [thisContext sender method sendsSelector: #mergeRequiredForJumpTo:])]]
  		ifFalse: 
  			[self assert: fixup mergeSimStack isNil.
  			 self moveVolatileSimStackEntriesToRegisters.
  			 self setMergeSimStackOf: fixup].
  	^super ensureFixupAt: targetPC!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>flushLiveRegistersForSuspensionPoint (in category 'bytecode generator support') -----
  flushLiveRegistersForSuspensionPoint
  	"Flush any live registers for a C call at a suspension/resumption point, i.e.flush all registers.
  	 Answer if any registers were flushed."
  	<inline: true>
  	| flushed |
  	flushed := false.
  	self assert: simSelf type = SSBaseOffset.
  	simSelf liveRegister ~= NoReg ifTrue:
  		[simSelf liveRegister: NoReg.
  		 flushed := true].
  	0 to: simStackPtr do:
  		[:i|
+ 		 self assert: (i < methodOrBlockNumTemps
+ 						ifTrue: [(self simStackAt: i) type = SSBaseOffset]
+ 						ifFalse: [(self simStackAt: i)  spilled]).
- 		 self assert: (self simStackAt: i) type = (i < methodOrBlockNumTemps
- 													ifTrue: [SSBaseOffset]
- 													ifFalse: [SSSpill]).
  		 (self simStackAt: i) liveRegister ~= NoReg ifTrue:
  			[(self simStackAt: i) liveRegister: NoReg.
  			 flushed := true]].
  	^flushed!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	| nextPC branchDescriptor unforwardRcvr argReg targetPC
  	  unforwardArg  rcvrReg postBranchPC retry fixup
  	  comparison
  	  needMergeToTarget needMergeToContinue |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #toContinueLabel type: #'AbstractInstruction *'>
  	<var: #toTargetLabel type: #'AbstractInstruction *'>
  	<var: #comparison type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
  
  	"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."
  	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 not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^self 
  			genIdenticalNoBranchArgIsConstant: unforwardArg not
  			rcvrIsConstant: unforwardRcvr not
  			argReg: argReg 
  			rcvrReg: rcvrReg 
  			orNotIf: orNot].
  	
  	self assert: (unforwardArg or: [unforwardRcvr]).
  
  	retry := self Label.
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	(self fixupAt: nextPC) notAFixup "The next instruction is dead.  we can skip it."
  		ifTrue:  [deadCode := true]
  		ifFalse: [self deny: deadCode]. "push dummy value below"
  
  	"self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack"
  	"If there are merges to be performed on the forward branches we have to execute
  	 the merge code only along the path requiring that merge, and exactly once."
  	needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
  	needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
  	orNot == branchDescriptor isBranchTrue
  		ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
  			[fixup := needMergeToContinue
  						ifTrue: [0] "jumps will fall-through to to-continue merge code"
+ 						ifFalse: [self ensureFixupAt: postBranchPC].
- 						ifFalse: [self ensureNonMergeFixupAt: postBranchPC].
  			 comparison := self JumpZero: (needMergeToTarget
  												ifTrue: [0] "comparison will be fixed up to to-target merge code"
+ 												ifFalse: [self ensureFixupAt: targetPC])]
- 												ifFalse: [self ensureNonMergeFixupAt: targetPC])]
  		ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
  			[fixup := needMergeToTarget
  						ifTrue: [0] "jumps will fall-through to to-target merge code"
+ 						ifFalse: [self ensureFixupAt: targetPC].
- 						ifFalse: [(self ensureNonMergeFixupAt: targetPC)].
  			 comparison := self JumpZero: (needMergeToContinue
  												ifTrue: [0] "comparison will be fixed up to to-continue merge code"
+ 												ifFalse: [self ensureFixupAt: postBranchPC])].
- 												ifFalse: [self ensureNonMergeFixupAt: postBranchPC])].
  
  	"The forwarders check(s) need(s) to jump back to the comparison (retry) if a forwarder is found,
  	 else jump forward either to the next forwarder check or to the postBranch or branch target (fixup).
  	 But if there is merge code along a path, the jump must be to the merge code."
  	(unforwardArg and: [unforwardRcvr]) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: retry].
  	objectRepresentation 
  		genEnsureOopInRegNotForwarded: (unforwardRcvr ifTrue: [rcvrReg] ifFalse: [argReg]) 
  		scratchReg: TempReg 
  		ifForwarder: retry
  		ifNotForwarder: fixup.
  	"If fixup is zero then the ifNotForwarder path falls through to a Label which is interpreted
  	 as either to-continue or to-target, depending on orNot == branchDescriptor isBranchTrue."
  	orNot == branchDescriptor isBranchTrue
  		ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
  			[needMergeToContinue ifTrue: "fall-through to to-continue merge code"
  				[self Jump: (self ensureFixupAt: postBranchPC)].
  			 needMergeToTarget ifTrue: "fixup comparison to to-target merge code"
  				[comparison jmpTarget: self Label.
  				 self Jump: (self ensureFixupAt: targetPC)]]
  		ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
  			[needMergeToTarget ifTrue: "fall-through to to-target merge code"
  				[self Jump: (self ensureFixupAt: targetPC)].
  			 needMergeToContinue ifTrue: "fixup comparison to to-continue merge code"
  				[comparison jmpTarget: self Label.
  				 self Jump: (self ensureFixupAt: postBranchPC)]].
  
  	deadCode ifFalse: "duplicate the merge fixup's top of stack so as to avoid a false confict."
  		[self ssPushDesc: ((self fixupAt: nextPC) mergeSimStack at: simStackPtr + 1)].
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	| eventualTarget desc reg fixup ok mbb noMustBeBoolean |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #mbb type: #'AbstractInstruction *'>
  	eventualTarget := self eventualTargetOf: targetBytecodePC.
  	desc := self ssTop.
  	self ssPop: 1.
  
  	noMustBeBoolean := self extASpecifiesNoMustBeBoolean.
  	extA := 0.
  
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must annotate the bytecode for correct pc mapping."
  		 desc constant = boolean
  			ifTrue:
  				[deadCode := true. "Can't fall through."
  				 fixup := self ensureFixupAt: eventualTarget.
  				 self annotateBytecode: (self Jump: fixup)]
  		 	ifFalse:
  				[self annotateBytecode: (self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label])].
  		 ^0].
  
  	"try and use the top entry's register if any, but only if it can be destroyed."
  	reg := (desc type ~= SSRegister
  			or: [(self anyReferencesToRegister: desc register inAllButTopNItems: 0)
  			or: [(desc register = ReceiverResultReg and: [optStatus isReceiverResultRegLive])]])
  				ifTrue: [TempReg]
  				ifFalse: [desc register].
  	desc popToReg: reg.
  	"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.
  
  	"Merge required; must not generate merge code along untaken branch, so flip the order."
  	(self mergeRequiredForJumpTo: eventualTarget)
  		ifTrue:
  			[self genSubConstant: (boolean = objectMemory trueObject
  										ifTrue: [objectMemory falseObject]
  										ifFalse: [objectMemory trueObject])
  				R: reg.
  			 ok := self JumpZero: 0.
  			 self CmpCq: (boolean = objectMemory trueObject
  							ifTrue: [objectMemory trueObject - objectMemory falseObject]
  							ifFalse: [objectMemory falseObject - objectMemory trueObject])
  				R: reg.
  			 noMustBeBoolean ifTrue: 
  				[self JumpZero: (self ensureFixupAt: eventualTarget). "generates merge code"
  				 ok jmpTarget: (self annotateBytecode: self lastOpcode).
  				 ^0].
  			 mbb := self JumpNonZero: 0.
  			 self Jump: (self ensureFixupAt: eventualTarget). "generates merge code"
  			 mbb jmpTarget: self Label]
  		ifFalse:
  			[self genSubConstant: boolean R: reg.
+ 			 self JumpZero: (self ensureFixupAt: eventualTarget).
- 			 self JumpZero: (self ensureNonMergeFixupAt: eventualTarget).
  			 noMustBeBoolean ifTrue: 
  				[self annotateBytecode: self lastOpcode.
  				 ^0].
  			 self CmpCq: (boolean = objectMemory falseObject
  							ifTrue: [objectMemory trueObject - objectMemory falseObject]
  							ifFalse: [objectMemory falseObject - objectMemory trueObject])
  				R: reg.
  			 ok := self JumpZero: 0].
  
  	reg ~= TempReg ifTrue:
  		[self MoveR: reg R: TempReg].
  	self copySimStackToScratch: simSpillBase.
  	self ssFlushTo: simStackPtr.
  	self genCallMustBeBooleanFor: boolean.
  	"NOTREACHED"
  	ok jmpTarget: (self annotateBytecode: self Label).
  	self restoreSimStackFromScratch.
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetPC primDescriptor branchDescriptor
  	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index rcvrReg argReg branchToTarget needMergeToContinue needMergeToTarget |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	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: (self ssValue: 1) constant].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
  
  	"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].
  
  	"In-line the comparison and the jump, but if the types are not SmallInteger then we will need
  	 to do a send and fall through to the following conditional branch.  Since we're allocating values
  	 in registers we would like to keep those registers live on the inlined path and reload registers
  	 along the non-inlined send path.  The merge logic at the branch destinations handles this."
  	argIsInt
  		ifTrue:
  			[rcvrReg := self allocateRegForStackEntryAt: 1.
  			 (self ssValue: 1) popToReg: rcvrReg]
  		ifFalse:
  			[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  			 rcvrReg = Arg0Reg ifTrue:
  				[rcvrReg := argReg. argReg := Arg0Reg].
  			 self ssTop popToReg: argReg.
  			 (self ssValue: 1) popToReg: rcvrReg.
  			 rcvrIsInt ifFalse:
  				[self MoveR: argReg R: TempReg]].
  	self ssPop: 2.
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifFalse: "Neither known to be ints; and them together for the test..."
  								[objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg]
  							ifTrue: "One known; in-place single-bit test for the other"
  								[objectRepresentation genJumpNotSmallInteger: (rcvrIsInt ifTrue: [argReg] ifFalse: [rcvrReg])].
  	argIsInt
  		ifTrue: [self CmpCq: argInt R: rcvrReg]
  		ifFalse: [self CmpR: argReg R: rcvrReg].
  
  	"self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack; printSimStack: (self fixupAt: targetPC) mergeSimStack"
  	"If there are merges to be performed on the forward branches we have to execute
  	 the merge code only along the path requiring that merge, and exactly once."
  	needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
  	needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
  	"Cmp is weird/backwards so invert the comparison."
  	(needMergeToTarget and: [needMergeToContinue]) ifTrue:
  		[branchToTarget := self genConditionalBranch: (branchDescriptor isBranchTrue
  										ifTrue: [primDescriptor opcode]
  										ifFalse: [self inverseBranchFor: primDescriptor opcode])
  								operand: 0.
  		 self Jump: (self ensureFixupAt: postBranchPC).
  		 branchToTarget jmpTarget: self Label.
  		 self Jump: (self ensureFixupAt: targetPC)].
  	(needMergeToTarget and: [needMergeToContinue not]) ifTrue:
  		[self genConditionalBranch: (branchDescriptor isBranchFalse
  										ifTrue: [primDescriptor opcode]
  										ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ 			operand: (self ensureFixupAt: postBranchPC) asUnsignedInteger.
- 			operand: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
  		 self Jump: (self ensureFixupAt: targetPC)].
  	(needMergeToTarget not and: [needMergeToContinue]) ifTrue:
  		[self genConditionalBranch: (branchDescriptor isBranchTrue
  										ifTrue: [primDescriptor opcode]
  										ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ 			operand: (self ensureFixupAt: targetPC) asUnsignedInteger.
- 			operand: (self ensureNonMergeFixupAt: targetPC) asUnsignedInteger.
  		 self Jump: (self ensureFixupAt: postBranchPC)].
  	(needMergeToTarget or: [needMergeToContinue]) ifFalse:
  		[self genConditionalBranch: (branchDescriptor isBranchTrue
  										ifTrue: [primDescriptor opcode]
  										ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ 			operand: (self ensureFixupAt: targetPC) asUnsignedInteger.
+ 		 self Jump: (self ensureFixupAt: postBranchPC)].
- 			operand: (self ensureNonMergeFixupAt: targetPC) asUnsignedInteger.
- 		 self Jump: (self ensureNonMergeFixupAt: postBranchPC)].
  	jumpNotSmallInts jmpTarget: self Label.
  	self ssFlushTo: simStackPtr.
  	self deny: rcvrReg = Arg0Reg.
  	argIsInt
  		ifTrue: [self MoveCq: argInt R: Arg0Reg]
  		ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R: Arg0Reg]].
  	rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R: ReceiverResultReg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>swapCurrentRegistersInMask:accordingToRegisterOrderIn: (in category 'bytecode generator support') -----
  swapCurrentRegistersInMask: conflictingRegsMask accordingToRegisterOrderIn: mergeSimStack
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	"Swap liveRegisters in simStack entries according to their order in mergeSimStack so as to avoid
  	 overwriting live registers when merging simStack into mergeSimStack.  Consider the following two simStacks
  		target:		0: | rA | __ | rB | rC | rD | <- sp
  		current:	0: | __ | __ | rD | rA | rC | <- sp
  	 If we were to assign in a naive order, 0 through sp rA would be overwritten before its value in current[3] is written to rC,
  	 and rC would be overwritten before its value in current[4] is written to rD.  But if we swap the registers in current so that
  	 they respect the reverse ordering in target we can assign directly:
  		swap current[3] & current[4]
  					0: | __ | __ | rD | rC | rA | <- sp
  	 now do the assignment in the order target[0] := current[0],  target[1] := current[1], ...  target[4] := current[4],
  	 i.e. rA := current[0]; rB := rD; (rC := rC); (rD := rD).
  
  	 See https://hal.inria.fr/inria-00435844/file/article-hal.pdf
  		Florent Bouchez, Quentin Colombet, Alain Darte, Christophe Guillon, Fabrice Rastello.
  		Parallel Copy Motion. SCOPES, ACM, 2010, pp.0. <inria-00435844>
  
  	 So find any conflicts, and if there are any, swap registers in the simStack to resolve them."
  
  	"self printSimStack; printSimStack: mergeSimStack"
  
  	"Some processors have a SwapRR but not all.  Write one-size-fits-all code that moves things through TempReg."
  	| order n visitedMask ssEntry regA regB |
  	<var: 'order' declareC: 'sqInt order[8*BytesPerWord]'>
  	<var: 'ssEntry' type: #'SimStackEntry *'>
  	self cCode: [self me: order ms: 0 et: (self sizeof: order)]
  		inSmalltalk: [order := CArrayAccessor on: (Array new: 8*BytesPerWord withAll: 0)].
  	n := 0.
  	visitedMask := conflictingRegsMask.
  	0 to: methodOrBlockNumTemps - 1 do:
  		[:i|
  		 ssEntry := self simStack: mergeSimStack at: i.
  		(ssEntry registerMaskOrNone anyMask: visitedMask) ifTrue:
  			[order at: ssEntry registerOrNone put: (n := n + 1).
  			 visitedMask := visitedMask - ssEntry registerMaskOrNone]].
+ 	self assert: n >= 1.
+ 	n <= 2 ifTrue: "simple case; here to show me what I have to do in addition to the sort"
- 	self assert: n > 1.
- 	n = 2 ifTrue: "simple case; here to show me what I have to do in addition to the sort"
  		[regA := conflictingRegsMask highBit - 1.
  		 regB := (conflictingRegsMask - (1 << regA)) highBit - 1.
+ 		 self SwapR: regA R: regB Scratch: TempReg.
+ 		 0 to: simStackPtr do:
- 		 self MoveR: regA R: TempReg.
- 		 self MoveR: regB R: regA.
- 		 self MoveR: TempReg R: regB.
- 		0 to: simStackPtr do:
  			[:i|
+ 			 ssEntry := self simStack: simStack at: i.
+ 			 (ssEntry registerMaskOrNone anyMask: conflictingRegsMask) ifTrue:
- 			 ssEntry := self simStackAt: i.
- 			(ssEntry registerMaskOrNone anyMask: conflictingRegsMask) ifTrue:
  				[| reg |
  				 reg := ssEntry registerOrNone = regA ifTrue: [regB] ifFalse: [regA].
  				 ssEntry type = SSRegister ifTrue:
  					[ssEntry register: reg].
  				 ssEntry liveRegister: reg]].
  		 ^self].
  
  	self halt!



More information about the Vm-dev mailing list