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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 26 19:58:26 UTC 2018


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

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

Name: VMMaker.oscog-eem.2327
Author: eem
Time: 26 January 2018, 11:57:52.384622 am
UUID: 9b4049be-1cd2-4832-ac13-e744492f1007
Ancestors: VMMaker.oscog-eem.2326

StackToRegisterMappingCogit:
Get much stricter with simSpillBase for the benefit of RegisterAllocatingCogit (and eventually SistaCogit).

updateSimSpillBase is now called after the new descriptor is pushed and either counts up or counts down as required to guarantee it points one beyoind the last spilled entry.  The assertCorrectSimStackPtr asserts now insist on this.  With this change we can start to replace all the simSpillBase max: 0 prharses with simply simSpillBase.

Deal with the assett failures due to frameless methods with unused temporaries by simply refusing to JIT them; see the new methodFoundInvalidPostScan hook.

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

Item was changed:
  ----- Method: CoInterpreter>>frameCallerContext:put: (in category 'frame access') -----
  frameCallerContext: theFP put: aValue
  	"In the StackInterpreter the saved ip field of a base frame holds the
  	 base frame's caller context. But in the Cog VM the first word on the
  	 stack holds the base frame's caller context, which is immediately
  	 above the stacked receiver."
  	<var: #theFP type: #'char *'>
+ 	<inline: true>
+ 	self assert: (aValue = objectMemory nilObject or: [objectMemory isContext: aValue]).
  	self assert: (self isBaseFrame: theFP).
  	self assert: theFP + (self frameStackedReceiverOffset: theFP) + (2 * objectMemory wordSize) = (stackPages stackPageFor: theFP) baseAddress.
  	self assert: (stackPages longAt: theFP + (self frameStackedReceiverOffset: theFP) + objectMemory wordSize) = (self frameContext: theFP).
  	^stackPages
  		longAt: theFP + (self frameStackedReceiverOffset: theFP) + (2 * objectMemory wordSize)
  		put: aValue!

