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

commits at source.squeak.org commits at source.squeak.org
Fri Nov 25 20:28:00 UTC 2016


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

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

Name: VMMaker.oscog-eem.2004
Author: eem
Time: 25 November 2016, 12:27:17.318388 pm
UUID: 2611a673-7341-4feb-b642-20dd06d9ae87
Ancestors: VMMaker.oscog-cb.2003

RegisterAllocatingCogit:
Compile readStream>>#next correctly, i.e. compile the inlined + in "^collection at: (position := position + 1)" in the context of colleciton on the stack.  Also keep receiverResultRegLive.

Alas these changes cause IdentityDictionary>scanFor: to blow up again, sending \\ to the key.

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

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileWith: (in category 'compile abstract instructions') -----
  reconcileWith: simStackEntry
+ 	"Make the state of each simStackEntry, a stack entry along the non-inlined special selector path,
+ 	 the same as the corresponding simStackEntry along the inlined path (the receiver)."
  	<var: #simStackEntry type: #'SimStackEntry *'>
  	type = SSConstant ifTrue:
  		[cogit AddCw: BytesPerWord R: SPReg.
  		 ^self].
  	liveRegister ~= NoReg ifTrue:
  		[simStackEntry popToReg: liveRegister.
  		 ^self].
  	type = SSRegister ifTrue:
  		[simStackEntry popToReg: register.
  		 ^self].
  	self halt!

Item was changed:
  StackToRegisterMappingCogit subclass: #RegisterAllocatingCogit
+ 	instanceVariableNames: 'numFixups mergeSimStacksBase nextFixup scratchSimStack scratchSpillBase scratchOptStatus'
- 	instanceVariableNames: 'numFixups mergeSimStacksBase nextFixup scratchSimStack scratchSpillBase'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !RegisterAllocatingCogit commentStamp: 'cb 4/15/2016 14:58' prior: 0!
  RegisterAllocatingCogit is an optimizing code generator that is specialized in register allocation..
  
  On the contrary to StackToRegisterMappingCogit, RegisterAllocatingCogit keeps at each control flow merge point the state of the simulated stack to merge into and not only an integer fixup. Each branch and jump record the current state of the simulated stack, and each fixup is responsible for merging this state into the saved simulated stack.
  !

Item was changed:
  ----- Method: RegisterAllocatingCogit class>>declareCVarsIn: (in category 'C translation') -----
  declareCVarsIn: aCodeGen
+ 	aCodeGen
+ 		var: #scratchSimStack
+ 			type: #'CogSimStackEntry *';
+ 		var: #scratchOptStatus
+ 			type: #CogSSOptStatus!
- 	aCodeGen var: #scratchSimStack type: #'CogSimStackEntry *'!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>captureUnspilledSpillsForSpecialSelectorSend: (in category 'bytecode generator support') -----
+ captureUnspilledSpillsForSpecialSelectorSend: liveRegisterMask
+ 	"Since we're allocating values in registers we would like to keep those registers live on the inlined path
+ 	 and reload registers along the non-inlined send path.  But any values that would need to be spilled
+ 	 along the non-inlined path must be captured before the split so that both paths can join.  If we don't
+ 	 capture the values on the non-inlined path we could access stale values.  So for all stack entries that
+ 	 would be spilled along the non-inlined path, assign them to registers, or spill if none are available."
+ 	| i liveRegs reg |
+ 	liveRegs := liveRegisterMask.
+ 	optStatus isReceiverResultRegLive ifTrue:
+ 		[liveRegs := liveRegs + (self registerMaskFor: ReceiverResultReg)].
+ 	reg := TempReg. "Anything but NoReg"
+ 	i := simStackPtr + 1. "We must spill a contiguous range at the hot top of stack, so we assign coldest first :-("
+ 	[reg ~= NoReg and: [i > simSpillBase and: [i > 0]]] whileTrue:
+ 		[i := i - 1.
+ 		 self deny: ((self simStackAt: i) spilled and: [(self simStackAt: i) type = SSBaseOffset]).
+ 		 ((self simStackAt: i) spilled not
+ 		  and: [(self simStackAt: i) type = SSBaseOffset]) ifTrue:
+ 			[reg := self allocateRegNotConflictingWith: liveRegs.
+ 			 reg ~= NoReg ifTrue:
+ 				[(self simStackAt: i) storeToReg: reg]]].
+ 	reg = NoReg ifTrue:
+ 		[self ssFlushTo: i]!

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

