[Vm-dev] VM Maker: VMMaker.oscog-mt.3259.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Oct 27 13:45:08 UTC 2022


Marcel Taeumel uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-mt.3259.mcz

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

Name: VMMaker.oscog-mt.3259
Author: mt
Time: 27 October 2022, 3:45:00.324984 pm
UUID: bfaad400-d7ee-f74e-99f6-853fc646b4f3
Ancestors: VMMaker.oscog-mt.3258

Fixes "-Wint-conversion" error for SistaVM builds.

=============== Diff against VMMaker.oscog-mt.3258 ===============

Item was changed:
  ----- Method: SistaCogit>>genByteEqualsInlinePrimitiveResult:returnReg: (in category 'inline primitive generators') -----
  genByteEqualsInlinePrimitiveResult: jmp returnReg: reg
  	"Byte equal is falling through if the result is true, or jumping using jmp if the result is false.
  	 The method is required to set the jump target of jmp.
  	 We look ahead for a branch and pipeline the jumps if possible..
  	 ReturnReg is used only if not followed immediately by a branch."
  	| branchDescriptor nextPC postBranchPC targetBytecodePC localJump canElide |
+ 	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #localJump type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	"Case 1 - not followed by a branch"
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])
  		ifFalse: 
  			[self genMoveTrueR: reg.
  			 localJump := self Jump: 0.
  			 jmp jmpTarget: (self genMoveFalseR: reg).
  			 localJump jmpTarget: self Label.
  			 self ssPushRegister: reg.
  			^ 0].
  
  	"Case 2 - followed by a branch"
  	(self fixupAt: nextPC) notAFixup
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC.
  			 self ensureFixupAt: postBranchPC ]
  		ifFalse:
  			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  	"We can only elide the jump if the pc after nextPC is the same as postBranchPC.
  	 Branch following means it may not be."
  	self nextDescriptorExtensionsAndNextPCInto:
  		[:iguana1 :iguana2 :iguana3 :followingPC| nextPC := followingPC].
  	canElide := deadCode and: [nextPC = postBranchPC].
  	 branchDescriptor isBranchTrue
  		ifTrue: 
  			[ self Jump: (self ensureNonMergeFixupAt: targetBytecodePC).
  			  canElide 
  					ifFalse: [ jmp jmpTarget: (self ensureNonMergeFixupAt: postBranchPC) ]
  					ifTrue: [ jmp jmpTarget: self Label ] ]
  		ifFalse: [ canElide ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC).
  				 jmp jmpTarget: (self ensureNonMergeFixupAt: targetBytecodePC) ] ].
  	^0!

Item was changed:
  ----- Method: SistaCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
  	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask
  	  rcvrConstant argConstant |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpEqual type: #'AbstractInstruction *'>
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  
  	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
  		[^super genForwardersInlinedIdenticalOrNotIf: orNot].
  
  	regMask := 0.
  	
  	unforwardRcvr := (self ssValue: 1) mayBeAForwarder.
  	unforwardArg := self ssTop mayBeAForwarder.
  	(unforwardRcvr not and: [unforwardArg not])
  		ifTrue: [unforwardRcvr := true.
  				"TODO: use genVanilla with profiling counters (not implemented).
  				^self genVanillaInlinedIdenticalOrNotIf: orNot"].
  	self assert: (unforwardArg or: [unforwardRcvr]).
  	"We use reg for non annotable constants to avoid duplicating objRef."
  	rcvrConstant := objectRepresentation isUnannotatableConstant: (self ssValue: 1).
  	argConstant := objectRepresentation isUnannotatableConstant: self ssTop.
  	
  	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)."
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: argConstant not 
  		rcvrNeedsReg: rcvrConstant not 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^ self 
  			genIdenticalNoBranchArgIsConstant: argConstant
  			rcvrIsConstant: rcvrConstant
  			argReg: argReg 
  			rcvrReg: rcvrReg 
  			orNotIf: orNot].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
  	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
  	
  	regMask := argReg = NoReg
  					ifTrue: [self registerMaskFor: rcvrReg]
  					ifFalse:
  						[rcvrReg = NoReg
  							ifTrue: [self registerMaskFor: argReg]
  							ifFalse: [self registerMaskFor: rcvrReg and: argReg]].
  	counterReg := self allocateRegNotConflictingWith: regMask.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  
  	self genCmpArgIsConstant: argConstant rcvrIsConstant: rcvrConstant argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  	
  	orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
  		ifFalse:
+ 			[ fixup := self ensureNonMergeFixupAt: postBranchPC.
+ 			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) ]
- 			[ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
- 			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ]
  		ifTrue:
+ 			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC.
+ 			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC)  ].
- 			[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
- 			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ].
  	
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	self Jump: fixup.
  	
  	countTripped jmpTarget: self Label.
  	
  	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
  	self ssPop: -2. 
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2. 
  	
  	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
  	We therefore directly assign the result to TempReg to save one move instruction"
  	jumpEqual := orNot ifFalse: [self JumpZero: 0] ifTrue: [self JumpNonZero: 0].
  	self genMoveFalseR: TempReg.
  	jumpNotEqual := self Jump: 0.
  	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
  	jumpNotEqual jmpTarget: self Label.
  	self ssPushRegister: TempReg.
  	
  	(self fixupAt: nextPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
  	
  	^ 0!



More information about the Vm-dev mailing list