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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 8 00:30:01 UTC 2018


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

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

Name: VMMaker.oscog-eem.2331
Author: eem
Time: 7 February 2018, 4:29:40.345022 pm
UUID: d0e828c3-358c-4ff1-9762-3bcbe3306514
Ancestors: VMMaker.oscog-eem.2330

RegisterAllocatingCogit:
Refactor to allow RegisterAllocatingCogit to deal with the push initial nils hack, i.e. move the two pass loop mechanism out of compileAbstractInstructionsFrom:through: into compileMethodBody & compileBlockBodies.

Ensure a few loops using simSpillBase compyte a rahge that is between 0 and simStackPtr.

Make several asserts use maybeCompilingFirstPassOfBlockWithInitialPushNil instead of open coding the expression.

Execution appears to be correct until nextPutAll: is sent to a SmallInteger evaluating "aStream nextPutAll: (m < 10 ifTrue: [':0'] ifFalse: [':'])." in Time>>#print24:showSeconds:showSubseconds:on:

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

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileWith:spillOffset:onSpillOrUnspill: (in category 'compile abstract instructions') -----
  reconcileWith: targetEntry spillOffset: spillOffset onSpillOrUnspill: spillOrUnspillBlock
  	"Make the state of a targetEntry, a stack entry following a non-inlined special selector
  	 send, the same as the corresponding entry (the receiver) along the inlined path.
  	 spillOffset is zero for non-spill locations (self & temps), and the offset of the spill for
  	 volatile stack entries. spillOrUnspillBlock is a block evaluated with the target's
  	 registerOrNone if the receiver and target have different spilledness.
  	 Answer if the reconciliation merged a register; merged registers must be deassigned."
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<inline: true>
  	| targetReg mergedRegister |
  	spilled = targetEntry spilled ifTrue:
  		[self assert: ((self isSameEntryAs: targetEntry)
  					 or: [(targetEntry spilled not and: [targetEntry registerOrNone ~= NoReg])
  					 or: [spilled and: [type = SSConstant and: [offset = targetEntry offset]]]]).
  		 (targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  			[liveRegister := NoReg.
  			 ^false].
  		 mergedRegister := false.
  		 type caseOf: {
  			[SSBaseOffset]	-> [liveRegister ~= targetReg ifTrue:
  									[cogit MoveMw: offset r: register R: targetReg.
  									 mergedRegister := true].
  								targetEntry type caseOf: {
  									[SSBaseOffset]	-> [liveRegister := targetReg.
  														(self isSameEntryAs: targetEntry) ifFalse:
  															[type := SSSpill.
  															 offset := spillOffset]].
  									[SSSpill]		-> [liveRegister := targetReg. type := SSSpill.
  														offset := spillOffset].
  									[SSConstant]	-> [liveRegister := targetReg. type := SSSpill.
  														offset := spillOffset].
  									[SSRegister]	-> [register := targetReg. type := SSRegister] }].
  			[SSSpill]		-> [cogit MoveMw: offset r: register R: targetReg.
  								liveRegister := targetReg.
  								mergedRegister := true].
  			[SSConstant]	-> [cogit genMoveConstant: constant R: targetReg.
+ 								type := SSRegister. register := targetReg. liveRegister := NoReg.
- 								type := SSRegister. register := targetReg.
  								mergedRegister := true].
  			[SSRegister]	-> [targetReg ~= register ifTrue:
  									[cogit MoveR: register R: targetReg.
  									 register := targetReg.
  									 mergedRegister := true]] }.
  		 ^mergedRegister].
  	targetReg := targetEntry registerOrNone.
  	spillOrUnspillBlock value: targetReg.
+ 	(type = SSConstant
+ 	 and: [targetEntry type ~= SSConstant or: [targetEntry constant ~= constant]]) ifTrue:
+ 		[type := SSSpill. offset := spillOffset. register := FPReg].
  	liveRegister ~= targetReg ifTrue:
  		[liveRegister := NoReg].
  	^false!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>compileAbstractInstructionsFrom:through: (in category 'compile abstract instructions') -----
  compileAbstractInstructionsFrom: start through: end
  	"Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course.
+ 	 Override to recompile after a loop requiring a merge is detected."
- 	 Override to provide a development-time only escape for failed merges due to partially implemented
- 	 parallel move.  Override to recompile after a loop requiring a merge is detected."
- 	| result initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
- 	compilationPass := 1.
  	scratchBytecodePC := nil.
+ 	^super compileAbstractInstructionsFrom: start through: end!
- 	initialOpcodeIndex := opcodeIndex.
- 	initialCounterIndex := self maybeCounterIndex."for SistaCogit"
- 	literalsManager saveForRecompile.
- 	NewspeakVM ifTrue:
- 		[initialIndexOfIRC := indexOfIRC].
- 	[recompileForLoopRegisterAssignments := false.
- 	 result := super compileAbstractInstructionsFrom: start through: end.
- 	 result = 0 and: [recompileForLoopRegisterAssignments]]
- 		whileTrue:
- 			[self assert: compilationPass <= 2.
- 			 self reinitializeAllButBackwardFixupsFrom: start through: end.
- 			 self resetSimStack: start.
- 			 self reinitializeOpcodesFrom: initialOpcodeIndex to: opcodeIndex - 1.
- 			 compilationPass := compilationPass + 1.
- 			 nextFixup := 0.
- 			 opcodeIndex := initialOpcodeIndex.
- 			 self maybeSetCounterIndex: initialCounterIndex. "For SistaCogit"
- 			 literalsManager resetForRecompile.
- 			 NewspeakVM ifTrue:
- 				[indexOfIRC := initialIndexOfIRC]].
- 	^result!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
+ compileBlockBodies
+ 	<inline: false>
+ 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
+ 	  initialStackPtr initialOpcodeIndex initialIndexOfIRC initialCounterIndex |
+ 	<var: #blockStart type: #'BlockStart *'>
+ 	self assert: blockCount > 0.
+ 	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
+ 	savedNeedsFrame := needsFrame.
+ 	savedNumArgs := methodOrBlockNumArgs.
+ 	savedNumTemps := methodOrBlockNumTemps.
+ 	inBlock := InVanillaBlock.
+ 	compiledBlocksCount := 0.
+ 	[compiledBlocksCount < blockCount] whileTrue:
+ 		[blockStart := self blockStartAt: compiledBlocksCount.
+ 		 (result := self scanBlock: blockStart) < 0 ifTrue: [^result].
+ 		 compilationPass := 1.
+ 		 scratchBytecodePC := nil.
+ 		 initialOpcodeIndex := opcodeIndex.
+ 		 initialCounterIndex := self maybeCounterIndex."for SistaCogit"
+ 		 literalsManager saveForRecompile.
+ 		 NewspeakVM ifTrue:
+ 			[initialIndexOfIRC := indexOfIRC].
+ 		 [recompileForLoopRegisterAssignments := false.
+ 		  self compileBlockEntry: blockStart.
+ 		  initialStackPtr := simStackPtr.
+ 		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
+ 						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
+ 			[^result].
+ 		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
+ 		   estimated the number of initial nils (because it assumed one or more pushNils to
+ 		   produce an operand were pushNils to initialize temps.  This is very rare, so
+ 		   compensate by checking, adjusting numInitialNils and recompiling the block body.
+ 		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
+ 		  initialStackPtr ~= simStackPtr or: [recompileForLoopRegisterAssignments]]
+ 			whileTrue:
+ 				[self assert: (initialStackPtr > simStackPtr or: [deadCode]).
+ 				 self assert: compilationPass = 1.
+ 				 compilationPass := compilationPass + 1. "for asserts"
+ 				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
+ 				 blockStart fakeHeader dependent: nil.
+ 				 self reinitializeAllButBackwardFixupsFrom: blockStart startpc + blockStart numInitialNils through: blockStart startpc + blockStart span - 1.
+ 				 nextFixup := 0.
+ 				 self resetSimStack: blockStart startpc.
+ 				 self reinitializeOpcodesFrom: initialOpcodeIndex to: opcodeIndex - 1.
+ 				 opcodeIndex := initialOpcodeIndex.
+ 				 self maybeSetCounterIndex: initialCounterIndex. "For SistaCogit"
+ 				 literalsManager resetForRecompile.
+ 				 NewspeakVM ifTrue:
+ 					[indexOfIRC := initialIndexOfIRC]].
+ 		compiledBlocksCount := compiledBlocksCount + 1].
+ 	needsFrame := savedNeedsFrame.
+ 	methodOrBlockNumArgs := savedNumArgs.
+ 	methodOrBlockNumTemps := savedNumTemps.
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>compileMethodBody (in category 'compile abstract instructions') -----
+ compileMethodBody
+ 	"Compile the top-level method body."
+ 	<inline: true>
+ 	| result initialOpcodeIndex initialCounterIndex initialIndexOfIRC start |
+ 	endPC < initialPC ifTrue: [^0]. "quick primitives"
+ 	"When compiling, skip any initial CallPrimitive and optional StorePrimErrCode bytecodes.
+ 	 These are dealt with in compileFrameBuild."
+ 	compilationPass := 1.
+ 	scratchBytecodePC := nil.
+ 	initialOpcodeIndex := opcodeIndex.
+ 	initialCounterIndex := self maybeCounterIndex."for SistaCogit"
+ 	literalsManager saveForRecompile.
+ 	NewspeakVM ifTrue:
+ 		[initialIndexOfIRC := indexOfIRC].
+ 	[recompileForLoopRegisterAssignments := false.
+ 	 start := initialPC + (self deltaToSkipPrimAndErrorStoreIn: methodObj header: methodHeader).
+ 	 result := self compileAbstractInstructionsFrom: start through: endPC.
+ 	 result = 0
+ 	 and: [recompileForLoopRegisterAssignments]]
+ 		whileTrue:
+ 			[self assert: compilationPass <= 2.
+ 			 self reinitializeAllButBackwardFixupsFrom: start through: endPC.
+ 			 self resetSimStack: start.
+ 			 self reinitializeOpcodesFrom: initialOpcodeIndex to: opcodeIndex - 1.
+ 			 compilationPass := compilationPass + 1.
+ 			 nextFixup := 0.
+ 			 opcodeIndex := initialOpcodeIndex.
+ 			 self maybeSetCounterIndex: initialCounterIndex. "For SistaCogit"
+ 			 literalsManager resetForRecompile.
+ 			 NewspeakVM ifTrue:
+ 				[indexOfIRC := initialIndexOfIRC]].
+ 	^result!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>copySimStackToScratch: (in category 'bytecode generator support') -----
  copySimStackToScratch: spillBase
  	<inline: true>
+ 	self assert: (spillBase > methodOrBlockNumTemps
+ 				or: [self maybeCompilingFirstPassOfBlockWithInitialPushNil and: [spillBase > methodOrBlockNumArgs]]).
- 	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>>duplicateRegisterAssignmentsInTemporaries (in category 'debugging') -----
  duplicateRegisterAssignmentsInTemporaries
  	| liveRegisters |
  	liveRegisters := 0.
+ 	0 to: (methodOrBlockNumTemps min: (simStackPtr min: simSpillBase - 1)) do: "The min:s are for the initial push nil hack"
+ 		[:i| | current liveRegister |
+ 		liveRegister := (current := self simStackAt: i) liveRegister.
- 	0 to: methodOrBlockNumTemps do:
- 		[:i| | liveRegister |
- 		liveRegister := (self simStackAt: i) liveRegister.
  		liveRegister ~= NoReg ifTrue:
  			[(self register: liveRegister isInMask: liveRegisters) ifTrue:
+ 				["Filter out pushed temps in first-pass vanilla blocks"
+ 				 (self maybeCompilingFirstPassOfBlockWithInitialPushNil
+ 				  and: [current type = SSBaseOffset
+ 				  and: [current offset ~= (self frameOffsetOfTemporary: i - 1)]]) ifFalse:
+ 					[^true]].
+ 			 liveRegisters := liveRegisters bitOr: (self registerMaskFor: liveRegister)]].
- 				[^true].
- 			 liveRegisters := liveRegisters bitOr: 1 << liveRegister]].
  	^false!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup
  	"At a merge point the cogit expects the stack to be in the same state as fixup's 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.
  	 Generate code to merge the current simStack with that of the target fixup, the goal being to
  	 keep as many registers live as possible."
  	"self printSimStack; printSimStack: fixup mergeSimStack"
  	"self simStackPrintString-> fixup simStackPrintString"
  	"abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
  	<var: #fixup type: #'BytecodeFixup *'>
  	| currentRegisters targetRegisters mergeSimStack current target spillOffset |
  	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  	self assert: simStackPtr = fixup simStackPtr.
  	currentRegisters := self liveRegistersFrom: 0 to: simStackPtr in: simStack.
  	targetRegisters := self liveRegistersFrom: 0 to: simStackPtr in: mergeSimStack.
  	self resolveConflicts: (currentRegisters bitAnd: targetRegisters) with: fixup mergeSimStack to: fixup simStackPtr.
  	self assert: (self conflictsResolvedBetweenSimStackAnd: mergeSimStack).
  	(self pushForMergeWith: mergeSimStack)
  		ifTrue:
  			[0 to: simStackPtr do:
  				[:i|
  				 spillOffset := i > methodOrBlockNumTemps
  									ifTrue: [self frameOffsetOfTemporary: i - 1]
  									ifFalse: [0].
  				 ((current := self simStack: simStack at: i)
  					reconcileWith: (target := self simStack: mergeSimStack at: i)
  					spillOffset: spillOffset
  					onSpillOrUnspill:
  						[:targetReg|
  						 self deny: current spilled.
  						 self assert: spillOffset ~= 0.
  						 current ensureSpilledAt: spillOffset from: FPReg]) ifTrue:
  					[i > methodOrBlockNumTemps ifTrue:
  						[self deassignRegister: current registerOrNone in: mergeSimStack.
+ 						 self deassignRegister: current registerOrNone in: simStack.
  						 self deny: (self register: current registerOrNone
  										isInMask: self liveRegistersInSelfAndTemps)]]]]
  		ifFalse:
  			[simStackPtr to: 0 by: -1 do:
  				[:i|
  				 spillOffset := i > methodOrBlockNumTemps
  									ifTrue: [self frameOffsetOfTemporary: i - 1]
  									ifFalse: [0].
  				 ((current := self simStack: simStack at: i)
  					reconcileWith: (target := self simStack: mergeSimStack at: i)
  					spillOffset: spillOffset
  					onSpillOrUnspill:
  						[:targetReg|
  						 self assert: current spilled.
  						 self assert: spillOffset ~= 0.
  						 targetReg  ~= NoReg
  							ifTrue: [self PopR: targetReg]
  							ifFalse: [self AddCq: objectRepresentation wordSize R: SPReg]]) ifTrue:
  					[i > methodOrBlockNumTemps ifTrue:
  						[self deassignRegister: current registerOrNone in: mergeSimStack.
+ 						 self deassignRegister: current registerOrNone in: simStack.
  						 self deny: (self register: current registerOrNone
  										isInMask: self liveRegistersInSelfAndTemps)]]]].
  	self updateSimSpillBase!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeWithFixupIfRequired: (in category 'simulation stack') -----
  mergeWithFixupIfRequired: fixup
  	"If this bytecode has a fixup, some kind of merge needs to be done. There are 4 cases:
  		1) the bytecode has no fixup (fixup isNotAFixup)
  			do nothing
  		2) the bytecode has a non merge fixup
  			the fixup has needsNonMergeFixup.
  			The code generating non merge fixup (currently only special selector code) is responsible
  				for the merge so no need to do it.
  			We set deadCode to false as the instruction can be reached from jumps.
  		3) the bytecode has a merge fixup, but execution flow *cannot* fall through to the merge point.
  			the fixup has needsMergeFixup and deadCode = true.
  			ignores the current simStack as it does not mean anything 
  			restores the simStack to the state the jumps to the merge point expects it to be.
  		4) the bytecode has a merge fixup and execution flow *can* fall through to the merge point.
  			the fixup has needsMergeFixup and deadCode = false.
  			Merge the state into the fixup's state via mergeCurrentSimStackWith:forwards:.
  			
  	In addition, if this is a backjump merge point, we patch the fixup to hold the current simStackPtr 
  	for later assertions. self printSimStack: fixup mergeSimStack"
  
  	<var: #fixup type: #'BytecodeFixup *'>
  	deadCode ifFalse:
  		[self assertCorrectSimStackPtr].
  
  	"case 1"
  	fixup notAFixup ifTrue:
  		[^0].
  
  	"case 2"
  	fixup isNonMergeFixup ifTrue:
  		[deadCode
  			ifTrue:
  				[self deny: fixup simStackPtr isNil.
  				 simStackPtr := fixup simStackPtr.
  				 self restoreSimStackAtMergePoint: fixup.
  				 deadCode := false.
  				 self assertCorrectSimStackPtr]
  			ifFalse:
  				[self flushRegistersOnlyLiveOnFallThrough: fixup].
  		 ^0].
  
  	"cases 3 and 4"
  	self assert: fixup isMergeFixup.
  	self traceMerge: fixup.
  	deadCode 
  		ifTrue: "case 3"
  			[simStackPtr := fixup simStackPtr.
  			self restoreSimStackAtMergePoint: fixup.
+ 			deadCode := false]
- 			deadCode := false.]
  		ifFalse: "case 4"
  			[(fixup isBackwardBranchFixup and: [compilationPass > 1])
  				ifTrue:
  					[fixup simStackPtr: simStackPtr.
  					 self mergeCurrentSimStackWith: fixup.
  					 self copySimStackToFixup: fixup]
  				ifFalse:
  					[self mergeCurrentSimStackWith: fixup]].
  	"cases 3 and 4"
  	fixup isBackwardBranchFixup ifTrue:
  		[fixup mergeSimStack ifNil:
  			[self assert: compilationPass = 1.
  			 self setMergeSimStackOf: fixup]].
  	fixup targetInstruction: self Label.
  	self assertCorrectSimStackPtr.
  	self assert: (self simStackMergeCompatibleWith: fixup).