Item was changed:
  ----- Method: RegisterAllocatingCogit>>flushLiveRegistersForSend (in category 'bytecode generator support') -----
  flushLiveRegistersForSend
  	<inline: true>
  	self assert: simSelf type = SSBaseOffset.
  	simSelf liveRegister: NoReg.
  	0 to: simStackPtr do:
  		[:i|
  		 self assert: ((self simStackAt: i) spilled
+ 					 and: [(self simStackAt: i) type = SSConstant
+ 						or: [((self simStackAt: i) type = SSBaseOffset
- 					 and: [((self simStackAt: i) type = SSBaseOffset
  							or: [i >= methodOrBlockNumTemps
  								and: (self simStackAt: i) type = SSSpill])
+ 							 and: [(self simStackAt: i) register = FPReg
+ 							 and: [(self simStackAt: i) offset = (self frameOffsetOfTemporary: i)]]]]).
- 					 and: [(self simStackAt: i) register = FPReg
- 					 and: [(self simStackAt: i) offset = (self frameOffsetOfTemporary: i)]]]).
  		 (self simStackAt: i) liveRegister: NoReg]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>freeAnyRegNotConflictingWith: (in category 'simulation stack') -----
+ freeAnyRegNotConflictingWith: regMask
+ 	"Spill the closest register on stack not conflicting with regMask. 
+ 	 Override so no assertion failure if no register can be allocated."
+ 	<var: #desc type: #'CogSimStackEntry *'>
+ 	| reg index |
+ 	self assert: needsFrame.
+ 	reg := NoReg.
+ 	index := simSpillBase max: 0.
+ 	[reg = NoReg and: [index < simStackPtr]] whileTrue: 
+ 		[ | desc |
+ 		 desc := self simStackAt: index.
+ 		 desc type = SSRegister ifTrue:
+ 			[(regMask anyMask: (self registerMaskFor: desc register)) ifFalse: 
+ 				[reg := desc register]].
+ 		 index := index + 1].
+ 	reg ~= NoReg ifTrue:
+ 		[self ssAllocateRequiredReg: reg].
+ 	^reg!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
+ 	 jumpNotSmallInts jumpContinue index rcvrReg argReg regMask |
- 	 jumpNotSmallInts jumpContinue index rcvrReg argReg |
  	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
  			["Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
+ 	"Since one or other of the arguments is an integer we can very likely profit from inlining.
+ 	 But if the other type is not SmallInteger or if the operation overflows then we will need to do a send.
+ 	 Since we're allocating values in registers we would like to keep those registers live on the inlined path
+ 	 and reload registers along the non-inlined send path.  But any values that would need to be spilled
+ 	 along the non-inlined path must be captured before the split so that both paths can join.  If we don't
+ 	 capture the values on the non-iblined path we could access stale values.  So for all stack entries that
+ 	 would be spilled along the non-inlined path, assign them to registers, or spill if none are available."
  	argIsInt
  		ifTrue:
  			[rcvrReg := self allocateRegForStackEntryAt: 1.
  			 (self ssValue: 1) popToReg: rcvrReg.
+ 			 self MoveR: rcvrReg R: TempReg.
+ 			 regMask := self registerMaskFor: rcvrReg]
- 			 self MoveR: rcvrReg R: TempReg]
  		ifFalse:
  			[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  			 self ssTop popToReg: argReg.
  			 (self ssValue: 1) popToReg: rcvrReg.
+ 			 self MoveR: argReg R: TempReg.
+ 			 regMask := self registerMaskFor: rcvrReg and: argReg].
- 			 self MoveR: argReg R: TempReg].
  	self ssPop: 2.
