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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 28 11:02:49 UTC 2015


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

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

Name: VMMaker.oscog-cb.1267
Author: cb
Time: 28 April 2015, 1:00:54.291 pm
UUID: d6fac431-cfba-44bc-9590-d031f970feda
Ancestors: VMMaker.oscog-cb.1266

Find a workaround to compile genSpecialSelectorComparison without slang generating incorrect code for the macro replacement of super.

Added many types to remove C compiler warnings.

I also added temporarily 
	<returnTypeC: #sqInt> in getJumpTargetPCAt: to solve a conflict between ARM and IA 32 back end until Eliot or Tim tells me a better solution.

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

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>allImmediate:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	| jmpImmediate |
  	< inline: true>	
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	self assert: immediateMask = objectMemory tagMask.
  	cogit MoveR: reg R: TempReg.
  	jmpImmediate := self genJumpNotImmediateInScratchReg: TempReg.
  	jmpImmediate jmpTarget: targetFixUp.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
  branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
  	| jmpImmediate|
  	<inline: true>
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	cogit MoveR: reg R: TempReg.
  	classIndex = objectMemory smallIntegerTag ifTrue:
  		[jmpImmediate := self genJumpNotSmallIntegerInScratchReg: TempReg].
  	classIndex = objectMemory characterTag ifTrue:
  		[jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
  	jmpImmediate jmpTarget: targetFixUp!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>allImmediate:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	| incorrectTag tag1 tag2 |
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
- 	< inline: true>		
  	cogit MoveR: reg R: TempReg.
  	(self genJumpNotImmediateInScratchReg: TempReg) jmpTarget: targetFixUp. 
  	immediateMask = objectMemory tagMask ifFalse: 
  		[ "TempReg holds the rcvr tag"
  		"In this case one immediate tag out of the three is not present in arrayObj. 
  		We look for it, and generate a jump to the fixup if the rcvr tag matches"
  		tag1 := objectMemory classTagForClass: (objectMemory fetchPointer: 0 ofObject: arrayObj).
  		tag2 := objectMemory classTagForClass: (objectMemory fetchPointer: 1 ofObject: arrayObj).
  		incorrectTag :=  self fetchImmediateTagOtherThanTag1: tag1 tag2: tag2.
  		cogit CmpCq: incorrectTag R: TempReg.
  		cogit JumpZero: targetFixUp ].!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>branchIf:notInstanceOfBehavior:target: (in category 'sista support') -----
  branchIf: reg notInstanceOfBehavior: classObj target: targetFixUp
  	"Generate a branch if reg is an instance of classObj, otherwise fall-
  	 through. Cannot change the value of reg (may be used afterwards)."
  	| classIndex |
  	<inline: true>
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	classIndex := objectMemory classTagForClass: classObj.
  	(objectMemory isImmediateClass: classObj)
  		ifTrue:
  			[self branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp ]
  		ifFalse:
  			[cogit MoveR: reg R: TempReg.
  			(self genJumpImmediateInScratchReg: TempReg) jmpTarget: targetFixUp.
  			 self genGetClassIndexOfNonImm: reg into: TempReg.
  			 self genCmpClassIndex: classIndex R: TempReg.
  			 cogit JumpNonZero: targetFixUp ].
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	"Generate a branch if reg is an instance of any of the classes in arrayObj,
  	 otherwise fall-through. reg should not be edited."
  	
  	| allImmediate noneImmediate immediateMask numNonImmediates classObj |
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
- 	<inline: true>
  	
  	"let me tell you all about it, let me falsify"
  	allImmediate := true. noneImmediate := true. immediateMask := 0. numNonImmediates := 0.
  	0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  		[:i|
  		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  		 (objectMemory isImmediateClass: classObj)
  			ifTrue:
  				[noneImmediate := false.
  				 immediateMask := immediateMask + (objectMemory classTagForClass: classObj)]
  			ifFalse:
  				[allImmediate := false.
  				 numNonImmediates := numNonImmediates + 1]].
  
  	noneImmediate ifTrue: [ ^ self noneImmediateBranchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ].
  
  	allImmediate ifTrue: [ ^ self allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ].
  
  	^ self mixed: numNonImmediates branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:ifForwarder:ifNotForwarder: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch ifForwarder: fwdJumpTarget ifNotForwarder: nonFwdJumpTargetOrZero
  	"Make sure that the oop in reg is not forwarded.  
  	 Use the fact that isForwardedObjectClassIndexPun is a power of two to save an instruction."
  	| skip ok finished |
  	<inline: true>
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #skip type: #'AbstractInstruction *'>
  	<var: #finished type: #'AbstractInstruction *'>
  	self assert: reg ~= scratch.
  	cogit MoveR: reg R: scratch.
  	skip := self genJumpImmediateInScratchReg: scratch.
  	"notionally
  		self genGetClassIndexOfNonImm: reg into: scratch.
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  	 but the following is an instruction shorter:"
  	cogit MoveMw: 0 r: reg R: scratch.
  	cogit
  		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  		R: scratch.
  	ok := cogit JumpNonZero: 0.
  	self genLoadSlot: 0 sourceReg: reg destReg: reg.
  	cogit Jump: fwdJumpTarget.
  	finished := nonFwdJumpTargetOrZero = 0
  		ifTrue: [ cogit Label ]
+ 		ifFalse: [ self cCoerceSimple: nonFwdJumpTargetOrZero to: #'AbstractInstruction *' ].
- 		ifFalse: [ nonFwdJumpTargetOrZero ].
  	skip jmpTarget: (ok jmpTarget: finished).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:jumpBackTo: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch jumpBackTo: instruction
+ 	<var: #instruction type: #'AbstractInstruction *'>
- 	<inline: true>
  	^ self 
  		genEnsureOopInRegNotForwarded: reg 
  		scratchReg: scratch 
  		ifForwarder: instruction
  		ifNotForwarder: 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>mixed:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  mixed: numNonImmediates branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	| jmpImmediate jumps label numCases classObj index |
+ 	<var: #label type: #'AbstractInstruction *'>
+ 	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jumps type: #'AbstractInstruction **'>
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	numCases := objectMemory numSlotsOf: arrayObj.
  	cogit MoveR: reg R: TempReg.
  	jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  	
  	"Rcvr is non immediate"
  	jumps := self alloca: numNonImmediates type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
  	self genGetClassIndexOfNonImm: reg into: TempReg.
  	index := 0.
  	0 to: numCases - 1 do:
  		[:i|
  			classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			(objectMemory isImmediateClass: classObj) ifFalse: [
  				self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  				jumps at: index put: (cogit JumpZero: 0).
  				index := index + 1 ] ].
  	cogit Jump: targetFixUp.
  	
  	"Rcvr is immediate"
  	jmpImmediate jmpTarget: cogit Label.
  	numCases - numNonImmediates "num Immediates allowed"
  		caseOf:
  		{[ 1 ] -> [ "1 immediate allowed. jump to targetFixUp if the rcvr is not this immediate"
  			0 to: numCases - 1 do:
  				[ :j |
  				classObj := objectMemory fetchPointer: j ofObject: arrayObj.
  				(objectMemory isImmediateClass: classObj) ifTrue: [
  					self branchIf: reg hasNotImmediateTag: (objectMemory classTagForClass: classObj) target: targetFixUp ] ] ] .
  		[ 2 ] -> [ "2 immediates allowed. On 32 bits nothing to do, all immediate are allowed, on 64 bits generates the jump to fixup for the third tag"
  				self branch2CasesIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ] .
  		[ 3 ] -> [ "nothing to do, all immediates are allowed." ] }.
  	
  	label := self Label.
  	0 to: numNonImmediates - 1 do: [:i |
  		(jumps at: i) jmpTarget: label ].
  	
  	^ 0
  		!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>noneImmediateBranchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  noneImmediateBranchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	"All classes in arrayObj are not immediate"
  	| label numJumps jumps classObj |
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
+ 	<var: #label type: #'AbstractInstruction *'>
- 	<inline: true>
  	<var: #jumps type: #'AbstractInstruction **'>
  	cogit MoveR: reg R: TempReg.
  	jumps := self alloca: (objectMemory numSlotsOf: arrayObj) type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
  	(self genJumpImmediateInScratchReg: TempReg) jmpTarget: targetFixUp.
  	self genGetClassIndexOfNonImm: reg into: TempReg.
  	0 to: (numJumps := objectMemory numSlotsOf: arrayObj) - 1 do:
  		[:i|
  		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  		 self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  		jumps at: i put: (cogit JumpZero: 0) ].
  	cogit Jump: targetFixUp.
  	label := self Label.
  	0 to: numJumps do: [:i |
  		(jumps at: i) jmpTarget: label ].
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') -----
  genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
  	"SistaV1: *	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
  								
  	| reg literal distance targetFixUp |
  	
  	"We loose the information of in which register is stack top 
  	when jitting the branch target so we need to flush everything. 
  	We could use a fixed register here...."
  	reg := self allocateRegForStackEntryAt: 0.
  	self ssTop popToReg: reg.
  	self ssFlushTo: simStackPtr. "flushed but the value is still in reg"
  	
  	literal := self getLiteral: (extA * 256 + byte1).
  	extA := 0.
  	distance := extB * 256 + byte2.
  	extB := 0.
  	
+ 	targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'..
- 	targetFixUp := (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) asUnsignedInteger.
  		
  	(objectMemory isArrayNonImm: literal)
  		ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp]
  		ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp].
  						
  	self genPopStackBytecode.
  	
  	^0!

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
  	  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: [ ^ self genUnoptimizedSpecialSelectorComparison ].
