[Vm-dev] VM Maker: VMMaker.oscog-cb.1810.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Apr 16 01:07:02 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1810.mcz

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

Name: VMMaker.oscog-cb.1810
Author: cb
Time: 15 April 2016, 6:05:26.586463 pm
UUID: 2e5fb6e7-e3a1-44ce-86ed-3a699b5bfc8f
Ancestors: VMMaker.oscog-eem.1809

- Made explicit messages related to bytecode fixup (abstract away from integer flags)
- Introduced RegisterAllocatingCogit, though it is not complete yet.
- rename vars in alloca methods.

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

Item was changed:
  VMStructType subclass: #CogBytecodeFixup
  	instanceVariableNames: 'targetInstruction instructionIndex'
+ 	classVariableNames: 'NeedsFixupFlag'
- 	classVariableNames: ''
  	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 added:
+ ----- Method: CogBytecodeFixup class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Initialize the fixup flags.  In this class we have only one flag, 1, which
+ 	 means set the fixup to point to the first instruction for a particular bytecode.
+ 	 A forward branch from one bytecode to a later one will set its jmpTarget to
+ 	 a fixup.  later, in compileAbstractInstructionsFrom:to:, any fixup with its
+ 	 targetInstruction set to NeedsFixupFlag will have its targetInstruction set
+ 	 to the first bytecode of the sequence.  Later still, when code is generated
+ 	 jumps follow fixups to eliminate the fixup and target the rigth instruction."
+ 	NeedsFixupFlag := 1!

Item was added:
+ ----- Method: CogBytecodeFixup>>becomeFixup (in category 'converting') -----
+ becomeFixup
+ 	<inline: true>
+ 	targetInstruction := self cCoerceSimple: NeedsFixupFlag to: #'AbstractInstruction *'!

Item was added:
+ ----- Method: CogBytecodeFixup>>cCoerceSimple:to: (in category 'coercion') -----
+ cCoerceSimple: flagOrAbstractOp to: cType
+ 	<doNotGenerate>
+ 	^ flagOrAbstractOp!

Item was added:
+ ----- Method: CogBytecodeFixup>>needsFixup (in category 'testing') -----
+ needsFixup
+ 	<inline: true>
+ 	^ targetInstruction asInteger = NeedsFixupFlag!

Item was added:
+ ----- Method: CogBytecodeFixup>>notAFixup (in category 'testing') -----
+ notAFixup
+ 	<inline: true>
+ 	^ targetInstruction = 0!

