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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 7 02:09:33 UTC 2016


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

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

Name: VMMaker.oscog-eem.2028
Author: eem
Time: 6 December 2016, 6:08:48.407545 pm
UUID: a66fd6b5-4adb-4770-83b4-a29622cc4314
Ancestors: VMMaker.oscog-eem.2027

RegisterAllocatingCogit:

No longer flush on conditional branch; instead leave it up to the merge logic to harmonise the stacks on join.

Consequently, fix the order of generating fixups and pushing the dummyValue when no deadCode in genSpecialSelectorEqalsEquals:.  This didn't matter with the StackToRegisterMappingCogit but in the RegisterAllocatingCogit now that teh stack is not flushed on conditional branch, it is critical; the fixup must be established before the dummyValue is pushed.

Also consequently make mergeCurrentSimStackWith:/reconcileForwardsWith: more intelligent, able to merge when the target has spills and the current does not.

At least mark that mustBeBoolean: will switch to an interpreted frame (yet to be implementd).

Fix a slip in genSubConstant:R: which always used TempReg and didn't use its argument.

Fix a slip in temp name printing for sim stack printing.

Use = to compare objectmemory falseObject and objectMemory trueObject swith SSConstant entry constants.  These are integeger oops, not objects, and so integral comparison shoudl be used.

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

Item was added:
+ ----- Method: CoInterpreter>>ceSendMustBeBooleanInterpreting: (in category 'trampolines') -----
+ ceSendMustBeBooleanInterpreting: anObject
+ 	"For RegisterAllocatingCogit we want the address following a conditional branch not to be reachable, so we
+ 	 don't have to generate code to reload registers.  Instead simply convert to an interpreter frame."
+ 	<api>
+ 	self shouldBeImplemented.
+ 	instructionPointer := self popStack.
+ 	self push: anObject.
+ 	self push: instructionPointer.
+ 	^self
+ 		ceSendAbort: (objectMemory splObj: SelectorMustBeBoolean)
+ 		to: anObject
+ 		numArgs: 0!

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: #'targetEntry *'>
  	| 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].
