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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 3 18:49:47 UTC 2016


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

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

Name: VMMaker.oscog-eem.2023
Author: eem
Time: 3 December 2016, 10:48:57.324652 am
UUID: ee0a00bb-160d-4efe-a960-f81681c4012a
Ancestors: VMMaker.oscog-eem.2022

RegisterAllocatingCogit:

Fix a slip in reconcileForwardsWith:; if a constant is merged with something other than the same constant then the resulting stack entry cannot be constant.  This fixes the bug compiling the or: in UnixFileDirectory>>#setPathName:.

Refactor mergeWithFixupIfRequired: & mergeCurrentSimStackWith: to pass fixup so that mergeCurrentSimStackWith: can update isReceiverResultRegSelf correctly.  This fixes the bug accessing array for the second send of #size in WeakSet>>scanFor:.

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

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.  Make sure targetEntry
+ 	 reflects the state of the merged simStack; it will be installed as the current
+ 	 entry by restoreSimStackAtMergePoint: in mergeWithFixupIfRequired:."
- 	 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:
  				[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]] }.
+ 	(targetEntry type = SSConstant
+ 	 and: [type ~= SSConstant or: [constant ~= targetEntry constant]]) ifTrue:
+ 		[targetEntry
+ 			register: targetReg;
+ 			type: SSRegister]!
- 								[cogit MoveR: register R: targetReg]] }!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSen
 dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit>>recordProcessing (in category 'simulation only') -----
  recordProcessing
  	| inst |
  	self recordRegisters.
  	inst := self recordLastInstruction.
+ 	"Set RRRName ito the selector that accesses ReceiverResultReg (RRR) to alter instruction printing to add the value of RRR as a suffix
+ 		(RRRName := #rdx)
+ 		(RRRName := #edx)
+ 		(RRRName := #nil)"
  	printRegisters ifTrue:
+ 		[RRRName ifNil: [processor printRegistersOn: coInterpreter transcript].
- 		[processor printRegistersOn: coInterpreter transcript.
  		 printInstructions ifFalse:
+ 			[coInterpreter transcript cr]].
- 			[coInterpreter transcript cr].].
  	printInstructions ifTrue:
  		[printRegisters ifTrue:
  			[coInterpreter transcript cr].
+ 		 coInterpreter transcript nextPutAll: inst.
+ 		 RRRName ifNotNil:
+ 			[coInterpreter transcript space; nextPutAll: RRRName; space.
+ 			 (processor perform: RRRName) printOn: coInterpreter transcript base: 16 length: 8 padded: false].
+ 		 coInterpreter transcript cr; flush]!
- 		 coInterpreter transcript nextPutAll: inst; cr; flush]!

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]]
- 				ifNotNil: [self mergeCurrentSimStackWith: fixup mergeSimStack]]
  		ifFalse: 
  			[self assert: fixup mergeSimStack isNil.
  			self moveVolatileSimStackEntriesToRegisters.
  			self setMergeSimStackOf: fixup].
  	^super ensureFixupAt: targetIndex!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
+ mergeCurrentSimStackWith: fixup
+ 	<var: #fixup type: #'BytecodeFixup *'>
+ 	| mergeSimStack currentEntry targetEntry |
- mergeCurrentSimStackWith: mergeSimStack
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	"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 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."
- 	| currentEntry targetEntry |
  	<var: #currentEntry type: #'SimStackEntry *'>
  	<var: #targetEntry type: #'SimStackEntry *'>
+ 	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
- 	mergeSimStack ifNil: [^self].
  	"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 resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack.
  	self assert: (self conflcitsResolvedBetweenSimStackAnd: mergeSimStack).
  	simStackPtr to: 0 by: -1 do:
  		[:i|
  		 currentEntry := self simStack: simStack at: i.
  		 targetEntry := self simStack: mergeSimStack at: i.
  		 currentEntry reconcileForwardsWith: targetEntry.
  		 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
  		 spilled ifFalse:
  			[simSpillBase := i - 1].
  		 simStack
  			at: i
  			put: (self
  					cCode: [mergeSimStack at: i]
+ 					inSmalltalk: [(mergeSimStack at: i) copy])"].
+ 
+ 	"a.k.a. fixup isReceiverResultRegSelf: (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
+ 	optStatus isReceiverResultRegLive ifFalse:
+ 		[fixup isReceiverResultRegSelf: false]!
- 					inSmalltalk: [(mergeSimStack at: i) copy])"]!

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.
  			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 *'>
  	"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: [simStackPtr := fixup simStackPtr] "case 3"
+ 		ifFalse: [self mergeCurrentSimStackWith: fixup]. "case 4"
- 		ifFalse: [self mergeCurrentSimStackWith: fixup mergeSimStack]. "case 4"
  	"cases 3 and 4"
  	deadCode := false.
  	fixup isBackwardBranchFixup ifTrue:
  		[self assert: fixup mergeSimStack isNil.
  		 self setMergeSimStackOf: fixup].
  	fixup targetInstruction: self Label.
  	self assert: simStackPtr = fixup simStackPtr.
  	self cCode: '' inSmalltalk:
  		[self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].
  	self restoreSimStackAtMergePoint: fixup.
  	
  	^0!



More information about the Vm-dev mailing list