+ 	"self simStackPrintString, fixup simStackPrintString"
- 	"self simStackPrintString""fixup simStackPrintString"
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>reinitializeAllButBackwardFixupsFrom:through: (in category 'compile abstract instructions') -----
  reinitializeAllButBackwardFixupsFrom: start through: end
  	"When a method must be recompiled due to moving a loop's register
  	 assignments to the head of a loop, backward fixups must be marked
  	 as such, and all but backward fixups must be reinitialized."
- 	<inline: true>
  	| descriptor nExts pc distance targetPC |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	pc := start.
  	nExts := 0.
  	[pc <= end] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 (descriptor isBranch
  		  and: [self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj]) ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 self initializeFixupAt: targetPC].
  		 descriptor isBlockCreation
  			ifTrue:
  				[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  				 pc := pc + descriptor numBytes + distance]
  			ifFalse: [pc := pc + descriptor numBytes].
  		 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  	start to: end do:
  		[:i| | fixup |
  		 fixup := self fixupAt: i.
  		 (fixup notAFixup or: [fixup isBackwardBranchFixup]) ifFalse:
  			[fixup reinitialize]]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>resetSimStack: (in category 'bytecode generator support') -----
  resetSimStack: startPC
  	<inline: true>
  	simSpillBase := methodOrBlockNumTemps + 1.
  	simStackPtr := methodOrBlockNumTemps.