Item was changed:
  ----- Method: Cogit>>compileCogMethod: (in category 'compile abstract instructions') -----
  compileCogMethod: selector
  	<returnTypeC: #'CogMethod *'>
  	| numBytecodes numBlocks numCleanBlocks result extra |
  	hasYoungReferent := (objectMemory isYoungObject: methodObj)
  						  or: [objectMemory isYoung: selector].
  	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
  	inBlock := 0.
  	postCompileHook := nil.
  	maxLitIndex := -1.
  	extra := ((primitiveIndex := coInterpreter primitiveIndexOf: methodObj) > 0
  			and: [(coInterpreter isQuickPrimitiveIndex: primitiveIndex) not])
  				ifTrue: [30]
  				ifFalse: [10].
  	initialPC := coInterpreter startPCOfMethod: methodObj.
  	"initial estimate.  Actual endPC is determined in scanMethod."
  	endPC := (coInterpreter isQuickPrimitiveIndex: primitiveIndex)
  					ifTrue: [initialPC - 1]
  					ifFalse: [objectMemory numBytesOf: methodObj].
  	numBytecodes := endPC - initialPC + 1.
  	self allocateOpcodes: (numBytecodes + extra) * self estimateOfAbstractOpcodesPerBytecodes
  		bytecodes: numBytecodes
  		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	(numBlocks := self scanMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
  	numCleanBlocks := self scanForCleanBlocks.
+ 	self methodFoundInvalidPostScan ifTrue:
+ 		[^coInterpreter cCoerceSimple: ShouldNotJIT to: #'CogMethod *'].
  	self allocateBlockStarts: numBlocks + numCleanBlocks.
  	blockCount := 0.
  	numCleanBlocks > 0 ifTrue:
  		[self addCleanBlockStarts].
  	(self maybeAllocAndInitCounters
  	 and: [self maybeAllocAndInitIRCs]) ifFalse: "Inaccurate error code, but it'll do.  This will likely never fail."
  		[^coInterpreter cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogMethod: selector!

Item was added:
+ ----- Method: Cogit>>methodFoundInvalidPostScan (in category 'testing') -----
+ methodFoundInvalidPostScan
+ 	"This is a hook for subclasses to filter out methods they can't deal with."
+ 	^false!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>copySimStackToScratch: (in category 'bytecode generator support') -----
  copySimStackToScratch: spillBase
  	<inline: true>
+ 	self assert: spillBase > methodOrBlockNumTemps.
  	scratchBytecodePC = bytecodePC ifTrue:
  		[^self].
  	scratchBytecodePC := bytecodePC.
  	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!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureReceiverResultRegContainsSelf (in category 'bytecode generator support') -----
  ensureReceiverResultRegContainsSelf
+ 	"First ensure that ReceiverResultReg is allocated to self,
+ 	 which may cause spills, etc.  Then copy the register into
+ 	 any instances of simSelf on the stack."
- 	methodOrBlockNumTemps + 1 to: simStackPtr do:
- 		[:i|
- 		(self simSelf isSameEntryAs: (self simStackAt: i))
- 			ifTrue: [(self simStackAt: i) liveRegister: ReceiverResultReg]
- 			ifFalse:
- 				[(self simStackAt: i) liveRegister = ReceiverResultReg ifTrue:
- 					[(self simStackAt: i) liveRegister: NoReg]]].
  	super ensureReceiverResultRegContainsSelf.
+ 	"the storeToReg: in putSelfInReceiverResultReg in
+ 	 ensureReceiverResultRegContainsSelf copies the register to all copies.
+ 	 So simply check that the stack agrees with this."
+ 	self assert: self receiverResultRegIsAssignedToSelfAndNothingElse!
- 	self assert: self receiverIsInReceiverResultReg!

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

Item was changed:
  ----- Method: RegisterAllocatingCogit>>freeAnyRegNotConflictingWith: (in category 'simulation stack') -----
  freeAnyRegNotConflictingWith: regMask
  	"Spill the closest register on stack not conflicting with regMask. 
  	 Override to unassign assigned temp regs if necessary."
  	<var: #desc type: #'CogSimStackEntry *'>
  	| index desc |
  	self assert: needsFrame.
+ 	self assert: simSpillBase >= 0.
+ 	index := simSpillBase.
- 	index := simSpillBase max: 0.
  	[index < simStackPtr] whileTrue: 
  		[desc := self simStackAt: index.
  		 desc type = SSRegister ifTrue:
  			[(regMask anyMask: (self registerMaskFor: desc register)) ifFalse: 
  				[self ssAllocateRequiredReg: desc register.
  				 ^desc register]].
  		 index := index + 1].
  	1 to: methodOrBlockNumTemps do:
  		[:i|
  		 desc := self simStackAt: i.
  		 (desc liveRegister = NoReg
  		  or: [self register: desc liveRegister isInMask: regMask]) ifFalse:
  			[self ssAllocateRequiredReg: desc liveRegister.
  			 ^desc liveRegister]].
  	(self simSelf liveRegister = NoReg
  	 or: [self register: self simSelf liveRegister isInMask: regMask]) ifFalse:
  		[self ssAllocateRequiredReg: self simSelf liveRegister.
  		 ^self simSelf liveRegister].
  	^NoReg!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt destReg
  	 jumpNotSmallInts jumpContinue jumpOverflow index rcvrReg argReg regMask |
  	<var: #jumpOverflow type: #'AbstractInstruction *'>
  	<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)])
  				or: [self mclassIsSmallInteger and: [(self ssValue: 1) isSameEntryAs: self simSelf]].
  
  	(argIsInt and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
  		[| result |
  		 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.
  	 See reconcileRegisterStateForJoinAfterSpecialSelectorSend below."
  	argIsInt
  		ifTrue:
  			[rcvrReg := self allocateRegForStackEntryAt: 1.
  			 (self ssValue: 1) popToReg: rcvrReg.
  			 regMask := self registerMaskFor: rcvrReg]
  		ifFalse:
  			[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  			 self ssTop popToReg: argReg.
  			 (self ssValue: 1) popToReg: rcvrReg.
  			 regMask := self registerMaskFor: rcvrReg and: argReg].
  
  	"rcvrReg can be reused for the result iff the receiver is a constant or is an SSRegister that is not used elsewhere."
  	destReg := ((rcvrIsInt and: [rcvrIsConst])
  				 or: [(self ssValue: 1) type = SSRegister
  					 and: [(self anyReferencesToRegister: rcvrReg inAllButTopNItems: 2) not]])
  					ifTrue: [rcvrReg]
  					ifFalse: [self allocateRegNotConflictingWith: regMask].
  	self ssPop: 2.
  	jumpNotSmallInts := (rcvrIsInt and: [argIsInt]) ifFalse:
  							[argIsInt
  								ifTrue: [objectRepresentation genJumpNotSmallInteger: rcvrReg]
  								ifFalse:
  									[rcvrIsInt
  										ifTrue: [objectRepresentation genJumpNotSmallInteger: argReg]
  										ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg and: argReg scratch: TempReg]]].
  	rcvrReg ~= destReg ifTrue:
  		[self MoveR: rcvrReg R: destReg].
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[self AddCq: argInt - ConstZero R: destReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before doing send"
  							 rcvrReg = destReg ifTrue:
  								[self SubbCq: argInt - ConstZero R: rcvrReg]]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: destReg.
  							 self AddR: argReg R: destReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before doing send"
  							 destReg = rcvrReg ifTrue:
  								[(rcvrIsInt and: [rcvrIsConst])
  									ifTrue: [self MoveCq: rcvrInt R: rcvrReg]
  									ifFalse:
  										[self SubbR: argReg R: rcvrReg.
  										 objectRepresentation genSetSmallIntegerTagsIn: rcvrReg]]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[self SubCq: argInt - ConstZero R: destReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before doing send"
  							 rcvrReg = destReg ifTrue:
  								[self AddcCq: argInt - ConstZero R: rcvrReg]]
  						ifFalse:
  							[(self anyReferencesToRegister: argReg inAllButTopNItems: 0)
  								ifTrue: "argReg is live; cannot strip tags and continue on no overflow without restoring tags"
  									[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
  									 self SubR: argReg R: destReg.
  									 jumpOverflow := self JumpOverflow: 0.
  									 "no overflow; must undo the damage before continuing"
  									 objectRepresentation genSetSmallIntegerTagsIn: argReg.
  									 jumpContinue := self Jump: 0.
  									 jumpOverflow jmpTarget: self Label.
  									 "overflow; must undo the damage before doing send"
  									 ((rcvrIsInt and: [rcvrIsConst]) or: [destReg ~= rcvrReg]) ifFalse:
  										[self AddcR: argReg R: destReg].
  									 objectRepresentation genSetSmallIntegerTagsIn: argReg]
  								ifFalse:
  									[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
  									 self SubR: argReg R: destReg.
  									 jumpContinue := self JumpNoOverflow: 0.
  									 "overflow; must undo the damage before doing send"
  									 ((rcvrIsInt and: [rcvrIsConst]) or: [destReg ~= rcvrReg]) ifFalse:
  										[self AddcR: argReg R: rcvrReg].
  									 objectRepresentation genSetSmallIntegerTagsIn: argReg]]].
  		[AndRR] -> [argIsInt
  						ifTrue: [self AndCq: argInt R: destReg]
  						ifFalse: [self AndR: argReg R: destReg].
  					jumpContinue := jumpNotSmallInts ifNotNil: [self Jump: 0]].
  		[OrRR]	-> [argIsInt
  						ifTrue: [self OrCq: argInt R: destReg]
  						ifFalse: [self OrR: argReg R: destReg].
  					jumpContinue := jumpNotSmallInts ifNotNil: [self Jump: 0]] }.
  	jumpNotSmallInts
  		ifNil: [jumpContinue ifNil: "overflow cannot happen"
  				[self annotateInstructionForBytecode.
  				 self ssPushRegister: destReg.
  				 ^0]]
  		ifNotNil:
  			[jumpNotSmallInts jmpTarget: self Label].
  	self ssPushRegister: destReg.