- 	(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 ].
  	
  	"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].
  
  	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).
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  
  	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 genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	
  	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
  	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #label type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [ ^ super genSpecialSelectorEqualsEquals ].
  
  	regMask := 0.
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	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 ].
  		
  	argReg ifNotNil: [ regMask := self registerMaskFor: argReg ].
  	rcvrReg ifNotNil: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
  	
  	"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].
  	
  	counterReg := self allocateRegNotConflictingWith: regMask.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  	
  	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 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. 
  	
  	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 genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	^ 0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genUnconditionalTrapBytecode (in category 'bytecode generators') -----
  genUnconditionalTrapBytecode
  	"SistaV1: *	217		Trap"
+ 	self ssFlushTo: simStackPtr.
- 	"Use ssFlushNoUpdateTo: so we continue compiling as if the stack had not been flushed . 
- 	(typically, this kind of trap is in a branch)  
- 	Control does not return after the ceClassTrapTrampoline call."
- 	self ssFlushNoUpdateTo: simStackPtr.
  	self CallRT: ceTrapTrampoline.
  	self annotateBytecode: self Label.
  	^0!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>genUnoptimizedSpecialSelectorComparison (in category 'bytecode generators') -----
+ genUnoptimizedSpecialSelectorComparison
+ 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
+ 	^ super genSpecialSelectorComparison!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>getJumpTargetPCAt: (in category 'method introspection') -----
  getJumpTargetPCAt: pc
  	<api>