- 		[self assert: (self isSameEntryAs: targetEntry).
  		 ^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 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."
  	^targetEntry type = SSBaseOffset
  	  and: [targetEntry register = FPReg
  	  and: [(self isSameEntryAs: targetEntry) not]]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>directionForMergeWith: (in category 'bytecode generator support') -----
+ directionForMergeWith: mergeSimStack
+ 	"Answer > 0 if values must be pushed from simStack to merge with mergeSimStack, otherwise < 0 (the default)."
+ 	<var: #mergeSimStack type: #'SimStackEntry *'>
+ 	<inline: true>
+ 	simStackPtr to: methodOrBlockNumArgs by: -1 do:
+ 		[:i|
+ 		 (self simStack: mergeSimStack at: i) spilled ifTrue:
+ 			[(self simStack: simStack at: i) spilled ifFalse:
+ 				[^1]]].
+ 	^-1!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	| nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
  	unforwardArg  rcvrReg postBranchPC label fixup |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #label type: #'AbstractInstruction *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := 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].
  	
  	label := self Label.
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
  	(self fixupAt: nextPC - initialPC) notAFixup
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
+ 			[self deny: deadCode]. "push dummy value below"
- 			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  
  	self assert: (unforwardArg or: [unforwardRcvr]).
  	"We could use (branchDescriptor isBranchTrue xor: orNot) to simplify this."
  	orNot 
  		ifFalse: [branchDescriptor isBranchTrue
  					ifTrue: 
  						[ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
  						self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  					ifFalse: "branchDescriptor is branchFalse"
  						[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  						self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]]
  		ifTrue: [branchDescriptor isBranchTrue
  					ifFalse: "branchDescriptor is branchFalse"
  						[ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
  						self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  					ifTrue:
  						[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  						self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]].
+ 
+ 	deadCode ifFalse:
+ 		[self ssPushConstant: objectMemory trueObject]. "dummy value"
- 		
  	"The forwarders checks need to jump back to the comparison (label) if a forwarder is found, else 
  	jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
  	unforwardArg ifTrue: 
  		[ unforwardRcvr
  			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
  			ifFalse: [ objectRepresentation 
  				genEnsureOopInRegNotForwarded: argReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ] ].
  	unforwardRcvr ifTrue: 
  		[ objectRepresentation 
  			genEnsureOopInRegNotForwarded: rcvrReg 
  			scratchReg: TempReg 
  			ifForwarder: label
  			ifNotForwarder: fixup ].
  		
  	"Not reached, execution flow have jumped to fixup"
  	
  	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
+ genJumpIf: boolean to: targetBytecodePC
+ 	<inline: false>
+ 	| desc reg fixup ok |
+ 	<var: #desc type: #'CogSimStackEntry *'>
+ 	<var: #fixup type: #'BytecodeFixup *'>
+ 	<var: #ok type: #'AbstractInstruction *'>
+ 	desc := self ssTop.
+ 	self ssPop: 1.
+ 	(desc type == SSConstant
+ 	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
+ 		["Must arrange there's a fixup at the target whether it is jumped to or
+ 		  not so that the simStackPtr can be kept correct."
+ 		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
+ 		 "Must annotate the bytecode for correct pc mapping."
+ 		 self annotateBytecode: (desc constant = boolean
+ 									ifTrue: [self Jump: fixup]
+ 									ifFalse: [self prevInstIsPCAnnotated
+ 												ifTrue: [self Nop]
+ 												ifFalse: [self Label]]).
+ 		 extA := 0.
+ 		 ^0].
+ 	"try and use the top entry's register if anty, 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.
+ 	self genSubConstant: boolean R: reg.
+ 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
+ 	
+ 	self extASpecifiesNoMustBeBoolean ifTrue: 
+ 		[extA := 0. 
+ 		 self annotateBytecode: self lastOpcode.
+ 		 ^0].
+ 	extA := 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 CallRT: (boolean = objectMemory falseObject
+ 					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
+ 					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
+ 	"NOTREACHED"
+ 	ok jmpTarget: (self annotateBytecode: self Label).
+ 	self restoreSimStackFromScratch.
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
+ genMustBeBooleanTrampolineFor: boolean called: trampolineName
+ 	<var: #trampolineName type: #'char *'>
+ 	"For RegisterAllocatingCogit we want the address following a conditional branch not to be reachable, so we
+ 	 don't have to generate code to reload registers.  Instead simply convert to an interpreter frame."
+ 	<inline: false>
+ 	self zeroOpcodeIndex.
+ 	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
+ 	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
+ 	self AddCq: boolean R: TempReg.
+ 	^self genTrampolineFor: #ceSendMustBeBooleanInterpreting:
+ 		called: trampolineName
+ 		numArgs: 1
+ 		arg: TempReg
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		regsToSave: self emptyRegisterMask
+ 		pushLinkReg: true
+ 		resultReg: NoReg
+ 		appendOpcodes: true!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>genVanillaInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
+ genVanillaInlinedIdenticalOrNotIf: orNot
+ 	| nextPC postBranchPC targetBytecodePC branchDescriptor
+ 	  rcvrReg argReg argIsConstant rcvrIsConstant  |
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ 	
+ 	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 to use correct machine opcodes.
+ 	 However annotable constants can't be resolved statically, hence we need to careful."
+ 	rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant].
+ 	
+ 	self 
+ 		allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not 
+ 		rcvrNeedsReg: rcvrIsConstant not 
+ 		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: argIsConstant 
+ 			rcvrIsConstant: rcvrIsConstant 
+ 			argReg: argReg 
+ 			rcvrReg: rcvrReg 
+ 			orNotIf: orNot].
+ 	
+ 	self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
+ 	self ssPop: 2.
+ 
+ 	"Further since there is a following conditional jump bytecode, define
+ 	 non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	(self fixupAt: nextPC - initialPC) notAFixup
+ 		ifTrue: "The next instruction is dead.  we can skip it."
+ 			[deadCode := true.
+ 		 	 self ensureFixupAt: targetBytecodePC - initialPC.
+ 			 self ensureFixupAt: postBranchPC - initialPC]
+ 		ifFalse:
+ 			[self deny: deadCode]. "push dummy value below"
+ 		
+ 	"We could simplify this with a xor:"
+ 	self genConditionalBranch: (orNot 
+ 						ifFalse: [branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero]]
+ 						ifTrue: [branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero]])
+ 		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ 
+ 	"If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else 
+ 	we need to jump over the code of the branch"
+ 	deadCode ifFalse:
+ 		[self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
+ 		 self ssPushConstant: objectMemory trueObject]. "dummy value"
+ 	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup
  	<var: #fixup type: #'BytecodeFixup *'>
+ 	| mergeSimStack direction currentEntry targetEntry |
- 	| mergeSimStack currentEntry targetEntry |
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	"At a merge point the cogit expects the stack to be in the same state as mergeSimStack.
  	 mergeSimStack is the state as of some jump forward to this point.  So make simStack agree
  	 with mergeSimStack (it is, um, problematic to plant code at the jump).
  	 Values may have to be assigned to registers.  Registers may have to be swapped.
  	 The state of optStatus must agree."
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<var: #currentEntry type: #'SimStackEntry *'>
  	<var: #duplicateEntry type: #'SimStackEntry *'>
  	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  	"Assignments amongst the registers must be made in order to avoid overwriting.
  	 If necessary exchange registers amongst simStack's entries to resolve any conflicts."
  	self resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack.
  	self assert: (self conflcitsResolvedBetweenSimStackAnd: mergeSimStack).
+ 	"Must determine if we will push or pop values.
+ 	 If pushing values must enumerate from bottom to top.
+ 	 If popping, must enumerate from top to bottom."
+ 	direction := self directionForMergeWith: mergeSimStack.
+ 	direction > 0
+ 		ifTrue:
+ 			[0 to: simStackPtr do:
+ 				[:i|
+ 				 currentEntry := self simStack: simStack at: i.
+ 				 targetEntry := self simStack: mergeSimStack at: i.
+ 				 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
+ 					[self assert: i >= methodOrBlockNumArgs.
+ 					 self deassignRegisterForTempVar: targetEntry in: mergeSimStack].
+ 				 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
+ 				 spilled ifFalse:
+ 					[simSpillBase := i - 1].
+ 				 simStack
+ 					at: i
+ 					put: (self
+ 							cCode: [mergeSimStack at: i]
+ 							inSmalltalk: [(mergeSimStack at: i) copy])"]]
+ 		ifFalse:
+ 			[simStackPtr to: 0 by: -1 do:
+ 				[:i|
+ 				 currentEntry := self simStack: simStack at: i.
+ 				 targetEntry := self simStack: mergeSimStack at: i.
+ 				 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
+ 					[self assert: i >= methodOrBlockNumArgs.
+ 					 self deassignRegisterForTempVar: targetEntry in: mergeSimStack].
+ 				 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
+ 				 spilled ifFalse:
+ 					[simSpillBase := i - 1].
+ 				 simStack
+ 					at: i
+ 					put: (self
+ 							cCode: [mergeSimStack at: i]
+ 							inSmalltalk: [(mergeSimStack at: i) copy])"]].
- 	simStackPtr to: 0 by: -1 do:
- 		[:i|
- 		 currentEntry := self simStack: simStack at: i.
- 		 targetEntry := self simStack: mergeSimStack at: i.
- 		 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
- 			[self assert: i >= methodOrBlockNumArgs.
- 			 self deassignRegisterForTempVar: targetEntry in: mergeSimStack].
- 		 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
- 		 spilled ifFalse:
- 			[simSpillBase := i - 1].
- 		 simStack
- 			at: i
- 			put: (self
- 					cCode: [mergeSimStack at: i]
- 					inSmalltalk: [(mergeSimStack at: i) copy])"].
  
  	"a.k.a. fixup isReceiverResultRegSelf: (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
  	optStatus isReceiverResultRegLive ifFalse:
  		[fixup isReceiverResultRegSelf: false]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>restoreSimStackFromScratch (in category 'bytecode generator support') -----
+ restoreSimStackFromScratch
+ 	<inline: true>
+ 	self cCode: [self mem: simStack cp: scratchSimStack y: self simStackSlots * (self sizeof: CogSimStackEntry)]
+ 		inSmalltalk: [0 to: simStackPtr do:
+ 						[:i|
+ 						simStack at: i put: (scratchSimStack at: i)]].
+ 	simSpillBase := scratchSpillBase.
+ 	optStatus := scratchOptStatus!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	"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."
  	| ok |
  	<var: #ok type: #'AbstractInstruction *'>
  	extA := 0.
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self PopR: TempReg.
  	self genSubConstant: boolean R: TempReg.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
+ 	self CallRT: (boolean = objectMemory falseObject
- 	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSubConstant:R: (in category 'constant support') -----
  genSubConstant: constant R: reg
  	"If the objectMemory allows it, generates a quick constant sub, else generates a word constant sub"
  	<inline: true>
  	^ (objectRepresentation shouldAnnotateObjectReference: constant)
+ 		ifTrue: [ self annotate: (self SubCw: constant R: reg) objRef: reg. ]
+ 		ifFalse: [ self SubCq: constant R: reg ]!
- 		ifTrue: [ self annotate: (self SubCw: constant R: TempReg) objRef: reg. ]
- 		ifFalse: [ self SubCq: constant R: TempReg ]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	| nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
  	unforwardArg  rcvrReg postBranchPC label fixup |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #label type: #'AbstractInstruction *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := 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].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	label := self Label.
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
  	(self fixupAt: nextPC - initialPC) notAFixup
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
+ 			[self deny: deadCode]. "push dummy value below"
- 			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  
  	self assert: (unforwardArg or: [unforwardRcvr]).
  	"We could use (branchDescriptor isBranchTrue xor: orNot) to simplify this."
  	orNot 
  		ifFalse: [branchDescriptor isBranchTrue
  					ifTrue: 
  						[ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
  						self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  					ifFalse: "branchDescriptor is branchFalse"
  						[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  						self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]]
  		ifTrue: [branchDescriptor isBranchTrue
  					ifFalse: "branchDescriptor is branchFalse"
  						[ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
  						self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  					ifTrue:
  						[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  						self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]].
+ 
+ 	deadCode ifFalse:
+ 		[self ssPushConstant: objectMemory trueObject]. "dummy value"
  		
  	"The forwarders checks need to jump back to the comparison (label) if a forwarder is found, else 
  	jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
  	unforwardArg ifTrue: 
  		[ unforwardRcvr
  			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
  			ifFalse: [ objectRepresentation 
  				genEnsureOopInRegNotForwarded: argReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ] ].
  	unforwardRcvr ifTrue: 
  		[ objectRepresentation 
  			genEnsureOopInRegNotForwarded: rcvrReg 
  			scratchReg: TempReg 
  			ifForwarder: label
  			ifNotForwarder: fixup ].
  		
  	"Not reached, execution flow have jumped to fixup"
  	
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	| desc fixup ok |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must arrange there's a fixup at the target whether it is jumped to or
  		  not so that the simStackPtr can be kept correct."
  		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self annotateBytecode: (desc constant = boolean
  									ifTrue: [self Jump: fixup]
  									ifFalse: [self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label]]).
  		 extA := 0.
  		 ^0].
  	desc popToReg: TempReg.
  	"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 genSubConstant: boolean R: TempReg.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	
  	self extASpecifiesNoMustBeBoolean ifTrue: 
  		[ extA := 0. 
  		self annotateBytecode: self lastOpcode.
  		^ 0].
  	extA := 0.
  	
+ .	self CmpCq: (boolean = objectMemory falseObject
- .	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
+ 	self CallRT: (boolean = objectMemory falseObject
- 	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genVanillaInlinedIdenticalOrNotIf: orNot
  	| nextPC postBranchPC targetBytecodePC branchDescriptor
  	  rcvrReg argReg argIsConstant rcvrIsConstant  |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	
  	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 to use correct machine opcodes.
  	 However annotable constants can't be resolved statically, hence we need to careful."
  	rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant].
  	
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not 
  		rcvrNeedsReg: rcvrIsConstant not 
  		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: argIsConstant 
  			rcvrIsConstant: rcvrIsConstant 
  			argReg: argReg 
  			rcvrReg: rcvrReg 
  			orNotIf: orNot].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
  	(self fixupAt: nextPC - initialPC) notAFixup
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
+ 			[self deny: deadCode]. "push dummy value below"
- 			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  		
  	"We could simplify this with a xor:"
  	self genConditionalBranch: (orNot 
  						ifFalse: [branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero]]
  						ifTrue: [branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero]])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  
  	"If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else 
  	we need to jump over the code of the branch"
+ 	deadCode ifFalse:
+ 		[self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
+ 		 self ssPushConstant: objectMemory trueObject]. "dummy value"
- 	deadCode ifFalse: [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>printSimStack:toDepth:spillBase:on: (in category 'simulation only') -----
  printSimStack: aSimStack toDepth: limit spillBase: spillBase on: aStream
  	<doNotGenerate>
  	| tempNamesOrNil width tabWidth |
  	aStream ensureCr.
  	limit < 0 ifTrue:
  		[^aStream nextPutAll: 'simStackEmpty'; cr; flush].
  	inBlock ~~ true ifTrue:
  		[(tempNamesOrNil := self class initializationOptions at: #tempNames ifAbsent: [#()]) isEmpty ifFalse:
  			[| tab longest |
  			 longest := tempNamesOrNil inject: '' into: [:m :t| m size >= t size ifTrue: [m] ifFalse: [t]].
  			 tabWidth := self widthInDefaultFontOf: (tab := String with: Character tab).
  			 width := self widthInDefaultFontOf: longest, tab.
  			 width <= ((self widthInDefaultFontOf: longest, (String with: Character space)) + 4) ifTrue:
  				[width := width + tabWidth]]].
  	0 to: limit do:
  		[:i|
+ 		width ifNotNil:
- 		tempNamesOrNil ifNotNil:
  			[self put: (tempNamesOrNil at: i + 1 ifAbsent: ['']) paddedTo: width tabWidth: tabWidth on: aStream].
  		aStream print: i.
  		i = spillBase
  			ifTrue: [aStream nextPutAll: ' sb'; tab]
  			ifFalse: [aStream tab; tab].
  		(aSimStack at: i) printStateOn: aStream.
  		aStream cr; flush]!



More information about the Vm-dev mailing list