+ 	self copySimStackToScratch: simSpillBase.
- 	self copySimStackToScratch: (simSpillBase min: simStackPtr - 1).
  	self ssPop: 1.
  	self ssFlushTo: simStackPtr.
  	rcvrReg = Arg0Reg
  		ifTrue:
  			[argReg = ReceiverResultReg
  				ifTrue: [self SwapR: Arg0Reg R: Arg0Reg Scratch: TempReg. argReg := Arg0Reg]
  				ifFalse: [self MoveR: rcvrReg R: ReceiverResultReg].
  			 rcvrReg := ReceiverResultReg].
  	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 changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith:forwards: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup forwards: forwards
  	"At a merge point the cogit expects the stack to be in the same state as mergeSimStack.
  	 mergeSimStack is the state as of some jump forward or backward to this point.  So make
  	 simStack agree with mergeSimStack (it is, um, problematic to plant code at the jump).
  	 Values may have to be assigned to registers.  Registers may have to be swapped.
  	 The state of optStatus must agree.
  	 Generate code to merge the current simStack with that of the target fixup,
  	 the goal being to keep as many registers live as possible.  If the merge is forwards
  	 registers can be deassigned (since registers are always written to temp vars).
  	 But if backwards, nothing can be deassigned, and the state /must/ reflect the target."
  	"self printSimStack; printSimStack: fixup mergeSimStack"
  	"abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
  	<var: #fixup type: #'BytecodeFixup *'>
  	| startIndex mergeSimStack |
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<var: #currentEntry type: #'SimStackEntry *'>
  	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  	startIndex := opcodeIndex. "for debugging"
  	"Assignments amongst the registers must be made in order to avoid overwriting.
  	 If necessary exchange registers amongst simStack's entries to resolve any conflicts."
  	self reconcileRegistersInTempVarsInCurrentSimStackWithThoseIn: mergeSimStack.
  	(self asserta: (self conflictsResolvedBetweenSimStackAnd: mergeSimStack)) ifFalse:
  		[Notification new tag: #failedMerge; signal].
  	(self pushForMergeWith: mergeSimStack)
  		ifTrue:
  			[methodOrBlockNumTemps + 1 to: simStackPtr do:
  				[:i| self mergePushingWithEntryInTargetSimStack: mergeSimStack at: i]]
  		ifFalse:
  			[simStackPtr to: methodOrBlockNumTemps + 1 by: -1 do:
  				[:i| self mergePoppingWithEntryInTargetSimStack: mergeSimStack at: i]].
  	"Still haven't handled simSpillBase."
  	self assert: (simSpillBase > simStackPtr
  				or: [simSpillBase > methodOrBlockNumTemps
+ 					and: [(self simStack: mergeSimStack at: simSpillBase - 1) spilled]])!
- 					and: [(self simStack: mergeSimStack at: simSpillBase) spilled]])!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>moveVolatileSimStackEntriesToRegisters (in category 'bytecode generator support') -----
  moveVolatileSimStackEntriesToRegisters
  	"When jumping forward to a merge point the stack must be reconcilable with the state that falls through to the merge point.
  	 We cannot easily arrange that later we add code to the branch, e.g. to spill values.  Instead, any volatile contents must be
  	 moved to registers.
  		[In fact, that's not exactly true, consider these two code sequences:
  							self at: (expr ifTrue: [1] ifFalse: [2]) put: a
  							self at: 1 put: (expr ifTrue: [a] ifFalse: [b])
  						 The first one needs 1 saving to a register to reconcile with 2.
  						 The second one has 1 on both paths, but we're not clever enough to spot this case yet.
  		 First of all, if the constant requires an annotation then it is difficult to deal with.  But if the constant
  		 does not require an annotation one way would be for a SimStackEntry for an SSConstant to refer to
  		 the loading instruction and then at the merge simply change the loading instruction to a Label if the
  		 constant is the same on both branches].
  	 Volatile contents are anything not spilled to the stack, because as yet we can only merge registers."
  	<inline: true>
  	| allocatedRegs |
  	<var: #desc type: #'SimStackEntry *'>
  	allocatedRegs := self allocatedRegisters.