+ 	<returnTypeC: #sqInt>
  	^backEnd jumpTargetPCAt: pc!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>ssFlushNoUpdateTo: (in category 'simulation stack') -----
- ssFlushNoUpdateTo: index
- 	"This version of ssFlushTo: does /not/ update the simulation stack; it merely generates the spill code.
- 	 It is used to spill all values to the stack on a rare failing branch (the class trap) when we don't want to
- 	 flush the stack on the main path and hence mustn't update the simulation stack if there is no spill."
- 	<var: 'copiedEntry' type: #CogSimStackEntry>
- 	self assert: needsFrame.
- 	methodOrBlockNumTemps to: simSpillBase - 1 do:
- 		[:i| self assert: (self simStackAt: i) spilled].
- 	simSpillBase <= index ifTrue:
- 		[(simSpillBase max: 0) to: index do:
- 			[:i| | copiedEntry |
- 			copiedEntry := self cCode: [simStack at: index]
- 								inSmalltalk: [(simStack at: index) copy].
- 			copiedEntry
- 				ensureSpilledAt: (self frameOffsetOfTemporary: i)
- 				from: FPReg]]!

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: #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 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) asUnsignedInteger.
- 			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
  			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  		ifFalse: "branchDescriptor is branchFalse"
+ 			[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
- 			[ 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 ].
  		
  	"Not reached, execution flow have jumped to fixup"
  	
  	^0!



More information about the Vm-dev mailing list