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

commits at source.squeak.org commits at source.squeak.org
Sat Apr 25 13:41:27 UTC 2015


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

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

Name: VMMaker.oscog-cb.1256
Author: cb
Time: 25 April 2015, 3:39:56.845 pm
UUID: 3f901fb1-b9ab-4c74-8a9a-b9483fbd9830
Ancestors: VMMaker.oscog-cb.1255

After spending yet another hour on the SistaCogit to figure out what is not working, I realized that I could simplify a lot the #== code generation code in StackToRegisterMappingCogit. The code is now simpler to read. The only difference in the generated machine code is that 2 branches now jump to the instruction after a Nop instead of jumping directly to the Nop, but though I enjoy stepping over Nops while simulating machine code, it does not change anything.

=============== Diff against VMMaker.oscog-cb.1255 ===============

Item was removed:
- ----- 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 changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
  	| nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
  	unforwardArg  rcvrReg postBranchPC label fixup |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	
  	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 genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
  	
  	"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 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) 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: 
+ 			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
+ 			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
+ 		ifFalse: "branchDescriptor is branchFalse"
+ 			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
+ 			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ].
+ 	"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 ].
- 	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 ].
- 	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].
  	^0!



More information about the Vm-dev mailing list