+ 	self assert: simSpillBase >= 0.
+ 	simSpillBase to: simStackPtr do: 
- 	(simSpillBase max: 0) to: simStackPtr do: 
  		[:i| | desc reg |
  		 desc := self simStackAt: i.
  		 desc spilled
  			ifTrue: [simSpillBase := i]
  			ifFalse:
  				[desc registerOrNone = NoReg ifTrue:
  					[reg := self allocateRegNotConflictingWith: allocatedRegs.
  					 reg = NoReg
  						ifTrue: [self halt] "have to spill"
  						ifFalse:
  							[desc storeToReg: reg.
  							 allocatedRegs := allocatedRegs bitOr: (self registerMaskFor: reg)]]]].
  	self deny: self duplicateRegisterAssignmentsInTemporaries!

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

Item was added:
+ ----- Method: RegisterAllocatingCogit>>receiverResultRegIsAssignedToSelfAndNothingElse (in category 'testing') -----
+ receiverResultRegIsAssignedToSelfAndNothingElse
+ 	| culprit |
+ 	0 to: simStackPtr do:
+ 		[:i|
+ 		 (self simSelf isSameEntryAs: (self simStackAt: i))
+ 		 ~= ((self simStackAt: i) liveRegister = ReceiverResultReg) ifTrue:
+ 			[culprit := i.
+ 			 ^false]].
+ 	^true!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ssFlushFrom:upThrough: (in category 'simulation stack') -----
  ssFlushFrom: start upThrough: unaryBlock
  	"Any occurrences on the stack of the value being stored (which is the top of stack)
  	 must be flushed, and hence any values colder than them stack."
  	<inline: true>
