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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 23 08:23:44 UTC 2015


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

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

Name: VMMaker.oscog-cb.1243
Author: cb
Time: 23 April 2015, 10:22:23.414 am
UUID: 783d50c8-1cf1-4b51-acf9-98aab1d6e486
Ancestors: VMMaker.oscog-eem.1242

Removed a ssAllocateRequiredReg which was not needed.

Basically refactored:

| constVal |
constVal := self ssTop maybeConstant.
	(self ssTop type = SSConstant
	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not])
	
to:

(objectRepresentation isUnannotatableConstant: self ssTop)

so I can understand the methods and see if I can change them with better register allocation. I am interested especially in genStorePop: popBoolean LiteralVariable: litVarIndex which has the flag:

	self flag: 'with better register allocation this wouldn''t need a frame.  e.g. use SendNumArgs instead of ReceiverResultReg'.

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

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 nExts
  	  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: [ ^ 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])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"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].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	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). "Use this as the count reg, can't conflict with the registers for the arg and the receiver"
- 	self ssAllocateRequiredReg: counterReg. "Use this as the count reg."
  	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: objectMemory wordSize = CounterBytes.
  	self MoveAw: counterAddress R: counterReg.
  	self SubCq: 16r10000 R: counterReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
  	self MoveR: counterReg Aw: counterAddress. "write back"
  
  	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 SubCq: 1 R: counterReg. "Count untaken"
  	self MoveR: counterReg Aw: counterAddress. "write back"
  	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: StackToRegisterMappingCogit>>genFramelessStorePop:ReceiverVariable: (in category 'bytecode generator support') -----
  genFramelessStorePop: popBoolean ReceiverVariable: slotIndex
  	<inline: false>
+ 	| topReg valueReg |
- 	| topReg valueReg constVal |
  	self assert: needsFrame not.
  	self ssFlushUpThroughReceiverVariable: slotIndex.
  	"Avoid store check for immediate values"
+ 	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
- 	constVal := self ssTop maybeConstant.
- 	(self ssTop type = SSConstant
- 	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not]) ifTrue:
  		[self ensureReceiverResultRegContainsSelf.
  		 self ssStorePop: popBoolean toPreferredReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[backEnd saveAndRestoreLinkRegAround:
  				[self CallRT: ceTraceStoreTrampoline]].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: slotIndex
  			destReg: ReceiverResultReg].
  	(topReg := self ssTop registerOrNil) isNil ifTrue:
  		[topReg := ClassReg].
  	valueReg := self ssStorePop: popBoolean toPreferredReg: topReg.
  	"Note that ReceiverResultReg remains live after ceStoreCheckTrampoline."
  	self ensureReceiverResultRegContainsSelf.
  	 traceStores > 0 ifTrue:
  		[self MoveR: valueReg R: TempReg.
  		 backEnd saveAndRestoreLinkRegAround:
  			[self CallRT: ceTraceStoreTrampoline]].
  	^objectRepresentation
  		genStoreSourceReg: valueReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: false!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:LiteralVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
+ 	| topReg valueReg association |
- 	| topReg valueReg association constVal |
  	self flag: 'with better register allocation this wouldn''t need a frame.  e.g. use SendNumArgs instead of ReceiverResultReg'.
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
  	"N.B.  No need to check the stack for references because we generate code for
  	 literal variable loads that stores the result in a register, deferring only the register push."
  	association := self getLiteral: litVarIndex.
- 	constVal := self ssTop maybeConstant.
  	"Avoid store check for immediate values"
+ 	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
- 	(self ssTop type = SSConstant
- 	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not]) ifTrue:
  		[self ssAllocateRequiredReg: ReceiverResultReg.
  		self genMoveConstant: association R: ReceiverResultReg.
  		 objectRepresentation
  			genEnsureObjInRegNotForwarded: ReceiverResultReg
  			scratchReg: TempReg.
  		 self ssStorePop: popBoolean toPreferredReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[self CallRT: ceTraceStoreTrampoline].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: ValueIndex
  			destReg: ReceiverResultReg].
  	((topReg := self ssTop registerOrNil) isNil
  	 or: [topReg = ReceiverResultReg]) ifTrue:
  		[topReg := ClassReg].
  	self ssPop: 1.
  	self ssAllocateCallReg: topReg. "for the ceStoreCheck call in genStoreSourceReg:... below"
  	self ssPush: 1.
  	valueReg := self ssStorePop: popBoolean toPreferredReg: topReg.
  	valueReg = ReceiverResultReg ifTrue:
  		[self MoveR: valueReg R: topReg].
  	self ssAllocateCallReg: ReceiverResultReg.
  	self annotate: (self MoveCw: association R: ReceiverResultReg) objRef: association.
  	objectRepresentation genEnsureObjInRegNotForwarded: ReceiverResultReg scratchReg: TempReg.
  	traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: ValueIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:ReceiverVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean ReceiverVariable: slotIndex
  	<inline: false>