+ 	self captureUnspilledSpillsForSpecialSelectorSend: regMask.
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg].
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[self AddCq: argInt - ConstZero R: rcvrReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: rcvrReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rcvrReg.
  							 self AddR: argReg R: rcvrReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: rcvrReg]
  								ifFalse:
  									[self SubR: argReg R: rcvrReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: rcvrReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[self SubCq: argInt - ConstZero R: rcvrReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: rcvrReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
  							 self SubR: argReg R: rcvrReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: argReg R: rcvrReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: argReg]].
  		[AndRR] -> [argIsInt
  						ifTrue: [self AndCq: argInt R: rcvrReg]
  						ifFalse: [self AndR: argReg R: rcvrReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
  						ifTrue: [self OrCq: argInt R: rcvrReg]
  						ifFalse: [self OrR: argReg R: rcvrReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	self ssPushRegister: rcvrReg.
  	self copySimStackToScratch: (simSpillBase min: simStackPtr - 1).
  	self ssPop: 1.
  	self ssFlushTo: simStackPtr.
  	self deny: rcvrReg = Arg0Reg.
  	argIsInt
  		ifTrue: [self MoveCq: argInt R: Arg0Reg]
  		ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R: Arg0Reg]].
  	rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R: ReceiverResultReg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines.
  	self reconcileRegisterStateForJoinAfterSpecialSelectorSend.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>receiverRefOnScratchSimStack (in category 'bytecode generator support') -----
+ receiverRefOnScratchSimStack
+ 	simStackPtr to: (0 max: scratchSpillBase) by: -1 do:
+ 		[:i|
+ 		 ((self addressOf: (scratchSimStack at: i)) register = ReceiverResultReg
+ 		  and: [(self addressOf: (scratchSimStack at: i)) type = SSBaseOffset]) ifTrue:
+ 			[^true]].
+ 	^false!

Item was changed:
+ ----- Method: RegisterAllocatingCogit>>reconcileRegisterStateForJoinAfterSpecialSelectorSend (in category 'bytecode generator support') -----
- ----- Method: RegisterAllocatingCogit>>reconcileRegisterStateForJoinAfterSpecialSelectorSend (in category 'bytecode generators') -----
  reconcileRegisterStateForJoinAfterSpecialSelectorSend
  	"When the control flow from the inlined special selector code (e.g. add or comparison)
  	 joins the control flow from the send, taken when the inlined code fails, we should decide
  	 whether to reload any registers known to contain useful values or mark them as dead."
  	 
  	"If ReceiverResultReg is live along the inlined path, and is used before the next full send,
  	 reload it on the uncommon path."
+ 	scratchOptStatus isReceiverResultRegLive ifTrue:
+ 		[(self existsInstVarRefBeforeSendOrReturn
+ 		  or: [self receiverRefOnScratchSimStack])
+ 			ifTrue:
+ 				[optStatus isReceiverResultRegLive: true.
+ 				 optStatus ssEntry storeToReg: ReceiverResultReg]
- 	optStatus isReceiverResultRegLive ifTrue:
- 		[self existsInstVarRefBeforeSendOrReturn
- 			ifTrue: [optStatus ssEntry storeToReg: ReceiverResultReg]
  			ifFalse: [optStatus isReceiverResultRegLive: false]].
  
  	"Restore the simStack to that in scratchSimStack,
  	 popping any spilled state back into allocated registers."
  	simSpillBase := scratchSpillBase.
+ 	simStackPtr to: 0 by: -1 do:
- 	simStackPtr to: simSpillBase + 1 by: -1 do:
  		[:i|
  		 self assert: (i = simStackPtr
  						ifTrue: [(self simStackAt: i) type = SSRegister]
  						ifFalse: [(self simStackAt: i) spilled]).
+ 		 (self addressOf: (scratchSimStack at: i)) spilled ifTrue:
+ 			[self assert: ((scratchSimStack at: i) isSameEntryAs: (self simStackAt: i)).
+ 			 ^self].
  		 (self addressOf: (scratchSimStack at: i)) reconcileWith: (self simStackAt: i).
  		 simStack
  			at: i
  			put: (self
  					cCode: [scratchSimStack at: i]
  					inSmalltalk: [(scratchSimStack at: i) copy])]!



More information about the Vm-dev mailing list