+ 	0 to: simStackPtr do:
+ 		[:i|
+ 		(self simStackAt: i) liveRegister: NoReg.
+ 		self cCode: '' inSmalltalk: [(self simStackAt: i) bcptr: startPC]]!
- 	self flushLiveRegistersForSend.
- 	self cCode: '' inSmalltalk:
- 		[0 to: methodOrBlockNumTemps do:
- 			[:i|
- 			(self simStackAt: i) bcptr: startPC]]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>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.  If the merge point follows a return, it
  	 isn't a merge, but a skip past a return.  If it is a real merge point then throw
  	 away all simStack optimization state."
  
  	fixup mergeSimStack ifNotNil:
  		[simSpillBase := methodOrBlockNumTemps + 1.
  		 0 to: simStackPtr do:
  			[:i|
  			self cCode: [simStack at: i put: (fixup mergeSimStack at: i)]
+ 				inSmalltalk: [(simStack at: i) copyFrom: (fixup mergeSimStack at: i)]].
+ 		 self updateSimSpillBase].
- 				inSmalltalk: [(simStack at: i) copyFrom: (fixup mergeSimStack at: i)]]].
  	^0!

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: [self maybeCompilingFirstPassOfBlockWithInitialPushNil and: [simSpillBase > methodOrBlockNumArgs]]).
- 				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:
  		[deadCode ifFalse:
  			[self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1])
  						= (self debugStackPointerFor: bytecodePC)]].!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>mergeWithFixupIfRequired: (in category 'simulation stack') -----
  mergeWithFixupIfRequired: fixup
  	"If this bytecode has a fixup, some kind of merge needs to be done. There are 4 cases:
  		1) the bytecode has no fixup (fixup isNotAFixup)
  			do nothing
  		2) the bytecode has a non merge fixup
  			the fixup has needsNonMergeFixup.
  			The code generating non merge fixup (currently only special selector code) is responsible
  				for the merge so no need to do it.
  			We set deadCode to false as the instruction can be reached from jumps.
  		3) the bytecode has a merge fixup, but execution flow *cannot* fall through to the merge point.
  			the fixup has needsMergeFixup and deadCode = true.
  			ignores the current simStack as it does not mean anything 
  			restores the simStack to the state the jumps to the merge point expects it to be.
  		4) the bytecode has a merge fixup and execution flow *can* fall through to the merge point.
  			the fixup has needsMergeFixup and deadCode = false.
  			flushes the stack to the stack pointer so the fall through execution path simStack is 
  				in the state the merge point expects it to be. 
  			restores the simStack to the state the jumps to the merge point expects it to be.
  			
  	In addition, if this is a backjump merge point, we patch the fixup to hold the current simStackPtr 
  	for later assertions."
  	<var: #fixup type: #'BytecodeFixup *'>
  
  	self assertCorrectSimStackPtr.
  
  	"case 1"
  	fixup notAFixup ifTrue:
  		[^0].
  
  	"case 2"
  	fixup isNonMergeFixup ifTrue:
  		[deadCode := false. ^0].
  
  	"cases 3 and 4"
  	self assert: fixup isMergeFixup.
  	self traceMerge: fixup.
  	deadCode
  		ifTrue: "case 3"
  			["Would like to assert fixup simStackPtr >= methodOrBlockNumTemps
  			   but can't because of the initialNils hack."
  			 self assert: (fixup simStackPtr >= methodOrBlockNumTemps
+ 						or: [self maybeCompilingFirstPassOfBlockWithInitialPushNil]).
- 						or: [inBlock = InVanillaBlock]).
  			 simStackPtr := fixup simStackPtr.
  			 LowcodeVM ifTrue:
  				[simNativeStackPtr := fixup simNativeStackPtr.
  				simNativeStackSize := fixup simNativeStackSize]]
  		ifFalse: "case 4"
  			[self ssFlushTo: simStackPtr].
  
  	"cases 3 and 4"
  	deadCode := false.
  	fixup isBackwardBranchFixup ifTrue:
  		[fixup simStackPtr: simStackPtr.
  		LowcodeVM ifTrue:
  			[fixup simNativeStackPtr: simNativeStackPtr.
  			 fixup simNativeStackSize: simNativeStackSize]].
  	fixup targetInstruction: self Label.
  	self assert: simStackPtr = fixup simStackPtr.
  	LowcodeVM ifTrue:
  		[self assert: simNativeStackPtr = fixup simNativeStackPtr.
  		 self assert: simNativeStackSize = fixup simNativeStackSize].
  
  	self cCode: '' inSmalltalk:
  		[self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].
  	self restoreSimStackAtMergePoint: fixup.
  
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateCallReg:and:and: (in category 'simulation stack') -----
  ssAllocateCallReg: requiredReg1 and: requiredReg2 and: requiredReg3
  	"Allocate registers needed in a run-time call (i.e. flush uses of the
  	 registers to the real stack).  Since the run-time can smash any and
  	 all caller-saved registers also flush all caller-saved registers."