+ 	self assert: simSpillBase >= 0.
+ 	start to: simSpillBase by: -1 do:
- 	start to: (simSpillBase max: 0) by: -1 do:
  		[ :index |
  		(unaryBlock value: (self simStackAt: index)) ifTrue: [ ^ self ssFlushTo: index ] ]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>traceSimStack (in category 'simulation only') -----
  traceSimStack
  	<cmacro: '() 0'>
  	(compilationTrace anyMask: 4) ifTrue:
+ 		[self printSimStack]!
- 		[self printSimSelf; printSimStack]!

Item was changed:
  ----- Method: StackInterpreter>>frameCallerContext:put: (in category 'frame access') -----
  frameCallerContext: theFP put: aValue
- 	<inline: true>
  	<var: #theFP type: #'char *'>
+ 	<inline: true>
+ 	self assert: (aValue = objectMemory nilObject or: [objectMemory isContext: aValue]).
  	^stackPages
  		longAt: theFP + FoxCallerContext "a.k.a. FoxCallerSavedIP"
  		put: aValue!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>assertCorrectSimStackPtr (in category 'compile abstract instructions') -----
  assertCorrectSimStackPtr
  	<inline: true>
  	"Would like to assert simply simSpillBase > methodOrBlockNumTemps but can't because
  	 of the initialNils hack for nested blocks in SqueakV3PlusClosures"
  	self assert: (simSpillBase >= methodOrBlockNumTemps
+ 				or: [inBlock = InVanillaBlock and: [simSpillBase >= 0]]).
+ 	(needsFrame and: [simSpillBase > 0]) ifTrue:
+ 		[self assert: (self simStackAt: simSpillBase - 1) spilled == true.
+ 		 self assert: (simSpillBase > simStackPtr or: [(self simStackAt: simSpillBase) spilled == false])].
+  	self cCode: '' inSmalltalk:
- 				or: [inBlock = InVanillaBlock]).
-  	 self cCode: '' inSmalltalk:
  		[deadCode ifFalse:
  			[self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1])
+ 						= (self debugStackPointerFor: bytecodePC)]].!
- 						= (self debugStackPointerFor: bytecodePC)]].
- 	!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>methodFoundInvalidPostScan (in category 'testing') -----
+ methodFoundInvalidPostScan
+ 	"Frameless methods with local temporaries cause problems,
+ 	 mostly in asserts, and yet they matter not at all for performance.
+ 	 Shun them."
+ 	needsFrame ifFalse:
+ 		[^methodOrBlockNumTemps > methodOrBlockNumArgs].
+ 	^super methodFoundInvalidPostScan!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>restoreSimStackAtMergePoint: (in category 'simulation stack') -----
  restoreSimStackAtMergePoint: fixup
  	<inline: true>
  	"All the execution paths reaching a merge point expect everything to be
  	 spilled on stack and the optStatus is unknown. Throw away all simStack and 
  	 optStatus optimization state."
- 	simSpillBase := methodOrBlockNumTemps + 1.
  	self voidReceiverOptStatus.
  	methodOrBlockNumTemps + 1 to: simStackPtr do:
  		[:i|
  		 (self simStackAt: i)
  			type: SSSpill;
  			offset: FoxMFReceiver - (i - methodOrBlockNumArgs * objectMemory bytesPerOop);
  			register: FPReg;
  			spilled: true].
