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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 2 20:53:40 UTC 2016


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

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

Name: VMMaker.oscog-eem.2021
Author: eem
Time: 2 December 2016, 12:52:57.838901 pm
UUID: 79a1fe01-f27f-4839-b390-3b952042f672
Ancestors: VMMaker.oscog-eem.2020

RegisterAllocatingCogit:
Rename moveSimStackConstantsToRegisters to moveVolatileSimStackEntriesToRegisters sicne we also have to capture inst var refs (anything not relative to FPReg).

Fix slip in reconcileForwardsWith:.

ensureNonMergeFixupAt: shoudl only set the mergeSimStack of the fixup if it doesn't yet have one.

When merging we have tio make sure that simSelf's liveRegister is up-to-date, not just optStatus.  Oh how nice it would be to only have simSelf and be able to nuke optStatus. [the issue is having two defs for a simStackEntry in StackToRegisterMappingCogit, one with liveRegister, needed for simSelf, one not, for normal entries].

Get fixups to remember the bytecode pc that set them, and print the bcpc(s).  Add printing simSelf to traceSimStack.

Execution now gets to Process>>popTo: during SmalltalkImage>installLowSpaceWatcher, 187 methods compiled and executed.

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

Item was changed:
  VMStructType subclass: #CogBytecodeFixup
+ 	instanceVariableNames: 'targetInstruction instructionIndex bcpc'
- 	instanceVariableNames: 'targetInstruction instructionIndex'
  	classVariableNames: 'NeedsFixupFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogBytecodeFixup commentStamp: 'eem 1/20/2011 12:41' prior: 0!
  I am a fixup for a bytecode in the Cogit.  Currently fixups are for labels only.  To fixup jumps the cogit places fixups in the fixups array at indices that correspond to bytecodes that are the targets of jumps.  When the cogit encounters a bytecode with a fixup it assigns the fixup's target field to the first generated instruction for the bytecode.  Later when AbstractInstruction Jump* instructions attempt to compute their target they follow the indirection through the fixup to the actual target.!