+ 	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask bitOr:
+ 										(self registerMaskFor: requiredReg1 and: requiredReg2 and: requiredReg3))
- 	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask
- 										bitOr: ((self registerMaskFor: requiredReg1)
- 										bitOr: ((self registerMaskFor: requiredReg2)
- 										bitOr: (self registerMaskFor: requiredReg3))))
  		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredRegMask:upThrough:upThroughNative: (in category 'simulation stack') -----
  ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr upThroughNative: nativeStackPtr
  	| lastRequired lastRequiredNative liveRegs |
  	lastRequired := -1.
  	lastRequiredNative := -1.
  	"compute live regs while noting the last occurrence of required regs.
  	 If these are not free we must spill from simSpillBase to last occurrence.
  	 Note we are conservative here; we could allocate FPReg in frameless methods."
  	liveRegs := self registerMaskFor: FPReg and: SPReg.
  	(simSpillBase max: 0) to: stackPtr do:
  		[:i|
  		liveRegs := liveRegs bitOr: (self simStackAt: i) registerMask.
+ 		((self simStackAt: i) registerMask anyMask: requiredRegsMask) ifTrue:
- 		((self simStackAt: i) registerMask bitAnd: requiredRegsMask) ~= 0 ifTrue:
  			[lastRequired := i]].
  	LowcodeVM ifTrue:
  		[self assert: nativeStackPtr = simNativeStackPtr.
  		 (simNativeSpillBase max: 0) to: nativeStackPtr do:
  			[:i|
  			liveRegs := liveRegs bitOr: (self simNativeStackAt: i) nativeRegisterMask.
  			((self simNativeStackAt: i) nativeRegisterMask anyMask: requiredRegsMask) ifTrue:
  				[lastRequiredNative := i]]].
  	"If any of requiredRegsMask are live we must spill."
  	(liveRegs anyMask: requiredRegsMask) ifTrue:
  		[self ssFlushTo: lastRequired.
  		 self deny: (self liveRegisters anyMask: requiredRegsMask)]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssFlushTo: (in category 'simulation stack') -----
  ssFlushTo: index
  	<inline: true>
  	self assert: self tempsValidAndVolatileEntriesSpilled.
  	LowcodeVM ifTrue:
  		[self ssNativeFlushTo: simNativeStackPtr].
  	simSpillBase <= index ifTrue:
+ 		[((simSpillBase max: methodOrBlockNumTemps + 1) min: simStackPtr) to: index do:
- 		[(simSpillBase max: methodOrBlockNumTemps + 1) to: index do:
  			[:i|
  			self assert: needsFrame.
  			(self simStackAt: i)
  				ensureSpilledAt: (self frameOffsetOfTemporary: i - 1) "frameOffsetOfTemporary: is 0-relative"
  				from: FPReg].
  		 simSpillBase := index + 1]!

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: [self maybeCompilingFirstPassOfBlockWithInitialPushNil]).
- 				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]!



More information about the Vm-dev mailing list