+ 	| topReg valueReg |
- 	| topReg valueReg constVal |
  	needsFrame ifFalse:
  		[^self genFramelessStorePop: popBoolean ReceiverVariable: slotIndex].
  	self ssFlushUpThroughReceiverVariable: slotIndex.
  	"Avoid store check for immediate values"
+ 	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
- 	constVal := self ssTop maybeConstant.
- 	(self ssTop type = SSConstant
- 	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not]) ifTrue:
  		[self ensureReceiverResultRegContainsSelf.
  		 self ssStorePop: popBoolean toPreferredReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[self CallRT: ceTraceStoreTrampoline].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: slotIndex
  			destReg: ReceiverResultReg].
  	((topReg := self ssTop registerOrNil) isNil
  	 or: [topReg = ReceiverResultReg]) ifTrue:
  		[topReg := ClassReg].
  	self ssPop: 1.
  	self ssAllocateCallReg: topReg. "for the ceStoreCheck call in genStoreSourceReg:... below"
  	self ssPush: 1.
  	valueReg := self ssStorePop: popBoolean toPreferredReg: topReg.
  	valueReg = ReceiverResultReg ifTrue:
  		[self MoveR: valueReg R: topReg].
  	"Note that ReceiverResultReg remains live after ceStoreCheckTrampoline."
  	self ensureReceiverResultRegContainsSelf.
  	 traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:RemoteTemp:At: (in category 'bytecode generator support') -----
  genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex
  	<inline: false>
+ 	| topReg valueReg topSpilled |
- 	| topReg valueReg constVal topSpilled |
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
  	"N.B.  No need to check the stack for references because we generate code for
  	 remote temp loads that stores the result in a register, deferring only the register push."
  	"Avoid store check for immediate values"
+ 	(objectRepresentation isUnannotatableConstant: self ssTop) ifTrue:
- 	constVal := self ssTop maybeConstant.
- 	(self ssTop type = SSConstant
- 	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not]) ifTrue:
  		[self ssAllocateRequiredReg: ReceiverResultReg.
  		 self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg.
  		 self ssStorePop: popBoolean toPreferredReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[self CallRT: ceTraceStoreTrampoline].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: slotIndex
  			destReg: ReceiverResultReg].
  	((topReg := self ssTop registerOrNil) isNil
  	 or: [topReg = ReceiverResultReg]) ifTrue:
  		[topReg := ClassReg].
  	self ssPop: 1.
  	"for the ceStoreCheck call in genStoreSourceReg:... below"
  	self ssAllocateCallReg: topReg and: ReceiverResultReg.
  	self ssPush: 1.
  	topSpilled := self ssTop spilled.
  	valueReg := self ssStorePop: (popBoolean or: [topSpilled]) toPreferredReg: topReg.
  	valueReg = ReceiverResultReg ifTrue:
  		[self MoveR: valueReg R: topReg].
  	popBoolean ifFalse:
  		[topSpilled ifFalse: [self ssPop: 1].
  		 self ssPushRegister: topReg].
  	self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg.
  	 traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssStorePop:toPreferredReg: (in category 'simulation stack') -----
  ssStorePop: popBoolean toPreferredReg: preferredReg
  	"Store or pop the top simulated stack entry to a register.
  	 Pop to preferredReg if the entry is not itself a register.
  	 Answer the actual register the result ends up in."
  	| actualReg |
  	actualReg := preferredReg.
  	popBoolean
+ 		ifTrue: [(self ssTop type = SSRegister "and: [self ssTop spilled not]")
+ 					ifTrue: [self assert: self ssTop spilled not.
+ 							self assert: self ssTop annotateUse not.
- 		ifTrue: [(self ssTop type = SSRegister and: [self ssTop spilled not])
- 					ifTrue: [self assert: self ssTop annotateUse not.
  							actualReg := self ssTop register]
  					ifFalse: [self ssTop popToReg: preferredReg].
  				self ssPop: 1]
  		ifFalse: [self ssTop type = SSRegister
  					ifTrue: [self assert: self ssTop annotateUse not.
  							actualReg := self ssTop register]
  					ifFalse: [self ssTop storeToReg: preferredReg]].
  	^actualReg!



More information about the Vm-dev mailing list