Item was added:
+ CogSSBytecodeFixup subclass: #CogRASSBytecodeFixup
+ 	instanceVariableNames: 'mergeFixup'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogRASSBytecodeFixup class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogRASSBytecodeFixup struct."
+ 
+ 	self allInstVarNames do:
+ 		[:ivn|
+ 		aBinaryBlock
+ 			value: ivn
+ 			value: (ivn caseOf: {
+ 					['targetInstruction']	-> [#'AbstractInstruction *'].
+ 					['mergeFixup']		-> [#'CogSimStackEntry *'] }
+ 					otherwise: [#sqInt])]!

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

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

Item was changed:
  CogBytecodeFixup subclass: #CogSSBytecodeFixup
  	instanceVariableNames: 'simStackPtr'
+ 	classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag UnknownSimStackPtrFlag'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogSSBytecodeFixup commentStamp: 'eem 1/20/2011 13:03' prior: 0!
  A CogSSBytecodeFixup extends CogBytecodeFixup with state to merge the stack at control-flow joins.  At a join the code generator must ensure that the stack is spilled to the same point along both branches and that the simStackPtr is correct.
  
  Instance Variables
  	simStackPtr:		<Integer>
  
  simStackPtr
  	- the simStackPtr at the jump to this fixup.  It should either agree with the incoming fixup if control continues, or replace the simStackPtr if contrl doesn't continue (the incomming control flow ended with a return)!

Item was added:
+ ----- Method: CogSSBytecodeFixup class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Initialize the fixup flags.  In this class we have two states.  A fixup is a bytecode
+ 	 being targeted by a branch, and a jump can target the fixup before the byetcode
+ 	 is generated.  A non-merge fixup is that for a bytecode that follows a return instruction.
+ 	 There is no control flow merge from the preceding instruction for this kind of fixup.
+ 	 A merge fixup is that for a bytecode where control flow arrives from both the preceding
+ 	 instruction and a branch.  When compileAbstractInstructionsFrom:to: finds a merge
+ 	 fixup, it must both set the targetInstruction and merge the stack/register state of the
+ 	 control flow from the preceding instruction with the stack/register state from the branch.
+ 	 Later still, when code is generated jumps follow fixups to eliminate the fixup and target
+ 	 the right instruction."
+ 	NeedsNonMergeFixupFlag := 1.
+ 	NeedsMergeFixupFlag := 2.
+ 	self assert: NeedsNonMergeFixupFlag < NeedsMergeFixupFlag.
+ 
+ 	UnknownSimStackPtrFlag := -2!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>becomeMergeFixup (in category 'converting') -----
+ becomeMergeFixup
+ 	<inline: true>
+ 	targetInstruction := self cCoerceSimple: NeedsMergeFixupFlag to: #'AbstractInstruction *'!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>becomeNonMergeFixup (in category 'converting') -----
+ becomeNonMergeFixup
+ 	<inline: true>
+ 	targetInstruction := self cCoerceSimple: NeedsNonMergeFixupFlag to: #'AbstractInstruction *'!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>isBackwardBranchFixup (in category 'testing') -----
+ isBackwardBranchFixup
+ 	<inline: true>
+ 	^ simStackPtr = UnknownSimStackPtrFlag!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>isMergeFixupOrIsFixedUp (in category 'testing') -----
+ isMergeFixupOrIsFixedUp
+ 	<inline: true>
+ 	^ targetInstruction asUnsignedInteger >= NeedsMergeFixupFlag!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>isNonMergeFixupOrNotAFixup (in category 'testing') -----
+ isNonMergeFixupOrNotAFixup
+ 	<inline: true>
+ 	^ targetInstruction asUnsignedInteger <= NeedsNonMergeFixupFlag!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>needsFixup (in category 'testing') -----
+ needsFixup
+ 	<inline: true>
+ 	^ targetInstruction asUnsignedInteger between: NeedsNonMergeFixupFlag and: NeedsMergeFixupFlag!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>needsFixupOrIsFixedUp (in category 'testing') -----
+ needsFixupOrIsFixedUp
+ 	<inline: true>
+ 	^ targetInstruction asUnsignedInteger > 0!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>notYetFixedUp (in category 'testing') -----
+ notYetFixedUp
+ 	<inline: true>
+ 	^ targetInstruction asUnsignedInteger <= NeedsMergeFixupFlag!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>reinitialize (in category 'accessing') -----
+ reinitialize
+ 	<inline: true>
+ 	targetInstruction := 0.
+ 	simStackPtr := 0.!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>setIsBackwardBranchFixup (in category 'accessing') -----
+ setIsBackwardBranchFixup
+ 	<inline: true>
+ 	simStackPtr := UnknownSimStackPtrFlag!

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 callerSavedRegMask 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 cPICEndSize 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 superSendTrampolines 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'
+ 	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 MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
- 	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 MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated 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>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
  	"Allocate the various arrays needed to compile abstract instructions, failing if the size
  	 needed is considered too high.  Notionally we only need as many fixups as there are
  	 bytecodes.  But we reuse fixups to record pc-dependent instructions in
  	 generateInstructionsAt: and so need at least as many as there are abstract opcodes.
  
  	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
  	 so that they are freed when compilation is done.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<inline: true>
+ 	| opcodeBytes fixupBytes allocBytes |
- 	| opcodeSize fixupSize allocSize |
  	numAbstractOpcodes := numberOfAbstractOpcodes.
+ 	opcodeBytes := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
+ 	fixupBytes := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
+ 	allocBytes := opcodeBytes + fixupBytes.
+ 	allocBytes > MaxStackAllocSize ifTrue: [^failBlock value].
- 	opcodeSize := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
- 	fixupSize := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
- 	allocSize := opcodeSize + fixupSize.
- 	allocSize > MaxStackAllocSize ifTrue: [^failBlock value].
  	self
  		cCode:
+ 			[abstractOpcodes := self alloca: allocBytes.
+ 			 self b: abstractOpcodes zero: allocBytes.
+ 			 fixups := (abstractOpcodes asUnsignedInteger + opcodeBytes) asVoidPointer]
- 			[abstractOpcodes := self alloca: allocSize.
- 			 self b: abstractOpcodes zero: allocSize.
- 			 fixups := (abstractOpcodes asUnsignedInteger + opcodeSize) asVoidPointer]
  		inSmalltalk:
  			[abstractOpcodes := CArrayAccessor on:
  									 ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
  			 fixups := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass new])].
  	self zeroOpcodeIndex.
  	labelCounter := 0!

Item was changed:
  ----- Method: Cogit>>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."
  	| nextOpcodeIndex descriptor fixup result nExts |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	bytecodePC := start.
  	nExts := result := 0.
  	[self cCode: '' inSmalltalk:
  		[(debugBytecodePointers includes: bytecodePC) ifTrue: [self halt]].
  	 byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj)  + bytecodeSetOffset.
  	 descriptor := self generatorAt: byte0.
  	 self loadSubsequentBytesForDescriptor: descriptor at: bytecodePC.
  	 nextOpcodeIndex := opcodeIndex.
  	 result := self perform: descriptor generator.
  	 descriptor isExtension ifFalse: "extended bytecodes must consume their extensions"
  		[self assert: (extA = 0 and: [extB = 0])].
  	 fixup := self fixupAt: bytecodePC - initialPC.
+ 	 fixup needsFixup ifTrue:
- 	 fixup targetInstruction ~= 0 ifTrue:
  		["There is a fixup for this bytecode.  It must point to the first generated
  		   instruction for this bytecode.  If there isn't one we need to add a label."
+ 		 opcodeIndex = nextOpcodeIndex ifTrue: [self Label].
- 		 opcodeIndex = nextOpcodeIndex ifTrue:
- 			[self Label].
  		 fixup targetInstruction: (self abstractInstructionAt: nextOpcodeIndex)].
  	 self maybeDumpLiterals: descriptor.
  	 bytecodePC := self nextBytecodePCFor: descriptor at: bytecodePC exts: nExts in: methodObj.
  	 result = 0 and: [bytecodePC <= end]]
  		whileTrue:
  			[nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  	self checkEnoughOpcodes.
  	^result!

Item was changed:
  ----- Method: Cogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
  compileEntireFullBlockMethod: numCopied
+ 	"Compile the abstract instructions for the entire full block method."
- 	"Compile the abstract instructions for the entire method, including blocks."
  	<option: #SistaV1BytecodeSet>
  	| result |
  	self preenMethodLabel.
  	self compileFullBlockEntry.
  
  	"Frame build"
  	self compileFullBlockMethodFrameBuild: numCopied.
  	"Method body"
  	(result := self compileMethodBody) < 0 ifTrue:
  		[^result].
  	self assert: blockCount = 0.
  	^0!

Item was changed:
  ----- Method: Cogit>>computeFullBlockEntryOffsets (in category 'initialization') -----
  computeFullBlockEntryOffsets
  	"Generate the entry code for a method to determine cmEntryOffset and cmNoCheckEntryOffset.  We
  	 need cmNoCheckEntryOffset up front to be able to generate the map starting from cmNoCheckEntryOffset"
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
+ 	SistaV1BytecodeSet ifTrue:
+ 		[self allocateOpcodes: 24 bytecodes: 0.
+ 		 methodOrBlockNumArgs := 0.
+ 		 self compileFullBlockEntry.
+ 		 self computeMaximumSizes.
+ 		 self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
+ 		 cbEntryOffset := fullBlockEntry address - methodZoneBase.
+ 		 cbNoSwitchEntryOffset := fullBlockNoContextSwitchEntry address - methodZoneBase]!
- 	self allocateOpcodes: 24 bytecodes: 0.
- 	methodOrBlockNumArgs := 0.
- 	self compileFullBlockEntry.
- 	self computeMaximumSizes.
- 	self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
- 	cbEntryOffset := fullBlockEntry address - methodZoneBase.
- 	cbNoSwitchEntryOffset := fullBlockNoContextSwitchEntry address - methodZoneBase!

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 targetInstruction = 0 ifTrue:
- 		[fixup targetInstruction: (self cCoerceSimple: 1 to: #'AbstractInstruction *')].
  	^fixup!

Item was changed:
  ----- Method: Cogit>>initializeFixupAt: (in category 'compile abstract instructions') -----
  initializeFixupAt: 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 *'>
+ 	(self fixupAt: targetIndex) becomeFixup!
- 	| fixup |
- 	<var: #fixup type: #'BytecodeFixup *'>
- 	fixup := self fixupAt: targetIndex.
- 	fixup targetInstruction: (self cCoerceSimple: 1 to: #'AbstractInstruction *').
- 	^fixup!

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

Item was added:
+ ----- Method: RegisterAllocatingCogit>>allocateMergeFixups (in category 'compile abstract instructions') -----
+ allocateMergeFixups
+ 	"Allocate the various arrays needed to allocate the merge fixups, failing if the size
+ 	 needed is considered too high.
+ 
+ 	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
+ 	 so that they are freed when compilation is done.
+ 
+ 	 N.B. We do one single alloca to save embarrassing C optimizers that
+ 	 generate incorrect code as both gcc and the intel compiler do on x86."
+ 	<inline: true>
+ 	| mergeSimStackBytes |
+ 	mergeSimStackBytes := numFixups * self  simStackSlots.
+ 	self cCode:
+ 		[mergeSimStacksBase := self alloca: mergeSimStackBytes.
+ 		 self b: mergeSimStacksBase zero: mergeSimStackBytes]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>bytecodeFixupClass (in category 'simulation only') -----
+ bytecodeFixupClass
+ 	<doNotGenerate>
+ 	^CogRASSBytecodeFixup!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileEntireFullBlockMethod: numCopied
+ 	"Compile the abstract instructions for the entire full block method."
+ 	self allocateMergeFixups.
+ 	^super compileEntireFullBlockMethod: numCopied!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>compileEntireMethod (in category 'compile abstract instructions') -----
+ compileEntireMethod
+ 	"Compile the abstract instructions for the entire method, including blocks."
+ 	self allocateMergeFixups.
+ 	^super compileEntireMethod!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>genJumpTo: (in category 'bytecode generator support') -----
+ genJumpTo: targetBytecodePC
+ 	self assert: simStackPtr <= (simSpillBase + 1). "Only 1 spilledValue max".
+ 	"Self ssFlushTo: simStackPtr"
+ 	self Jump: (self ensureFixupAt: targetBytecodePC - initialPC).
+ 	^ 0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>scanMethod (in category 'compile abstract instructions') -----
+ scanMethod
+ 	"Overrides to count the number of fixups."
+ 	"Scan the method (and all embedded blocks) to determine
+ 		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
+ 		- if the method needs a frame or not
+ 		- what are the targets of any backward branches.
+ 		- how many blocks it creates
+ 	 Answer the block count or on error a negative error code"
+ 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	needsFrame := false.
+ 	numFixups := 0.
+ 	prevBCDescriptor := nil.
+ 	NewspeakVM ifTrue:
+ 		[numIRCs := 0].
+ 	(primitiveIndex > 0
+ 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
+ 		[^0].
+ 	pc := latestContinuation := initialPC.
+ 	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
+ 	[pc <= endPC] whileTrue:
+ 		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
+ 		 descriptor := self generatorAt: byte0.
+ 		 descriptor isExtension ifTrue:
+ 			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
+ 				[^EncounteredUnknownBytecode].
+ 			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
+ 			 self perform: descriptor generator].
+ 		 (descriptor isReturn
+ 		  and: [pc >= latestContinuation]) ifTrue:
+ 			[endPC := pc].
+ 		 needsFrame ifFalse:
+ 			[(descriptor needsFrameFunction isNil
+ 			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
+ 				ifTrue: [needsFrame := true]
+ 				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
+ 		 descriptor isBranch ifTrue:
+ 			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
+ 			 targetPC := pc + descriptor numBytes + distance.
+ 			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
+ 				ifTrue: [self initializeFixupAt: targetPC - initialPC]
+ 				ifFalse: 
+ 					[latestContinuation := latestContinuation max: targetPC.
+ 					numFixups := numFixups + 1]].
+ 		 descriptor isBlockCreation ifTrue:
+ 			[numBlocks := numBlocks + 1.
+ 			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
+ 			 targetPC := pc + descriptor numBytes + distance.
+ 			 latestContinuation := latestContinuation max: targetPC.
+ 			 numFixups := numFixups + 1].
+ 		 NewspeakVM ifTrue:
+ 			[descriptor hasIRC ifTrue:
+ 				[numIRCs := numIRCs + 1]].
+ 		 pc := pc + descriptor numBytes.
+ 		 descriptor isExtension
+ 			ifTrue: [nExts := nExts + 1]
+ 			ifFalse: [nExts := extA := extB := 0].
+ 		 prevBCDescriptor := descriptor].
+ 	^numBlocks!

Item was changed:
+ RegisterAllocatingCogit subclass: #SistaStackToRegisterMappingCogit
- StackToRegisterMappingCogit subclass: #SistaStackToRegisterMappingCogit
  	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue ceTrapTrampoline branchReachedOnlyForCounterTrip'
  	classVariableNames: 'CounterBytes MaxCounterValue'
  	poolDictionaries: 'VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!
  
  !SistaStackToRegisterMappingCogit commentStamp: 'eem 4/7/2014 12:23' prior: 0!
  A SistaStackToRegisterMappingCogit is a refinement of StackToRegisterMappingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
  
  The basic scheme is that SistaStackToRegisterMappingCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
  
  SistaStackToRegisterMappingCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
  
  SistaStackToRegisterMappingCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
  
  Instance Variables
  	counterIndex:			<Integer>
  	counterMethodCache:	<CogMethod>
  	counters:				<Array of AbstractInstruction>
  	initialCounterValue:		<Integer>
  	numCounters:			<Integer>
  	picData:				<Integer Oop>
  	picDataIndex:			<Integer>
  	prevMapAbsPCMcpc:	<Integer>
  
  counterIndex
  	- xxxxx
  
  counterMethodCache
  	- xxxxx
  
  counters
  	- xxxxx
  
  initialCounterValue
  	- xxxxx
  
  numCounters
  	- xxxxx
  
  picData
  	- xxxxx
  
  picDataIndex
  	- xxxxx
  
  prevMapAbsPCMcpc
  	- xxxxx
  !

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
  	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpEqual type: #'AbstractInstruction *'>
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  
  	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
  		[^super genSpecialSelectorEqualsEqualsWithForwarders].
  
  	regMask := 0.
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  	
  	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
  	register so the forwarder check can jump back to the comparison after unforwarding the constant.
  	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
  	(machine code will use operations on constants)."
  	rcvrReg:= argReg := NoReg.
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
  		rcvrNeedsReg: unforwardRcvr 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  		
  	argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ].
  	rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
  	
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
  	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
  	
  	counterReg := self allocateRegNotConflictingWith: regMask.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  	
  	self assert: (unforwardArg or: [ unforwardRcvr ]).
  	
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	
  	self ssPop: 2.
  	
  	branchDescriptor isBranchTrue 
  		ifTrue: 
  			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
  			self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. ]
  		ifFalse: 
  			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
  			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. ].
  	
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	self Jump: fixup.
  	
  	countTripped jmpTarget: self Label.
  	
  	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
  	self ssPop: -2. 
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2. 
  	
  	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
  	We therefore directly assign the result to TempReg to save one move instruction"
  	jumpEqual := self JumpZero: 0.
  	self genMoveFalseR: TempReg.
  	jumpNotEqual := self Jump: 0.
  	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
  	jumpNotEqual jmpTarget: self Label.
  	self ssPushRegister: TempReg.
  	
+ 	(self fixupAt: nextPC - initialPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
- 	(self fixupAt: nextPC - initialPC) targetInstruction = 0 ifTrue: [ branchReachedOnlyForCounterTrip := true ].
  	
  	^ 0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- how many counters it needs/conditional branches it contains
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
+ 	numFixups := 0.
  	prevBCDescriptor := nil.
  	numCounters := 0.
  	NewspeakVM ifTrue:
  		[numIRCs := 0].
  	(primitiveIndex > 0
  	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse:
  					[latestContinuation := latestContinuation max: targetPC.
+ 					numFixups := numFixups + 1.
  					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  						[numCounters := numCounters + 1]]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
+ 			 latestContinuation := latestContinuation max: targetPC.
+ 			 numFixups := numFixups + 1].
- 			 latestContinuation := latestContinuation max: targetPC].
  		 NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!

Item was changed:
  SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
  	instanceVariableNames: 'prevBCDescriptor numPushNilsFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
+ 	classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag'
- 	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
  
  !StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 0!
  StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
  
  See methods in the class-side documentation protocol for more detail.
  
  Instance Variables
  	callerSavedRegMask:							<Integer>
  	ceEnter0ArgsPIC:								<Integer>
  	ceEnter1ArgsPIC:								<Integer>
  	ceEnter2ArgsPIC:								<Integer>
  	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
  	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	debugBytecodePointers:						<Set of Integer>
  	debugFixupBreaks:								<Set of Integer>
  	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
  	methodAbortTrampolines:						<CArrayAccessor of Integer>
  	methodOrBlockNumTemps:						<Integer>
  	optStatus:										<Integer>
  	picAbortTrampolines:							<CArrayAccessor of Integer>
  	picMissTrampolines:							<CArrayAccessor of Integer>
  	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
  	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	regArgsHaveBeenPushed:						<Boolean>
  	simSelf:											<CogSimStackEntry>
  	simSpillBase:									<Integer>
  	simStack:										<CArrayAccessor of CogSimStackEntry>
  	simStackPtr:									<Integer>
  	traceSimStack:									<Integer>
  
  callerSavedRegMask
  	- the bitmask of the ABI's caller-saved registers
  
  ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
  	- the trampoline for entering an N-arg PIC
  
  ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
  	- teh trampoline for entering a method with N register args
  	
  debugBytecodePointers
  	- a Set of bytecode pcs for setting breakpoints (simulation only)
  
  debugFixupBreaks
  	- a Set of fixup indices for setting breakpoints (simulation only)
  
  debugStackPointers
  	- an Array of stack depths for each bytecode for code verification
  
  methodAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  methodOrBlockNumTemps
  	- the number of method or block temps (including args) in the current compilation unit (method or block)
  
  optStatus
  	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
  
  picAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  picMissTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
  	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
  
  regArgsHaveBeenPushed
  	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
  
  simSelf
  	- the simulation stack entry representing self in the current compilation unit
  
  simSpillBase
  	- the variable tracking how much of the simulation stack has been spilled to the real stack
  
  simStack
  	- the simulation stack itself
  
  simStackPtr
  	- the pointer to the top of the simulation stack
  !
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	^(super ancilliaryClasses: options),
+ 	  { self basicNew bytecodeFixupClass. CogSimStackEntry. CogSSOptStatus }!
- 	  { CogSSBytecodeFixup. CogSimStackEntry. CogSSOptStatus }!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
  	aCodeGen
  		var: #methodAbortTrampolines
  			declareC: 'sqInt methodAbortTrampolines[4]';
  		var: #picAbortTrampolines
  			declareC: 'sqInt picAbortTrampolines[4]';
  		var: #picMissTrampolines
  			declareC: 'sqInt picMissTrampolines[4]';
  		var: 'ceCall0ArgsPIC'
  			declareC: 'void (*ceCall0ArgsPIC)(void)';
  		var: 'ceCall1ArgsPIC'
  			declareC: 'void (*ceCall1ArgsPIC)(void)';
  		var: 'ceCall2ArgsPIC'
  			declareC: 'void (*ceCall2ArgsPIC)(void)';
  		var: #ceCallCogCodePopReceiverArg0Regs
  			declareC: 'void (*ceCallCogCodePopReceiverArg0Regs)(void)';
  		var: #realCECallCogCodePopReceiverArg0Regs
  			declareC: 'void (*realCECallCogCodePopReceiverArg0Regs)(void)';
  		var: #ceCallCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*ceCallCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: #realCECallCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*realCECallCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: 'simStack'
+ 			declareC: 'CogSimStackEntry simStack[', self simStackSlots asString, ']';
- 			declareC: 'CogSimStackEntry simStack[', ((CoInterpreter bindingOf: #LargeContextSlots) value * 5 // 4) asString, ']';
  		var: 'simSelf'
  			type: #CogSimStackEntry;
  		var: #optStatus
  			type: #CogSSOptStatus;
  		var: 'prevBCDescriptor'
  			type: #'BytecodeDescriptor *'.
  
  	self numPushNilsFunction ifNotNil:
  		[aCodeGen
  			var: 'numPushNilsFunction'
  				declareC: 'sqInt (* const numPushNilsFunction)(struct _BytecodeDescriptor *,sqInt,sqInt,sqInt) = ', (aCodeGen cFunctionNameFor: self numPushNilsFunction);
  			var: 'pushNilSizeFunction'
  				declareC: 'sqInt (* const pushNilSizeFunction)(sqInt,sqInt) = ', (aCodeGen cFunctionNameFor: self pushNilSizeFunction)].
  
  	aCodeGen
  		addSelectorTranslation: #register to: (aCodeGen cFunctionNameFor: 'registerr');
  		addSelectorTranslation: #register: to: (aCodeGen cFunctionNameFor: 'registerr:')!

Item was added:
+ ----- Method: StackToRegisterMappingCogit class>>simStackSlots (in category 'translation') -----
+ simStackSlots
+ 	^ self basicNew simStackSlots!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>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."
  	| nextOpcodeIndex descriptor nExts fixup result |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	self traceSimStack.
  	bytecodePC := start.
  	nExts := 0.
  	descriptor := nil.
  	deadCode := false.
  	[self cCode: '' inSmalltalk:
  		[(debugBytecodePointers includes: bytecodePC) ifTrue: [self halt]].
  	fixup := self fixupAt: bytecodePC - initialPC.
  	"If there's no fixup following a return there's no jump to that code and it is dead."
  	(descriptor notNil and: [descriptor isReturn]) ifTrue: [deadCode := true].
+ 	fixup needsFixupOrIsFixedUp ifTrue:
+ 		[fixup isMergeFixupOrIsFixedUp ifTrue:
- 	fixup targetInstruction asUnsignedInteger > 0 ifTrue:
- 		[fixup targetInstruction asUnsignedInteger >= 2 ifTrue:
  			[self merge: fixup afterContinuation: deadCode not].
  		deadCode := false].
  	 self cCode: '' inSmalltalk:
  		[deadCode ifFalse:
  			[self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1])
  						= (self debugStackPointerFor: bytecodePC)]].
  	 byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj) + bytecodeSetOffset.
  	 descriptor := self generatorAt: byte0.
  	 self loadSubsequentBytesForDescriptor: descriptor at: bytecodePC.
  	 nextOpcodeIndex := opcodeIndex.
  	 result := deadCode
  				ifTrue: "insert nops for dead code that is mapped so that bc to mc mapping is not many to one"
  					[(descriptor isMapped
  					  or: [inBlock and: [descriptor isMappedInBlock]]) ifTrue:
  						[self annotateBytecode: self Nop].
  						0]
  				ifFalse:
  					[self perform: descriptor generator].
  	 descriptor isExtension ifFalse: "extended bytecodes must consume their extensions"
  		[self assert: (extA = 0 and: [extB = 0])].
  	 self traceDescriptor: descriptor; traceSimStack.
+ 	 fixup needsFixup ifTrue:
- 	 (fixup targetInstruction asUnsignedInteger between: 1 and: 2) ifTrue:
  		["There is a fixup for this bytecode.  It must point to the first generated
  		   instruction for this bytecode.  If there isn't one we need to add a label."
+ 		 opcodeIndex = nextOpcodeIndex ifTrue: [self Label].
- 		 opcodeIndex = nextOpcodeIndex ifTrue:
- 			[self Label].
  		 fixup targetInstruction: (self abstractInstructionAt: nextOpcodeIndex)].
  	 self maybeDumpLiterals: descriptor.
  	 bytecodePC := self nextBytecodePCFor: descriptor at: bytecodePC exts: nExts in: methodObj.
  	 result = 0 and: [bytecodePC <= end]] whileTrue:
  		[nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  	self checkEnoughOpcodes.
  	^result!

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
- 		 (fixup targetInstruction asUnsignedInteger > 1
- 		  and: [fixup simStackPtr > -2]) ifTrue: "ignore backward branch targets"
- 				[self assert: fixup simStackPtr = simStackPtr]].
- 	fixup targetInstruction asUnsignedInteger <= 1
  		ifTrue: "convert a non-merge into a merge"
+ 			[fixup becomeMergeFixup.
- 			[fixup targetInstruction: (self cCoerceSimple: 2 to: #'AbstractInstruction *').
  			 fixup simStackPtr: simStackPtr]
  		ifFalse:
+ 			[fixup isBackwardBranchFixup
- 			[fixup simStackPtr <= -2
  				ifTrue: ["this is the target of a backward branch and
  						 so doesn't have a simStackPtr assigned yet."
  						fixup simStackPtr: simStackPtr]
  				ifFalse: [self assert: fixup simStackPtr = simStackPtr]].
  	^fixup!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>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."
  	<returnTypeC: #'BytecodeFixup *'>
  	| fixup |
  	<var: #fixup type: #'BytecodeFixup *'>
  	fixup := self fixupAt: targetIndex.
+ 	fixup notAFixup ifTrue:
+ 		[fixup becomeNonMergeFixup].
- 	fixup targetInstruction = 0 ifTrue:
- 		[fixup targetInstruction: (self cCoerceSimple: 1 to: #'AbstractInstruction *')].
  	self cCode: '' inSmalltalk:
+ 		[fixup isMergeFixupOrIsFixedUp ifTrue:
- 		[fixup targetInstruction asUnsignedInteger > 1 ifTrue:
  			[self assert:
+ 					(fixup isBackwardBranchFixup
- 					(fixup simStackPtr = -2 "backward branch target"
  					 or: [fixup simStackPtr = (self debugStackPointerFor: targetIndex + initialPC)])]].
  	^fixup!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') -----
  genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg
  	"Inlined comparison. opTrue = jump for true and opFalse = jump for false"
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	| nextPC branchDescriptor targetBytecodePC postBranchPC |	
  		
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])
  		ifTrue: "This is the path where the inlined comparison is followed immediately by a branch"
+ 			[ (self fixupAt: nextPC - initialPC) notAFixup
- 			[ (self fixupAt: nextPC - initialPC) targetInstruction = 0
  				ifTrue: "The next instruction is dead.  we can skip it."
  					[deadCode := true.
  				 	 self ensureFixupAt: targetBytecodePC - initialPC.
  					 self ensureFixupAt: postBranchPC - initialPC ]
  				ifFalse:
  					[self ssPushConstant: objectMemory trueObject]. "dummy value"
  			self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse])
  				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. 
  			deadCode ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC) ] ]
  		ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch"
  			[| condJump jump |
  			condJump := self genConditionalBranch: opTrue operand: 0.
  			self genMoveFalseR: destReg.
  	 		jump := self Jump: 0.
  			condJump jmpTarget: (self genMoveTrueR: destReg).
  			jump jmpTarget: self Label].
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEqualsWithForwarders
  	| nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
  	unforwardArg  rcvrReg postBranchPC label fixup |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #label type: #'AbstractInstruction *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  
  	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
  	register so the forwarder check can jump back to the comparison after unforwarding the constant.
  	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
  	(machine code will use operations on constants) and does not generate forwarder checks."
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
  		rcvrNeedsReg: unforwardRcvr 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  
  	"If not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	label := self Label.
  	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	(self fixupAt: nextPC - initialPC) notAFixup
- 	(self fixupAt: nextPC - initialPC) targetInstruction = 0
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
  			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  
  	self assert: (unforwardArg or: [ unforwardRcvr ]).
  	branchDescriptor isBranchTrue 
  		ifTrue: 
  			[ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger.
  			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ]
  		ifFalse: "branchDescriptor is branchFalse"
  			[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ].
  		
  	"The forwarders checks need to jump back to the comparison (label) if a forwarder is found, else 
  	jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
  	unforwardArg ifTrue: 
  		[ unforwardRcvr
  			ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
  			ifFalse: [ objectRepresentation 
  				genEnsureOopInRegNotForwarded: argReg 
  				scratchReg: TempReg 
  				ifForwarder: label
  				ifNotForwarder: fixup ] ].
  	unforwardRcvr ifTrue: 
  		[ objectRepresentation 
  			genEnsureOopInRegNotForwarded: rcvrReg 
  			scratchReg: TempReg 
  			ifForwarder: label
  			ifNotForwarder: fixup ].
  		
  	"Not reached, execution flow have jumped to fixup"
  	
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genVanillaSpecialSelectorEqualsEquals
  	| nextPC postBranchPC targetBytecodePC branchDescriptor
  	  rcvrReg argReg argIsConstant rcvrIsConstant  |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	argIsConstant := self ssTop type = SSConstant.
  	"they can't be both constants because we do not have instructions manipulating two constants, 
  	if this is the case, which can happen due to annotable constants that can be moved in memory 
  	with become and therefore can't resolve #== at compilation time, still write the rcvr into a 
  	register as if it was not a constant. It's uncommon anyway."
  	rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant]. 
  	
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not 
  		rcvrNeedsReg: rcvrIsConstant not 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  	
  	"If not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[ ^ self genEqualsEqualsNoBranchArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	self genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	(self fixupAt: nextPC - initialPC) notAFixup
- 	(self fixupAt: nextPC - initialPC) targetInstruction = 0
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
  			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  		
  	self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  
  	"If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else 
  	we need to jump over the code of the branch"
  	deadCode ifFalse: [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>initializeFixupAt: (in category 'compile abstract instructions') -----
  initializeFixupAt: targetIndex
  	"Make sure there's a flagged fixup at the targetIndex (pc relative to first pc) in fixups.
  	 These are the targets  of backward branches.  A backward branch fixup's simStackPtr
  	 needs to be set when generating the code for the bytecode at the targetIndex.
  	 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
+ 		becomeMergeFixup;
+ 		setIsBackwardBranchFixup.
- 		targetInstruction: (self cCoerceSimple: 2 to: #'AbstractInstruction *');
- 		simStackPtr: -2.
  	^fixup!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>merge:afterContinuation: (in category 'simulation stack') -----
  merge: fixup afterContinuation: mergeWithContinuation
  	"Merge control flow at a fixup.  The fixup holds the simStackPtr at the jump to this target.
  	 See stackToRegisterMapping on the class side for a full description."
  	<var: #fixup type: #'BytecodeFixup *'>
  	self traceMerge: fixup.
  	"For now we don't try and preserve the optimization status through merges."
  	optStatus isReceiverResultRegLive: false.
  	"If this instruction follows a return or an unconditional branch then the
  	 current simStackPtr is irrelevant and we continue with that of the fixup."
  	mergeWithContinuation ifFalse:
+ 		[self assert: fixup isMergeFixupOrIsFixedUp.  "Must have a valid simStackPtr"
- 		[self assert: fixup targetInstruction asUnsignedInteger >= 2.  "Must have a valid simStackPtr"
  		 simStackPtr := fixup simStackPtr].
+ 	fixup notYetFixedUp ifTrue:
- 	fixup targetInstruction asUnsignedInteger <= 2 ifTrue:
  		["This is either a forward or backward branch target.
  		  The stack must be flushed."
  		 self ssFlushTo: simStackPtr.
+ 		 fixup isBackwardBranchFixup ifTrue:
- 		 fixup simStackPtr <= -2 ifTrue:
  			"This is the target of a backward branch.  It doesn't have a simStackPtr yet."
  			[fixup simStackPtr: simStackPtr].
  		 fixup targetInstruction: self Label].
  	self assert: simStackPtr >= fixup simStackPtr.
  	self cCode: '' inSmalltalk:
  		[self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].
  	simStackPtr := fixup simStackPtr.
  	simSpillBase := methodOrBlockNumTemps.
  	"For now throw away all type information for values on the stack, but sometime consider
  	 the more sophisticated merge described in the class side stackToRegisterMapping."
  	methodOrBlockNumTemps to: simStackPtr do:
  		[:i|
  		(self simStackAt: i)
  			mergeAt: FoxMFReceiver - (i - methodOrBlockNumArgs + 1 * objectMemory bytesPerOop)
  			from: FPReg]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>reinitializeFixupsFrom:through: (in category 'compile abstract instructions') -----
  reinitializeFixupsFrom: start through: end
  	"When a block must be recompiled due to overestimating the
  	 numInitialNils fixups must be restored, which means rescannning
  	 since backward branches need their targets initialized."
  	| descriptor nExts pc distance targetPC |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	pc := start.
  	nExts := 0.
  	[pc <= end] whileTrue:
+ 		[(self fixupAt: pc - initialPC) reinitialize.
- 		[(self fixupAt: pc - initialPC)
- 			targetInstruction: 0;
- 			simStackPtr: nil.
  		 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 - initialPC].
  		 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]]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	super setInterpreter: aCoInterpreter.
  
  	methodAbortTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  	picAbortTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  	picMissTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  
+ 	simStack := CArrayAccessor on: ((1 to: self class simStackSlots) collect: [:i| CogSimStackEntry new cogit: self]).
- 	simStack := CArrayAccessor on: ((1 to: 256) collect: [:i| CogSimStackEntry new cogit: self]).
  	simSelf := CogSimStackEntry new cogit: self.
  	optStatus := CogSSOptStatus new.
  
  	debugFixupBreaks := self class initializationOptions at: #debugFixupBreaks ifAbsent: [Set new].
  
  	numPushNilsFunction := self class numPushNilsFunction.
  	pushNilSizeFunction := self class pushNilSizeFunction!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>simStackSlots (in category 'simulation stack') -----
+ simStackSlots
+ 	"Answer the number of slots toinclude in a simulated stack.
+ 	 This needs to be big enough to include all slots in a context
+ 	 plus some overflow for safety."
+ 	<inline: true>
+ 	^((LargeContextSlots - CtxtTempFrameStart max: 64) * 11 // 10)!



More information about the Vm-dev mailing list