Item was changed:
  ----- Method: CogBytecodeFixup class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BytecodeFixup struct."
  
  	self allInstVarNames do:
  		[:ivn|
+ 		ivn ~= 'bcpc' ifTrue:
+ 			[aBinaryBlock
+ 				value: ivn
+ 				value: (ivn = 'targetInstruction'
+ 						ifTrue: [#'AbstractInstruction *']
+ 						ifFalse:
+ 							[#sqInt])]]!
- 		aBinaryBlock
- 			value: ivn
- 			value: (ivn = 'targetInstruction'
- 					ifTrue: [#'AbstractInstruction *']
- 					ifFalse:
- 						[#sqInt])]!

Item was added:
+ ----- Method: CogBytecodeFixup>>bcpc (in category 'accessing') -----
+ bcpc
+ 
+ 	^ bcpc!

Item was added:
+ ----- Method: CogBytecodeFixup>>bcpc: (in category 'accessing') -----
+ bcpc: anObject
+ 
+ 	^bcpc := anObject!

Item was changed:
  ----- Method: CogBytecodeFixup>>printStateOn: (in category 'debug printing') -----
  printStateOn: aStream
  	<doNotGenerate>
  	targetInstruction ifNotNil:
+ 		[aStream space; nextPut: $(; print: targetInstruction; nextPutAll: ' bc '; print: bcpc; nextPut: $)]!
- 		[aStream space; nextPut: $(; print: targetInstruction; nextPut: $)]!

Item was added:
+ ----- Method: CogBytecodeFixup>>recordBcpc: (in category 'simulation') -----
+ recordBcpc: bytecodePC
+ 	<inline: true>
+ 	self cCode: '' inSmalltalk:
+ 		[bcpc
+ 			ifNil: [bcpc := bytecodePC]
+ 			ifNotNil:
+ 				[bcpc := bcpc isInteger
+ 							ifTrue: [{bcpc. bytecodePC}]
+ 							ifFalse: [bcpc, {bytecodePC}]]]!

Item was added:
+ ----- Method: CogObjectRepresentation>>wordSize (in category 'accessing') -----
+ wordSize
+ 	<doNotGenerate>
+ 	^objectMemory wordSize!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileForwardsWith: (in category 'compile abstract instructions') -----
  reconcileForwardsWith: targetEntry
  	"Make the state of the receiver, a stack entry at the end of a basic block,
  	 the same as the corresponding simStackEntry at the target of a preceding
  	 jump to the beginning of the next basic block."
  	<var: #targetEntry type: #'targetEntry *'>
  	| targetReg |
  	(targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  		[self assert: (self isSameEntryAs: targetEntry).
  		 ^self].
  	liveRegister ~= NoReg ifTrue:
  		[liveRegister ~= targetReg ifTrue:
  			[cogit MoveR: liveRegister R: targetReg].
  		 (spilled and: [targetEntry spilled not]) ifTrue:
  			[cogit AddCq: objectRepresentation wordSize R: SPReg].
  		 ^self].
  	spilled
  		ifTrue:
+ 			[targetEntry spilled ifFalse:
- 			[targetEntry spilled ifTrue:
  				[cogit PopR: targetReg. "KISS; generate the least number of instructions..."
  				 ^self]]
  		ifFalse:
  			[self deny: targetEntry spilled].
  	type caseOf: {
  		[SSBaseOffset]	-> [cogit MoveMw: offset r: register R: targetReg].
  		[SSSpill]		-> [cogit MoveMw: offset r: register R: targetReg].
  		[SSConstant]	-> [cogit genMoveConstant: constant R: targetReg].
  		[SSRegister]	-> [register ~= targetReg ifTrue:
  								[cogit MoveR: register R: targetReg]] }!

Item was changed:
  ----- Method: CogSSBytecodeFixup>>printStateOn: (in category 'debug printing') -----
  printStateOn: aStream
  	<doNotGenerate>
  	(targetInstruction isNil and: [simStackPtr isNil]) ifTrue:
  		[^self].
  	aStream space; nextPut: $(.
  	targetInstruction ifNotNil:
  		[aStream space; print: targetInstruction].
  	simStackPtr ifNotNil:
+ 		[aStream nextPutAll: ' sp '; print: simStackPtr].
+ 	bcpc ifNotNil:
+ 		[aStream nextPutAll: ' bc '; print: bcpc].
- 		[aStream space; print: simStackPtr].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: Cogit>>ensureFixupAt: (in category 'compile abstract instructions') -----
  ensureFixupAt: targetIndex
  	"Make sure there's a flagged fixup at the targetIndex (pc relative to first pc) in fixups.
  	 Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction."
  	<returnTypeC: #'BytecodeFixup *'>
  	| fixup |
  	<var: #fixup type: #'BytecodeFixup *'>
  	fixup := self fixupAt: targetIndex.
  	fixup notAFixup ifTrue:
  		[fixup becomeFixup].
+ 	fixup recordBcpc: bytecodePC.
  	^fixup!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureFixupAt: (in category 'bytecode generator support') -----
  ensureFixupAt: targetIndex
  	| fixup |	
  	<var: #fixup type: #'BytecodeFixup *'>
  	fixup := self fixupAt: targetIndex.
  	fixup needsFixup 
  		ifTrue:
  			[fixup mergeSimStack
  				ifNil: [self setMergeSimStackOf: fixup]
  				ifNotNil: [self mergeCurrentSimStackWith: fixup mergeSimStack]]
  		ifFalse: 
  			[self assert: fixup mergeSimStack isNil.
+ 			self moveVolatileSimStackEntriesToRegisters.
+ 			self setMergeSimStackOf: fixup].
+ 	^super ensureFixupAt: targetIndex!
- 			self moveSimStackConstantsToRegisters.
- 			self setMergeSimStackOf: fixup ].
- 	^super ensureFixupAt: targetIndex.
- !

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureNonMergeFixupAt: (in category 'compile abstract instructions') -----
  ensureNonMergeFixupAt: targetIndex
  	"Make sure there's a flagged fixup at the targetIndex (pc relative to first pc) in fixups.
  	 Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction."
  	| fixup |
  	fixup := super ensureNonMergeFixupAt: targetIndex.
+ 	fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup].
- 	self setMergeSimStackOf: fixup.
  	^fixup!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>moveSimStackConstantsToRegisters (in category 'bytecode generator support') -----
- moveSimStackConstantsToRegisters
- 	<inline: true>
- 	<var: #desc type: #'SimStackEntry *'>
- 	self flag: 'I think this should be done at the merge point if required.  e.g. self at: 1 put: (expr ifTrue: [a] ifFalse: [b]) does not need to assign'. 
- 	(simSpillBase max: 0) to: simStackPtr do: 
- 		[:i| | desc reg |
- 		 desc := self simStackAt: i.
- 		 (desc type = SSConstant and: [desc liveRegister = NoReg]) ifTrue:
- 			[reg := self allocateRegNotConflictingWith: 0.
- 			 reg ~= NoReg ifTrue:
- 				[desc storeToReg: reg]]]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>moveVolatileSimStackEntriesToRegisters (in category 'bytecode generator support') -----
+ moveVolatileSimStackEntriesToRegisters
+ 	"When jumping forward to a merge point the stack mst 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.]
+ 	 Volatile contents are constants and base-offset references other than temporaries and spills (regsier ~= FPReg)"
+ 	<inline: true>
+ 	<var: #desc type: #'SimStackEntry *'>
+ 	(simSpillBase max: 0) to: simStackPtr do: 
+ 		[:i| | desc reg |
+ 		 desc := self simStackAt: i.
+ 		 ((desc type = SSConstant or: [desc type = SSBaseOffset and: [desc register ~= FPReg]])
+ 		  and: [desc liveRegister = NoReg]) ifTrue:
+ 			[reg := self allocateRegNotConflictingWith: 0.
+ 			 reg = NoReg
+ 				ifTrue: [self halt] "have to spill"
+ 				ifFalse: [desc storeToReg: reg]]]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>reconcileRegisterStateForJoinAfterSpecialSelectorSend (in category 'bytecode generator support') -----
  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]
+ 			ifFalse:
+ 				[optStatus isReceiverResultRegLive: false.
+ 				 optStatus ssEntry liveRegister: NoReg]].
- 			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:
  		[:i|
  		 self assert: (i = simStackPtr
  						ifTrue: [(self simStackAt: i) type = SSRegister]
  						ifFalse: [(self simStackAt: i) spilled]).
  		 (self simStackAt: i) reconcilePoppingWith: (self simStack: scratchSimStack at: i).
  		 simStack
  			at: i
  			put: (self
  					cCode: [scratchSimStack at: i]
  					inSmalltalk: [(scratchSimStack at: i) copy])]!

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 and optStatus optimization state."
+ 	(optStatus isReceiverResultRegLive: fixup isReceiverResultRegSelf) ifFalse:
+ 		[simSelf liveRegister: NoReg].
- 	optStatus isReceiverResultRegLive: fixup isReceiverResultRegSelf.
  	fixup mergeSimStack ifNotNil:
  		[simSpillBase := methodOrBlockNumTemps.
  		 0 to: simStackPtr do:
  			[:i|
  			self cCode: [simStack at: i put: (fixup mergeSimStack at: i)]
  				inSmalltalk: [(simStack at: i) copyFrom: (fixup mergeSimStack at: i)]]].
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>setMergeSimStackOf: (in category 'bytecode generator support') -----
  setMergeSimStackOf: fixup
  	<var: #fixup type: #'BytecodeFixup *'>
+ 	self moveVolatileSimStackEntriesToRegisters.
- 	self moveSimStackConstantsToRegisters.
  	fixup mergeSimStack
  		ifNil:
  			[self assert: nextFixup <= numFixups.
  			 self cCode: [fixup mergeSimStack: mergeSimStacksBase + (nextFixup * self simStackSlots * (self sizeof: CogSimStackEntry))].
  			 nextFixup := nextFixup + 1]
  		ifNotNil:
  			[self assert: fixup simStackPtr = simStackPtr.
  			 0 to: simStackPtr do:
  				[:i|
  				self assert: ((self simStackAt: i) isSameEntryAs: (fixup mergeSimStack at: i)).
  				(self simStackAt: i) liveRegister ~= (fixup mergeSimStack at: i) liveRegister ifTrue:
  					[(self simStackAt: i) liveRegister: NoReg]]].
  	fixup
  		simStackPtr: simStackPtr;
  		isReceiverResultRegSelf: optStatus isReceiverResultRegLive.
  	self cCode: [self mem: fixup mergeSimStack cp: simStack y: self simStackSlots * (self sizeof: CogSimStackEntry)]
  		inSmalltalk: [fixup mergeSimStack: self copySimStack]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ensureFixupAt: (in category 'compile abstract instructions') -----
  ensureFixupAt: targetIndex
  	"Make sure there's a flagged fixup at the targetIndex (pc relative to first pc) in fixups.
  	 Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction."
  	<returnTypeC: #'BytecodeFixup *'>
  	| fixup |
  	<var: #fixup type: #'BytecodeFixup *'>
  	fixup := self fixupAt: targetIndex.
  	self traceFixup: fixup.
  	self cCode: '' inSmalltalk:
  		[self assert: simStackPtr = (self debugStackPointerFor: targetIndex + initialPC).
  		 (fixup isMergeFixupOrIsFixedUp
  		  and: [fixup isBackwardBranchFixup not]) ifTrue: "ignore backward branch targets"
  			[self assert: fixup simStackPtr = simStackPtr]].
  	fixup isNonMergeFixupOrNotAFixup
  		ifTrue: "convert a non-merge into a merge"
  			[fixup becomeMergeFixup.
  			 fixup simStackPtr: simStackPtr.
  			 LowcodeVM ifTrue: [
  				 fixup simNativeStackPtr: simNativeStackPtr.
+ 				 fixup simNativeStackSize: simNativeStackSize]]
- 				 fixup simNativeStackSize: simNativeStackSize.]]
  		ifFalse:
  			[fixup isBackwardBranchFixup
+ 				ifTrue: "this is the target of a backward branch and
- 				ifTrue: ["this is the target of a backward branch and
  						 so doesn't have a simStackPtr assigned yet."
+ 						[fixup simStackPtr: simStackPtr.
+ 			 			 LowcodeVM ifTrue:
+ 				 			[fixup simNativeStackPtr: simNativeStackPtr.
+ 				 			 fixup simNativeStackSize: simNativeStackSize]]
+ 				ifFalse:
+ 					[self assert: fixup simStackPtr = simStackPtr.
+ 					 LowcodeVM ifTrue:
+ 				 		[self assert: fixup simNativeStackPtr = simNativeStackPtr.
+ 		 			 	 self assert: fixup simNativeStackSize = simNativeStackSize]]].
+ 	fixup recordBcpc: bytecodePC.
- 						fixup simStackPtr: simStackPtr.
- 			 			LowcodeVM ifTrue: [
- 				 			fixup simNativeStackPtr: simNativeStackPtr.
- 				 			fixup simNativeStackSize: simNativeStackSize.]]
- 				ifFalse: [
- 					self assert: fixup simStackPtr = simStackPtr.
- 					LowcodeVM ifTrue: [
- 				 		self assert: fixup simNativeStackPtr = simNativeStackPtr.
- 		 			 	self assert: fixup simNativeStackSize = simNativeStackSize.]]].
  	^fixup!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushReceiverBytecode (in category 'bytecode generators') -----
  genPushReceiverBytecode
  	optStatus isReceiverResultRegLive ifTrue:
  		[^self ssPushRegister: ReceiverResultReg].
+ 	self assert: simSelf liveRegister = NoReg.
  	^self ssPushDesc: simSelf!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>printSimSelf (in category 'simulation only') -----
+ printSimSelf
+ 	<doNotGenerate>
+ 	coInterpreter transcript ensureCr; nextPutAll: 'self: '.
+ 	simSelf printStateOn: coInterpreter transcript.
+ 	coInterpreter transcript cr; flush!

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



More information about the Vm-dev mailing list