+ 	simSpillBase := simStackPtr + 1.
  	LowcodeVM ifTrue:
  		[0 to: simNativeStackPtr do:
  			[ :i |
  			(self simNativeStackAt: i)
  				ensureIsMarkedAsSpilled].
  		simNativeSpillBase := simNativeStackPtr + 1].
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssFlushUpThrough: (in category 'simulation stack') -----
  ssFlushUpThrough: unaryBlock
  	"Any occurrences on the stack of the value being stored (which is the top of stack)
  	 must be flushed, and hence any values colder than them stack."
  	<inline: true>
+ 	self assert: simSpillBase >= 0.
+ 	simStackPtr - 1 to: simSpillBase by: -1 do:
- 	simStackPtr - 1 to: (simSpillBase max: 0) by: -1 do:
  		[ :index |
  		(unaryBlock value: (self simStackAt: index)) ifTrue: [ ^ self ssFlushTo: index ] ]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPop: (in category 'simulation stack') -----
  ssPop: n
  	self assert: (simStackPtr - n >= methodOrBlockNumTemps
  				or: [(needsFrame not and: [simStackPtr - n >= 0])
  				or: [self maybeCompilingFirstPassOfBlockWithInitialPushNil]]).
+ 	simStackPtr := simStackPtr - n.
+ 	self updateSimSpillBase!
- 	simStackPtr := simStackPtr - n!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushAnnotatedConstant: (in category 'simulation stack') -----
  ssPushAnnotatedConstant: literal
+ 	self ssPushConstant: literal.
- 	self ssPush: 1.
- 	self updateSimSpillBase.
- 	self ssTop
- 		type: SSConstant;
- 		spilled: false;
- 		constant: literal;
- 		bcptr: bytecodePC.
  	self annotateInstructionForBytecode.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushBase:offset: (in category 'simulation stack') -----
  ssPushBase: reg offset: offset
  	self ssPush: 1.
- 	self updateSimSpillBase.
  	self ssTop
  		type: SSBaseOffset;
  		spilled: false;
  		register: reg;
  		offset: offset;
  		bcptr: bytecodePC.
+ 	self updateSimSpillBase.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushConstant: (in category 'simulation stack') -----
  ssPushConstant: literal
  	self ssPush: 1.
- 	self updateSimSpillBase.
  	self ssTop
  		type: SSConstant;
  		spilled: false;
  		constant: literal;
  		bcptr: bytecodePC.
+ 	self updateSimSpillBase.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushRegister: (in category 'simulation stack') -----
  ssPushRegister: reg
  	self ssPush: 1.
- 	self updateSimSpillBase.
  	self ssTop
  		type: SSRegister;
  		spilled: false;
  		register: reg;
  		bcptr: bytecodePC.
+ 	self updateSimSpillBase.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>updateSimSpillBase (in category 'simulation stack') -----
  updateSimSpillBase
+ 	"Something volatile has been pushed on the stack; update simSpillBase accordingly."
  	<inline: true>
+ 	self assert: ((simSpillBase > methodOrBlockNumTemps
+ 				and: [simStackPtr >= methodOrBlockNumTemps])
+ 				or: [inBlock = InVanillaBlock and: [compilationPass = 1]]).
+ 	simSpillBase > simStackPtr
+ 		ifTrue:
+ 			[simSpillBase := simStackPtr + 1.
+ 			 [simSpillBase - 1 > methodOrBlockNumTemps
+ 			   and: [(self simStackAt: simSpillBase - 1) spilled not]] whileTrue:
+ 				[simSpillBase := simSpillBase - 1]]
+ 		ifFalse:
+ 			[[(self simStackAt: simSpillBase) spilled
+ 			   and: [simSpillBase <= simStackPtr]] whileTrue:
+ 				[simSpillBase := simSpillBase + 1]].
+ 	methodOrBlockNumTemps + 1 to: (simSpillBase - 1 min: simStackPtr) do:
+ 		[:i|
+ 		self assert: (self simStackAt: i) spilled == true]!
- 	self assert: (simSpillBase > methodOrBlockNumTemps
- 				or: [inBlock = InVanillaBlock]).
- 	simSpillBase > simStackPtr ifTrue:
- 		[simSpillBase := simStackPtr max: methodOrBlockNumTemps].!



More information about the Vm-dev mailing list