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

commits at source.squeak.org commits at source.squeak.org
Sun Jul 6 03:46:35 UTC 2014


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

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

Name: VMMaker.oscog-eem.804
Author: eem
Time: 5 July 2014, 8:43:20.915 pm
UUID: 8f232d31-fa50-4134-8556-da8fc12ab32d
Ancestors: VMMaker.oscog-tpr.803

Cogit:
Change the management of counters in Sista methods to
hold the counters well away from code.  In V3 use malloc
to allocate and free them (this means Sista V3 is not
currently simulable).  In Spur, store them in oldSpace in
pinned objects (hence Sista Spur simulates just fine).

Nuke unused variables in Cogit hierarchy.

Fix a few slips with the ceEnterCogCode => ceCallCogCode
putch in VMMaker.oscog-eem.802/tpr.803

Spur:
Fix bug in allocateSlotsForPinningInOldSpace:bytes:format:classIndex:
and make sure answered object is actually pinned.  Hence
fix pinObject: & primitivePin.

Plugins:
Fix access to the characterTable in the ThreadedFFIPlugins.
Replace characterTable at: with characterObjectOf:, and in
Spur, support wide characters.

Fix divide-as-shift issue in BalloonEnginePlugin.

SImulator:
Fix offset of counters in CogSistaMethodSurrogates for
Spur.

Slang:
Make the generateDivide:on:indent: check for the divide-as-
shift issue pull in sqAssert.h.

Add generateAllSistaConfigurationsUnderVersionControl
convenience.

=============== Diff against VMMaker.oscog-tpr.803 ===============

Item was changed:
  ----- Method: BalloonEnginePlugin>>stepToNextBezierForward:at: (in category 'beziers-simple') -----
  stepToNextBezierForward: updateData at: yValue
  	"Incrementally step to the next scan line in the given bezier update data.
  	Note: This method has been written so that inlining works, e.g.,
  		not declaring updateData as 'int*' but casting it on every use."
  	| minY lastX lastY fwDx fwDy |
  	<inline: true>
  	lastX := (self cCoerce: updateData to: 'int*') at: GBUpdateX.
  	lastY := (self cCoerce: updateData to: 'int*') at: GBUpdateY.
  	fwDx := (self cCoerce: updateData to: 'int*') at: GBUpdateDX.
  	fwDy := (self cCoerce: updateData to: 'int*') at: GBUpdateDY.
  	minY := yValue * 256.
  	"Step as long as we haven't yet reached minY and also
  	as long as fwDy is greater than zero thus stepping down.
  	Note: The test for fwDy should not be necessary in theory
  		but is a good insurance in practice."
  	[minY > lastY and:[fwDy >= 0]] whileTrue:[
+ 		lastX := lastX + ((fwDx + 16r8000) signedBitShift: -16).
+ 		lastY := lastY + ((fwDy + 16r8000) signedBitShift: -16).
- 		lastX := lastX + ((fwDx + 16r8000) // 16r10000).
- 		lastY := lastY + ((fwDy + 16r8000) // 16r10000).
  		fwDx := fwDx + ((self cCoerce: updateData to: 'int*') at: GBUpdateDDX).
  		fwDy := fwDy + ((self cCoerce: updateData to: 'int*') at: GBUpdateDDY).
  	].
  	(self cCoerce: updateData to: 'int*') at: GBUpdateX put: lastX.
  	(self cCoerce: updateData to: 'int*') at: GBUpdateY put: lastY.
  	(self cCoerce: updateData to: 'int*') at: GBUpdateDX put: fwDx.
  	(self cCoerce: updateData to: 'int*') at: GBUpdateDY put: fwDy.
+ 	^lastX signedBitShift: -8
- 	^lastX // 256
  !

Item was changed:
  ----- Method: CCodeGenerator>>generateDivide:on:indent: (in category 'C translation') -----
  generateDivide: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
  	| rcvr arg divisor check |
  	rcvr := msgNode receiver.
  	arg := msgNode args first.
  	check :=	false "If you need to check the validity of divides that had been implemented by signed shifts, change this to true..."
  				and: [arg isConstant
  				and: [(divisor := arg value) isInteger
  				and: [divisor isPowerOfTwo
  				and: [divisor > 0
  				and: [divisor <= (1 bitShift: 31)]]]]].
  	check ifTrue:
+ 		[(headerFiles includes: '"sqAssert.h"') ifFalse:
+ 			[self addHeaderFile: '"sqAssert.h"'].
+ 		aStream nextPut: $(; nextPutAll: 'assert(((sqInt) '.
- 		[aStream nextPut: $(; nextPutAll: 'assert(((sqInt) '.
  		 self emitCExpression: rcvr on: aStream.
  		 aStream nextPutAll: ' >> ', (divisor log: 2) asInteger printString.
  		 aStream nextPutAll: ') == ('.
  		 self emitCExpression: rcvr on: aStream.
  		aStream nextPutAll: ' / '.
  		self emitCExpression: msgNode args first on: aStream.
  		aStream nextPutAll: ')),'].
  	self emitCExpression: msgNode receiver on: aStream.
  	aStream nextPutAll: ' / '.
  	self emitCExpression: msgNode args first on: aStream.
  	check ifTrue:
  		[aStream nextPut: $)]!

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the
  	 inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
  								['objectHeader']			-> [self objectMemoryClass baseHeaderSize = 8
  																ifTrue: [#sqLong]
  																ifFalse: [#sqInt]].
+ 								['cmNumArgs']				-> [#(unsigned ' : 8')].		"SqueakV3 needs only 5 bits"
- 								['cmNumArgs']				-> [#(unsigned ' : 8')]. "SqueakV3 needs only 5 bits"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
  								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUsageCount']			-> [#(unsigned ' : 3')].		"See CMMaxUsageCount in initialize"
- 								['cmUsageCount']			-> [#(unsigned ' : 3')]. "see CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
  								['cmUsesMethodClass']		-> [#(unsigned #Boolean ' : 1')].
  								['cmUnusedFlags']			-> [#(unsigned ' : 2')].
+ 								['stackCheckOffset']		-> [#(unsigned ' : 12')].		"See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
+ 								['blockSize']				-> [#'unsigned short'].		"See MaxMethodSize in initialize"
- 								['stackCheckOffset']		-> [#(unsigned ' : 12')]. "See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
- 								['blockSize']				-> [#'unsigned short']. "See MaxMethodSize in initialize"
  								['blockEntryOffset']			-> [#'unsigned short'].
  								['homeOffset']				-> [#'unsigned short'].
  								['startpc']					-> [#'unsigned short'].
  								['padToWord']				-> [#(#BaseHeaderSize 8 'unsigned int')].
+ 								['nextMethod']				-> ['struct _CogMethod *'].	"See NewspeakCogMethod"
+ 								['counters']					-> [#usqInt]}				"See SistaCogMethod"
- 								['nextMethod']				-> ['struct _CogMethod *']} "see NewspeakCogMethod"
  							otherwise:
  								[#sqInt])]]!

Item was added:
+ ----- Method: CogObjectRepresentation>>allocateCounters: (in category 'sista support') -----
+ allocateCounters: nCounters
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>freeCounters: (in category 'sista support') -----
+ freeCounters: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>maybeMarkCounters: (in category 'sista support') -----
+ maybeMarkCounters: theCounters
+ 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
+ 	 to avoid them being garbage collected.  This is the hook through which that happens.
+ 	 By default, do nothing."
+ 	<var: #counters type: #usqInt>
+ 	<inline: true>!

Item was added:
+ ----- Method: CogObjectRepresentation>>numCountersFor: (in category 'sista support') -----
+ numCountersFor: theCounters
+ 	<var: #counters type: #usqInt>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>resetCountersIn: (in category 'sista support') -----
+ resetCountersIn: cogMethod
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<api>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>numCountersFor: (in category 'sista support') -----
+ numCountersFor: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	| objOop |
+ 	theCounters = 0 ifTrue:
+ 		[^0].
+ 	objOop := theCounters - objectMemory baseHeaderSize.
+ 	^objectMemory numSlotsOf: objOop!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>numCountersFor: (in category 'sista support') -----
+ numCountersFor: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	| objOop |
+ 	theCounters = 0 ifTrue:
+ 		[^0].
+ 	objOop := theCounters - objectMemory baseHeaderSize.
+ 	^2 * (objectMemory numSlotsOf: objOop)!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>allocateCounters: (in category 'sista support') -----
+ allocateCounters: nCounters
+ 	"On Spur allocate the counters on the heap as pinned objects.  The
+ 	 number of counters can be derived from the nbumber of slots in the obj."
+ 	<inline: true>
+ 	| objOop |
+ 	objOop := objectMemory allocatePinnedCounters: nCounters.
+ 	^objOop
+ 		ifNil: [0]
+ 		ifNotNil: [objOop + objectMemory baseHeaderSize]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>freeCounters: (in category 'sista support') -----
+ freeCounters: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	<inline: true>
+ 	theCounters ~= 0 ifTrue:
+ 		[objectMemory freeObject: theCounters - objectMemory baseHeaderSize]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>maybeMarkCounters: (in category 'sista support') -----
+ maybeMarkCounters: theCounters
+ 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
+ 	 to avoid them being garbage collected.  This is the hook through which that happens."
+ 	<var: #counters type: #usqInt>
+ 	<inline: true>
+ 	theCounters ~= 0 ifTrue:
+ 		[objectMemory markAndTrace: theCounters - objectMemory baseHeaderSize]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>resetCountersIn: (in category 'sista support') -----
+ resetCountersIn: cogMethod
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<api>
+ 	cogit fillInCounters: (self numCountersFor: cogMethod counters) atStartAddress: cogMethod counters!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>allocateCounters: (in category 'sista support') -----
+ allocateCounters: nCounters
+ 	"Malloc the counter space.  Fill the first slot with the number of counters for resetCountersIn:"
+ 	| theCounters |
+ 	<var: #theCounters type: #usqInt>
+ 	theCounters := self malloc: nCounters + 1 * (self sizeof: #sqInt).
+ 	theCounters = 0 ifTrue:
+ 		[^theCounters].
+ 	self longAt: theCounters put: nCounters.
+ 	^theCounters + (self sizeof: #sqInt)!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>freeCounters: (in category 'sista support') -----
+ freeCounters: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	theCounters ~= 0 ifTrue:
+ 		[self free: theCounters - (self sizeof: #sqInt)]!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>numCountersFor: (in category 'sista support') -----
+ numCountersFor: theCounters
+ 	<var: #theCounters type: #usqInt>
+ 	^objectMemory longAt: theCounters - (self sizeof: #sqInt)!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>resetCountersIn: (in category 'sista support') -----
+ resetCountersIn: cogMethod
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<api>
+ 	cogit
+ 		fillInCounters: (self numCountersFor: cogMethod counters)
+ 		atStartAddress: cogMethod counters!

Item was changed:
  ----- Method: CogSistaMethodSurrogate32 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^24 + self baseHeaderSize!
- 	^28!

Item was changed:
  ----- Method: CogSistaMethodSurrogate32 class>>offsetOf: (in category 'accessing') -----
  offsetOf: aByteSymbol
  	"These should be generated!!!!"
  	self assert: self objectMemoryClass baseHeaderSize = BaseHeaderSize.
+ 	^aByteSymbol == #counters
- 	^aByteSymbol == #numCounters
  		ifTrue: [20 + BaseHeaderSize]
  		ifFalse: [super offsetOf: aByteSymbol]!

Item was added:
+ ----- Method: CogSistaMethodSurrogate32>>counters (in category 'accessing') -----
+ counters
+ 	^memory unsignedLongAt: address + 21 + baseHeaderSize!

Item was added:
+ ----- Method: CogSistaMethodSurrogate32>>counters: (in category 'accessing') -----
+ counters: aValue
+ 	^memory
+ 		unsignedLongAt: address + 21 + baseHeaderSize
+ 		put: aValue!

Item was removed:
- ----- Method: CogSistaMethodSurrogate32>>numCounters (in category 'accessing') -----
- numCounters
- 	^memory unsignedLongAt: address + 21 + baseHeaderSize!

Item was removed:
- ----- Method: CogSistaMethodSurrogate32>>numCounters: (in category 'accessing') -----
- numCounters: aValue
- 	^memory
- 		unsignedLongAt: address + 21 + baseHeaderSize
- 		put: aValue!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^40 + self baseHeaderSize!
- 	^48!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64 class>>offsetOf: (in category 'accessing') -----
  offsetOf: aByteSymbol
  	"These should be generated!!!!"
  	self assert: self objectMemoryClass baseHeaderSize = BaseHeaderSize.
+ 	^aByteSymbol == #counters
- 	^aByteSymbol == #numCounters
  		ifTrue: [32 + BaseHeaderSize]
  		ifFalse: [super offsetOf: aByteSymbol]!

Item was added:
+ ----- Method: CogSistaMethodSurrogate64>>counters (in category 'accessing') -----
+ counters
+ 	^memory unsignedLongLongAt: address + 33 + baseHeaderSize!

Item was added:
+ ----- Method: CogSistaMethodSurrogate64>>counters: (in category 'accessing') -----
+ counters: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 33 + baseHeaderSize
+ 		put: aValue!

Item was removed:
- ----- Method: CogSistaMethodSurrogate64>>numCounters (in category 'accessing') -----
- numCounters
- 	^memory unsignedLongLongAt: address + 33 + baseHeaderSize!

Item was removed:
- ----- Method: CogSistaMethodSurrogate64>>numCounters: (in category 'accessing') -----
- numCounters: aValue
- 	^memory
- 		unsignedLongLongAt: address + 33 + baseHeaderSize
- 		put: aValue!

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 initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex 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 ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
- 	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 initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass ShouldNotJIT UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' 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 eventuakly teh 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 class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM
  	 support code.  include cePositive32BitIntegerTrampoline as a hack to prevent it being inlined (it is
  	 only used outside of Cogit by the object representation).  Include CFramePointer CStackPointer as
  	 a hack to get them declared at all."
  	^#('ceBaseFrameReturnTrampoline' 'ceCaptureCStackPointers' 'ceCheckForInterruptTrampoline'
  		'ceEnterCogCodePopReceiverReg' 'realCEEnterCogCodePopReceiverReg'
+ 		'ceCallCogCodePopReceiverReg' 'realCECallCogCodePopReceiverReg'
+ 		'ceCallCogCodePopReceiverAndClassRegs' 'realCECallCogCodePopReceiverAndClassRegs'
- 		'ceEnterCogCodePopReceiverAndClassRegs' 'realCEEnterCogCodePopReceiverAndClassRegs'
  		'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
  		'ceTryLockVMOwner' 'ceUnlockVMOwner'
  		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'missOffset'
  		'blockNoContextSwitchOffset' 'breakPC'
  		'CFramePointer' 'CStackPointer' 'cFramePointerInUse' 'ceGetSP'
  		'traceFlags' 'traceStores' 'debugPrimCallStackOffset')
  			includes: var!

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: ((coInterpreter methodHasCogMethod: aMethodObj) not
  				or: [(self noAssertMethodClassAssociationOf: aMethodObj) = objectMemory nilObject]).
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	self cppIf: NewspeakVM
  		ifTrue: [cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  				cogMethod ifNotNil:
  					[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  						[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  						 cogMethod methodObject: aMethodObj.
  						 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  					^cogMethod]].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	extA := extB := 0.
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
+ 		 self maybeFreeCounters.
+ 		 "Right now no errors should be reported, so nothing more to do."
+ 		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
- 		"Right now no errors should be reported, so nothing more to do."
- 		"self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

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

Item was changed:
  ----- Method: Cogit>>genCallEnilopmartFor:and:called: (in category 'initialization') -----
  genCallEnilopmartFor: regArg1 and: regArg2 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  This version is for entering code as if from a call.  The desired
  	 arguments and entry-point are pushed on a stackPage's stack, and beneath
  	 them is the call's return address.  The enilopmart pops off the values to be
  	 loaded into registers, and on CISCs then executes a return instruction to pop
  	 off the entry-point and jump to it.  On RISCs the enilopmart pops off the values
  	 to be loaded into registers, pops the entry-point into a scratch register, pops
  	 the return address into the LinkReg and then jumps to the entry point.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						call return pc
  						target address =>	reg1 = reg1val, etc
  						reg1val				LinkReg = call return pc
  		stackPointer ->	reg2val				pc = target address
  
  	 C.F. genEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genCallEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
- 	<returnTypeC: 'void (*genCallEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self PopR: TempReg.
  			 self PopR: LinkReg.
  			 self JumpR: TempReg]
  		ifFalse:
  			[self RetN: 0].
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genCallEnilopmartFor:called: (in category 'initialization') -----
  genCallEnilopmartFor: regArg1 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  This version is for entering code as if from a call.  The desired
  	 arguments and entry-point are pushed on a stackPage's stack, and beneath
  	 them is the call's return address.  The enilopmart pops off the values to be
  	 loaded into registers, and on CISCs then executes a return instruction to pop
  	 off the entry-point and jump to it.  On RISCs the enilopmart pops off the values
  	 to be loaded into registers, pops the entry-point into a scratch register, pops
  	 the return address into the LinkReg and then jumps to the entry point.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						call return pc		reg1 = reg1val
  						target address =>	LinkReg = call return pc
  		stackPointer ->	reg1val				pc = target address
  
  	 C.F. genEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genCallEnilopmartForcalled(sqInt regArg1, char *trampolineName))(void)'>
- 	<returnTypeC: 'void (*genCallEnilopmartForandandcalled(sqInt regArg1, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg1.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self PopR: TempReg.
  			 self PopR: LinkReg.
  			 self JumpR: TempReg]
  		ifFalse:
  			[self RetN: 0].
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						target address =>	reg1 = reg1val, etc
  						reg1val				pc = target address
  		stackPointer ->	reg2val
  
  	C.F. genCallEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
- 	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	backEnd hasLinkRegister
  		ifTrue: [backEnd hasPCRegister
  					ifTrue: [self PopR: PCReg]
  					ifFalse: [self PopR: LinkReg; RetN: 0]]
  		ifFalse: [self RetN: 0].
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						target address =>	reg1 = reg1val
  		stackPointer ->	reg1val				pc = target address
  
  	C.F. genCallEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genEnilopmartForcalled(sqInt regArg1, char *trampolineName))(void)'>
- 	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg1.
  	backEnd hasLinkRegister
  		ifTrue: [backEnd hasPCRegister
  					ifTrue: [self PopR: PCReg]
  					ifFalse: [self PopR: LinkReg; RetN: 0]]
  		ifFalse: [self RetN: 0].
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateEnilopmarts (in category 'initialization') -----
  generateEnilopmarts
  	"Enilopmarts transfer control from C into machine code (backwards trampolines)."
  	self cppIf: Debug
  		ifTrue:
  			[realCEEnterCogCodePopReceiverReg :=
  				self genEnilopmartFor: ReceiverResultReg
  					called: 'realCEEnterCogCodePopReceiverReg'.
  			 ceEnterCogCodePopReceiverReg := #enterCogCodePopReceiver.
  			 realCECallCogCodePopReceiverReg :=
  				self genCallEnilopmartFor: ReceiverResultReg
  					called: 'realCEEnterCogCodePopReceiverReg'.
+ 			 ceCallCogCodePopReceiverReg := #callCogCodePopReceiver.
- 			 ceEnterCogCodePopReceiverReg := #callCogCodePopReceiver.
  			 realCECallCogCodePopReceiverAndClassRegs :=
  				self genCallEnilopmartFor: ReceiverResultReg
  					and: ClassReg
  					called: 'realCECallCogCodePopReceiverAndClassRegs'.
  			 ceCallCogCodePopReceiverAndClassRegs := #callCogCodePopReceiverAndClassRegs]
  		ifFalse:
  			[ceEnterCogCodePopReceiverReg := self genEnilopmartFor: ReceiverResultReg
  				called: 'ceEnterCogCodePopReceiverReg'.
  			 ceCallCogCodePopReceiverReg := self genCallEnilopmartFor: ReceiverResultReg
  				called: 'ceCallCogCodePopReceiverReg'.
  			 ceCallCogCodePopReceiverAndClassRegs :=
  				self genCallEnilopmartFor: ReceiverResultReg
  					and: ClassReg
  					called: 'ceCallCogCodePopReceiverAndClassRegs'].
  
  	self genPrimReturnEnterCogCodeEnilopmart: false.
  	cePrimReturnEnterCogCode := methodZoneBase.
  	self outputInstructionsForGeneratedRuntimeAt: cePrimReturnEnterCogCode.
  	self recordGeneratedRunTime: 'cePrimReturnEnterCogCode' address: cePrimReturnEnterCogCode.
  
  	self genPrimReturnEnterCogCodeEnilopmart: true.
  	cePrimReturnEnterCogCodeProfiling := methodZoneBase.
  	self outputInstructionsForGeneratedRuntimeAt: cePrimReturnEnterCogCodeProfiling.
  	self recordGeneratedRunTime: 'cePrimReturnEnterCogCodeProfiling' address: cePrimReturnEnterCogCodeProfiling!

Item was changed:
  ----- Method: Cogit>>markAndTraceLiteralsIn: (in category 'garbage collection') -----
  markAndTraceLiteralsIn: cogMethod
  	<option: #SpurMemoryManager>
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: ((cogMethod cmType = CMMethod
  				 and: [objectMemory isMarked: cogMethod methodObject])
  				 or: [cogMethod cmType = CMOpenPIC
  				 and: [(objectMemory isImmediate: cogMethod selector)
  					or: [objectMemory isMarked: cogMethod selector]]]).
  	objectRepresentation markAndTraceLiteral: cogMethod selector.
+ 	self maybeMarkCountersIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiterals:pc:method:
  		 arg: cogMethod asInteger!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkUnmarkedSendsIn: (in category 'garbage collection') -----
  markLiteralsAndUnlinkUnmarkedSendsIn: cogMethod
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: cogMethod cmType = CMMethod.
  	self assert: (objectMemory isMarked: cogMethod methodObject).
  	objectRepresentation markAndTraceLiteral: cogMethod selector.
+ 	self maybeMarkCountersIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiteralsAndUnlinkIfUnmarkedSend:pc:method:
  		 arg: cogMethod asInteger!

Item was changed:
  ----- Method: Cogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
  maybeAllocAndInitCounters
  	"No-op in the non-Sista Cogits..."
+ 	<inline: true>
+ 	^true!
- 	<inline: true>!

Item was added:
+ ----- Method: Cogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
+ maybeFreeCounters
+ 	"No-op in the non-Sista Cogits..."
+ 	<inline: true>!

Item was added:
+ ----- Method: Cogit>>maybeMarkCountersIn: (in category 'garbage collection') -----
+ maybeMarkCountersIn: cogMethod
+ 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
+ 	 to avoid them being garbage collected.  This is the hook through which that happens."
+ 	<var: #cogMethod type: #'CogMethod *'>!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
  	aStream crtab.
  	cogMethod cmType = CMMethod ifTrue:
  		[aStream nextPutAll: 'objhdr: '.
  		cogMethod objectHeader printOn: aStream base: 16].
  	cogMethod cmType = CMBlock ifTrue:
  		[aStream nextPutAll: 'homemth: '.
  		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
  	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'method: '.
  		cogMethod methodObject printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'mthhdr: '.
  		cogMethod methodHeader printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		aStream crtab; nextPutAll: 'blkentry: '.
  		cogMethod blockEntryOffset printOn: aStream base: 16.
  		cogMethod blockEntryOffset ~= 0 ifTrue:
  			[aStream nextPutAll: ' => '.
  			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
  			 cogMethod cPICNumCases printOn: aStream base: 16.]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
  			cogMethod cmType ~= CMBlock ifTrue:
  				[aStream
  					crtab;
  					nextPutAll: 'cmRefersToYoung: ';
  					nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
  			cogMethod cmType = CMMethod ifTrue:
+ 				[([cogMethod counters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
+ 					[:cntrs| aStream crtab; nextPutAll: 'counters: '.
+ 						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [self printHex: cntrs]]]].
- 				[([cogMethod numCounters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
- 					[:nc| aStream crtab; nextPutAll: 'numCounters: '; print: nc]]].
  	aStream cr; flush!

Item was changed:
  CogMethod subclass: #SistaCogMethod
+ 	instanceVariableNames: 'counters'
- 	instanceVariableNames: 'numCounters'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
+ 
+ !SistaCogMethod commentStamp: 'eem 7/4/2014 11:59' prior: 0!
+ A SistaCogMethod is a CogMethod with a pointer to memory holding the Sista performance counters decremented in conditional branches.
+ 
+ Instance Variables
+ 	counters:		<pointer>
+ 
+ counters
+ 	- counters points to the first field of either a pinned object on the Spur heap or malloced memory.
+ !

Item was added:
+ ----- Method: SistaCogMethod>>counters (in category 'accessing') -----
+ counters
+ 	"Answer the value of counters"
+ 
+ 	^ counters!

Item was added:
+ ----- Method: SistaCogMethod>>counters: (in category 'accessing') -----
+ counters: anObject
+ 	"Set the value of counters"
+ 
+ 	^counters := anObject!

Item was removed:
- ----- Method: SistaCogMethod>>numCounters (in category 'accessing') -----
- numCounters
- 	"Answer the value of numCounters"
- 
- 	^ numCounters!

Item was removed:
- ----- Method: SistaCogMethod>>numCounters: (in category 'accessing') -----
- numCounters: anObject
- 	"Set the value of numCounters"
- 
- 	^numCounters := anObject!

Item was changed:
  StackToRegisterMappingCogit subclass: #SistaStackToRegisterMappingCogit
+ 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue prevMapAbsPCMcpc'
- 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue counterMethodCache prevMapAbsPCMcpc'
  	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 class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
+ 	aCodeGen var: 'counters' type: #usqInt!
- 	aCodeGen
- 		var: 'counters'
- 			type: #'AbstractInstruction *'!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>addressIsInInstructions: (in category 'testing') -----
- addressIsInInstructions: address
- 	<var: #address type: #'AbstractInstruction *'>
- 	^self cCode:
- 			'address >= &abstractOpcodes[0] && address < &abstractOpcodes[opcodeIndex]
- 			|| address >= &counters[0] && address < &counters[counterIndex]'
- 		inSmalltalk:
- 			[((abstractOpcodes object identityIndexOf: address) between: 1 and: opcodeIndex)
- 			or: [(counters object identityIndexOf: address) between: 1 and: counterIndex]]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>allocateCounters (in category 'initialization') -----
- allocateCounters
- 	"Allocate the structures used to manage counting conditional branch
- 	 compilation.  This  needs to be a macro since the structures are alloca'ed
- 	 (stack allocated) to ensure their being freed when compilation is done."
- 	<cmacro: '() do { \
- 		counters = numCounters ? alloca(sizeof(AbstractInstruction) * numCounters) : 0; \
- } while (0)'>
- 	counters := CArrayAccessor on:
- 					((1 to: numCounters) collect:
- 						[:ign| backEnd class new])!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	"override to maintain counterIndex when recompiling blocks; sigh."
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
  	  initialStackPtr initialOpcodeIndex initialAnnotationIndex initialCounterIndex |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
  	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 initialAnnotationIndex := annotationIndex.
  		 initialCounterIndex := counterIndex.
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + ((self pushNilSize: methodObj) * blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
  		   compensate by checking, adjusting numInitialNils and recompiling the block body."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
- 				 self reinitializeCountersFrom: initialCounterIndex to: counterIndex - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i|
  									abstractOpcodes
  										at: i
  										put: (processor abstractInstructionCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 annotationIndex := initialAnnotationIndex.
  				 counterIndex := initialCounterIndex].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>compileCogMethod: (in category 'compile abstract instructions') -----
+ compileCogMethod: selector
+ 	counters := 0.
+ 	^super compileCogMethod: selector!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>counterAt:in: (in category 'method introspection') -----
- counterAt: index in: cogMethod
- 	<var: #cogMethod type: #'CogMethod *'>
- 	"zero-relative counter access"
- 	^objectMemory longAt: cogMethod asUnsignedInteger + cogMethod blockSize - (cogMethod numCounters - index * CounterBytes)!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>counterAt:put:in: (in category 'method introspection') -----
- counterAt: index put: aValue in: cogMethod
- 	<var: #cogMethod type: #'CogMethod *'>
- 	"zero-relative counter access"
- 	^objectMemory
- 		longAt: cogMethod asUnsignedInteger + cogMethod blockSize - (cogMethod numCounters - index * CounterBytes)
- 		put: aValue!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
+ 	| cogMethod |
- 	| cogMethod firstCounter |
  	cogMethod := super disassembleMethod: surrogateOrAddress on: aStream.
  	(cogMethod cmType = CMMethod
+ 	 and: [cogMethod counters ~= 0]) ifTrue:
- 	 and: [cogMethod numCounters > 0]) ifTrue:
  		[aStream nextPutAll: 'counters:'; cr.
+ 		 numCounters := objectRepresentation numCountersFor: counters.
+ 		 0 to: numCounters - 1 do:
- 		 firstCounter := cogMethod address + cogMethod blockSize - (cogMethod numCounters * CounterBytes).
- 		 0 to: cogMethod numCounters - 1 do:
  			[:i| | addr |
+ 			 addr := i * CounterBytes + counters.
- 			 addr := i * CounterBytes + firstCounter.
  			 addr printOn: aStream base: 16.
  			 aStream nextPut: $:; space.
  			 (objectMemory longAt: addr) printOn: aStream base: 16.
  			 aStream cr].
  		 aStream flush]!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>fillInCPICHeader:size:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
+ fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
+ 	pic counters: 0.
+ 	^super fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>fillInCounters:atStartAddress: (in category 'generate machine code') -----
+ fillInCounters: nCounters atStartAddress: startAddress
+ 	startAddress
+ 		to: startAddress + (nCounters - 1 * CounterBytes)
+ 		by: CounterBytes
+ 		do: [:address|
+ 			objectMemory
+ 				long32At: address
+ 				put: (initialCounterValue << 16 + initialCounterValue)]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	super fillInMethodHeader: method size: size selector: selector.
+ 	self fillInCounters: numCounters atStartAddress: counters.
+ 	method counters: counters.
- 	method numCounters: counterIndex.
  	^method!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>fillInOPICHeader:size:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic size: size numArgs: numArgs selector: selector
+ 	pic counters: 0.
- 	pic numCounters: 0.
  	^super fillInOPICHeader: pic size: size numArgs: numArgs selector: selector!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generators') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
  	 so that scanning for send and branch data is simplified and that branch data is correct."
  	<inline: false>
+ 	| desc ok counterAddress countTripped retry |
- 	| desc ok counter countTripped retry |
- 	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #ok type: #'AbstractInstruction *'>
+ 	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #retry type: #'AbstractInstruction *'>
- 	<var: #counter type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	desc popToReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
+ 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
- 	counter := self addressOf: (counters at: counterIndex).
  	counterIndex := counterIndex + 1.
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
+ 	retry := self MoveAw: counterAddress R: SendNumArgsReg.
- 	retry := self MoveAw: counter asUnsignedInteger R: SendNumArgsReg.
- 	counter addDependent: (self annotateAbsolutePCRef: retry).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  	countTripped := self JumpCarry: 0.
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if SendNumArgsReg is 0 this is a mustBeBoolean, not a counter trip."
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
  	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
  	 trampoline will return directly to machine code, returning the boolean.  So the code should
  	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
  	self annotateBytecode: self Label.
  	self Jump: retry.
  	ok jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"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 primDescriptor branchDescriptor nExts
+ 	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst
+ 	  counterAddress countTripped |
+ 	<var: #countTripped type: #'AbstractInstruction *'>
- 	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst counter countTripped |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #counter type: #'AbstractInstruction *'>
- 	<var: #countTripped type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
  		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  		 self annotateBytecodeIfAnnotated: self ssTop.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
+ 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
- 	counter := self addressOf: (counters at: counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
+ 	self MoveAw: counterAddress R: SendNumArgsReg.
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEquals
  	"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 primDescriptor branchDescriptor nExts
+ 	  counterAddress countTripped unforwardArg unforwardRcvr |
+ 	<var: #countTripped type: #'AbstractInstruction *'>
- 	  counter countTripped unforwardArg unforwardRcvr |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #counter type: #'AbstractInstruction *'>
- 	<var: #countTripped type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	unforwardRcvr := (self ssValue: 1) type ~= SSConstant
  						or: [objectRepresentation shouldAnnotateObjectReference: (self ssValue: 1) constant].
  	unforwardArg := self ssTop type ~= SSConstant
  						or: [objectRepresentation shouldAnnotateObjectReference: self ssTop constant].
  	self marshallSendArguments: 1.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
+ 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
- 	counter := self addressOf: (counters at: counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
+ 	self MoveAw: counterAddress R: SendNumArgsReg.
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  	unforwardRcvr ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	unforwardArg ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg].
  	self CmpR: Arg0Reg R: ReceiverResultReg.
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
+ 	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
- 	counter addDependent: (self annotateAbsolutePCRef:
- 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: self Label.
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>generateCogMethod: (in category 'generate machine code') -----
- generateCogMethod: selector
- 	"We handle jump sizing simply.  First we make a pass that asks each
- 	 instruction to compute its maximum size.  Then we make a pass that
- 	 sizes jumps based on the maxmimum sizes.  Then we make a pass
- 	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
- 	 choose a smaller offset but must stick to the size set in the second pass.
- 
- 	 Override to add counters"
- 	<returnTypeC: #'CogMethod *'>
- 	| codeSize headerSize mapSize countersSize totalSize startAddress result method |
- 	<var: #method type: #'CogMethod *'>
- 	headerSize := self sizeof: CogMethod.
- 	methodLabel address: headerSize negated.
- 	self computeMaximumSizes.
- 	methodLabel concretizeAt: (methodZone allocate: 0).
- 	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
- 	mapSize := self generateMapAt: 0 start: methodLabel address + cmNoCheckEntryOffset.
- 	countersSize := counterIndex * CounterBytes.
- 	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize + countersSize.
- 	totalSize > MaxMethodSize ifTrue:
- 		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
- 	startAddress := methodZone allocate: totalSize.
- 	startAddress = 0 ifTrue:
- 		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
- 	self assert: startAddress + cmEntryOffset = entry address.
- 	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
- 	self regenerateCounterReferences: startAddress + totalSize.
- 	result := self outputInstructionsAt: startAddress + headerSize.
- 	self assert: startAddress + headerSize + codeSize = result.
- 	backEnd nopsFrom: result to: startAddress + totalSize - mapSize.
- 	self generateMapAt: startAddress + totalSize - countersSize - 1 start: startAddress + cmNoCheckEntryOffset.
- 	self fillInBlockHeadersAt: startAddress.
- 	self fillInCounters: counterIndex atEndAddress: startAddress + totalSize.
- 	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 					size: totalSize
- 					selector: selector.
- 	postCompileHook notNil ifTrue:
- 		[self perform: postCompileHook with: method with: primInvokeLabel.
- 		 postCompileHook := nil].
- 	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
- 	^method!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>handleWriteSimulationTrap: (in category 'simulation only') -----
- handleWriteSimulationTrap: aProcessorSimulationTrap
- 	<doNotGenerate>
- 	| address end |
- 	address := aProcessorSimulationTrap address.
- 	(address >= methodZone freeStart
- 	or: [address <= methodZoneBase]) ifTrue:
- 		[^super handleWriteSimulationTrap: aProcessorSimulationTrap].
- 
- 	(counterMethodCache isNil
- 	 or: [address < counterMethodCache
- 	 or: [counterMethodCache address + counterMethodCache blockSize < address]]) ifTrue:
- 		[counterMethodCache := methodZone methodFor: address].
- 	end := counterMethodCache address + counterMethodCache blockSize.
- 	self assert: (address
- 					between: end - (CounterBytes * counterMethodCache numCounters)
- 					and: end).
- 	objectMemory longAt: address put: (processor perform: aProcessorSimulationTrap registerAccessor).
- 	processor pc: aProcessorSimulationTrap nextpc!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	initialCounterValue := MaxCounterValue.
- 	numCounters := 0.
- 	self allocateCounters.
  	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>initializeCounters (in category 'initialization') -----
- initializeCounters
- 	"Initialize the counter labels for the current compilation.  We give them bogus
- 	 addresses since we can't determine their address until after the map is generated.
- 	 So we have to regenerate their dependent instructions after map generation."
- 	self reinitializeCountersFrom: 0 to: numCounters - 1.
- 	counterIndex := 0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>mapStartFor: (in category 'method map') -----
- mapStartFor: cogMethod
- 	"Answer the address of the first byte of the method map."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<inline: true>
- 	^cogMethod asUnsignedInteger + cogMethod blockSize - (cogMethod numCounters * CounterBytes) - 1!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
  maybeAllocAndInitCounters
  	<inline: true>
+ 	self assert: counters = 0.
+ 	counterIndex := 0.
+ 	numCounters = 0 ifTrue:
+ 		[^true].
+ 	counters := objectRepresentation allocateCounters: numCounters.
+ 	^counters ~= 0!
- 	self allocateCounters; initializeCounters!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
+ maybeFreeCounters
+ 	<inline: true>
+ 	counters ~= 0 ifTrue:
+ 		[objectMemory freeCounters: counters]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCountersOf: (in category 'compaction') -----
  maybeFreeCountersOf: aCogMethod
  	"Free any counters in the method."
  	<inline: true>
+ 	objectRepresentation freeCounters: aCogMethod counters!
- 	self shouldBeImplemented!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>maybeMarkCountersIn: (in category 'garbage collection') -----
+ maybeMarkCountersIn: cogMethod
+ 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
+ 	 to avoid them being garbage collected.  This is the hook through which that happens."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: true>
+ 	objectRepresentation maybeMarkCounters: cogMethod counters!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>printCountersFor:on: (in category 'simulation only') -----
- printCountersFor: cogMethod on: aStream
- 	| firstCounter |
- 	firstCounter := cogMethod address + cogMethod blockSize - (cogMethod numCounters * CounterBytes).
- 	0 to: cogMethod numCounters - 1 do:
- 		[:i| | addr |
- 		addr := i * CounterBytes + firstCounter.
- 		addr printOn: aStream base: 16.
- 		aStream nextPut: $:; space.
- 		(objectMemory longAt: addr) printOn: aStream base: 16.
- 		aStream cr]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>regenerateCounterReferences: (in category 'generate machine code') -----
- regenerateCounterReferences: methodEndAddress
- 	<var: #label type: #'AbstractInstruction *'>
- 	<var: #dependentInstruction type: #'AbstractInstruction *'>
- 	0 to: counterIndex - 1 do:
- 		[:i| | label dependentInstruction |
- 		label := self addressOf: (counters at: i).
- 		label address: methodEndAddress - ((counterIndex - i) * CounterBytes).
- 		dependentInstruction := label dependent.
- 		[dependentInstruction concretizeAt: dependentInstruction address.
- 		 dependentInstruction := dependentInstruction dependent.
- 		 dependentInstruction ~= nil] whileTrue]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>reinitializeCountersFrom:to: (in category 'initialization') -----
- reinitializeCountersFrom: start to: stop
- 	"Reinitialize the counter labels in the given range.  We give them bogus
- 	 addresses since we can't determine their address until after the map
- 	 is generated.  So we have to regenerate their dependent instructions
- 	 after map generation."
- 	| label |
- 	<var: #label type: #'AbstractInstruction *'>
- 	start to: stop do:
- 		[:i|
- 		label := self addressOf: (counters at: i).
- 		label
- 			opcode: Label;
- 			dependent: nil;
- 			address: methodZone zoneEnd - (numCounters + i * CounterBytes)]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>resetCountersIn: (in category 'sista callbacks') -----
  resetCountersIn: cogMethod
+ 	<doNotGenerate>
+ 	objectRepresentation resetCountersIn: cogMethod!
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<api>
- 	self
- 		fillInCounters: cogMethod numCounters
- 		atEndAddress: cogMethod asUnsignedInteger + cogMethod blockSize!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>allocatePinnedCounters: (in category 'sista support') -----
+ allocatePinnedCounters: nCounters
+ 	<api>
+ 	<option: #SistaStackToRegisterMappingCogit>
+ 	^self allocateSlotsForPinningInOldSpace: nCounters
+ 			bytes: (self objectBytesForSlots: nCounters)
+ 			format: self firstLongFormat
+ 			classIndex: 	self thirtyTwoBitLongsClassIndexPun!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
  		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
  		 chunk ifNotNil:
  			[(segmentManager segmentContainingObj: chunk) containsPinned: true]].
  	self checkFreeSpace.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self flag: #endianness.
  		 self longAt: chunk put: numSlots.
  		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
  		 self long64At: chunk + self baseHeaderSize
+ 			 put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
+ 					bitOr: 1 << self pinnedBitShift).
- 			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
  		 ^chunk + self baseHeaderSize].
+ 	self long64At: chunk
+ 		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
+ 					bitOr: 1 << self pinnedBitShift).
- 	self long64At: chunk put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
  	^chunk!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>allocatePinnedCounters: (in category 'sista support') -----
+ allocatePinnedCounters: nCounters
+ 	<api>
+ 	<option: #SistaStackToRegisterMappingCogit>
+ 	| numSlots |
+ 	numSlots := nCounters + 1 // 2.
+ 	^self allocateSlotsForPinningInOldSpace: numSlots
+ 			bytes: (self objectBytesForSlots: numSlots)
+ 			format: self firstLongFormat + (nCounters bitAnd: 1)
+ 			classIndex: 	self thirtyTwoBitLongsClassIndexPun!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
  		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes].
  	self checkFreeSpace.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self longAt: chunk
  			put: numSlots + (self numSlotsMask << self numSlotsFullShift).
  		 self longAt: chunk + self baseHeaderSize
+ 			put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
+ 					bitOr: 1 << self pinnedBitShift).
- 			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
  		 ^chunk + self baseHeaderSize].
  	self longAt: chunk
+ 		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
+ 				bitOr: 1 << self pinnedBitShift).
- 		put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
  	^chunk!

Item was changed:
  ----- Method: SpurMemoryManager>>freeObject: (in category 'free space') -----
  freeObject: objOop
+ 	<api>
  	| bytes |
  	bytes := self bytesInObject: objOop.
  	totalFreeOldSpace := totalFreeOldSpace + bytes.
  	^self freeChunkWithBytes: bytes at: (self startOfObject: objOop)!

Item was changed:
  ----- Method: SpurMemoryManager>>numSlotsOf: (in category 'object access') -----
  numSlotsOf: objOop
  	<returnTypeC: #usqInt>
+ 	<api>
  	| numSlots |
  	self flag: #endianness.
  	"numSlotsOf: should not be applied to free or forwarded objects."
  	self assert: (self classIndexOf: objOop) > self isForwardedObjectClassIndexPun.
  	numSlots := self rawNumSlotsOf: objOop..
  	^numSlots = self numSlotsMask	"overflow slots; (2^32)-1 slots are plenty"
  		ifTrue: [self rawOverflowSlotsOf: objOop]
  		ifFalse: [numSlots]!

Item was changed:
  SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+ 	instanceVariableNames: 'prevBCDescriptor isPushNilFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
- 	instanceVariableNames: 'prevBCDescriptor isPushNilFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'isPushNilFunction 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: 'isPushNilFunction pushNilSizeFunction'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
  
  	^(super mustBeGlobal: var)
+ 	   or: [#('ceCallCogCodePopReceiverArg0Regs' 'ceCallCogCodePopReceiverArg1Arg0Regs'
+ 			'realCECallCogCodePopReceiverArg0Regs' 'realCECallCogCodePopReceiverArg1Arg0Regs'
+ 			'ceCall0ArgsPIC' 'ceCall1ArgsPIC' 'ceCall2ArgsPIC') includes: var]!
- 	   or: [#('ceEnterCogCodePopReceiverArg0Regs' 'ceEnterCogCodePopReceiverArg1Arg0Regs'
- 			'realCEEnterCogCodePopReceiverArg0Regs' 'realCEEnterCogCodePopReceiverArg1Arg0Regs'
- 			'ceEnter0ArgsPIC' 'ceEnter1ArgsPIC' 'ceEnter2ArgsPIC') includes: var]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ceEnterCogCodePopReceiverArg0Regs (in category 'simulation only') -----
- ceEnterCogCodePopReceiverArg0Regs
- 	<api: 'extern void (*ceEnterCogCodePopReceiverArg0Regs)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnterCogCodePopReceiverArg0Regs numArgs: 2!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ceEnterCogCodePopReceiverArg1Arg0Regs (in category 'simulation only') -----
- ceEnterCogCodePopReceiverArg1Arg0Regs
- 	<api: 'extern void (*ceEnterCogCodePopReceiverArg1Arg0Regs)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnterCogCodePopReceiverArg1Arg0Regs numArgs: 3!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>enterCogCodePopReceiverArg0Regs (in category 'debugging') -----
- enterCogCodePopReceiverArg0Regs
- 	"This is a static version of ceEnterCogCodePopReceiverArg0Regs
- 	 for break-pointing when debugging in C."
- 	<api>
- 	<inline: false>
- 	"This exists only for break-pointing."
- 	self cCode: [self realCEEnterCogCodePopReceiverArg0Regs]
- 		inSmalltalk: [self ceEnterCogCodePopReceiverArg0Regs]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>enterCogCodePopReceiverArg1Arg0Regs (in category 'debugging') -----
- enterCogCodePopReceiverArg1Arg0Regs
- 	"This is a static version of ceEnterCogCodePopReceiverArg1Arg0Regs
- 	 for break-pointing when debugging in C."
- 	<api>
- 	<inline: false>
- 	"This exists only for break-pointing."
- 	self cCode: [self realCEEnterCogCodePopReceiverArg1Arg0Regs]
- 		inSmalltalk: [self ceEnterCogCodePopReceiverArg1Arg0Regs]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCreateIntegralResultOop:ofAtomicType:in: (in category 'callout support') -----
  ffiCreateIntegralResultOop: retVal ofAtomicType: atomicType in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #retVal type: #usqLong>
  	"Callout support. Return the appropriate oop for the given atomic type"
  	| shift value mask byteSize |
  	self assert: atomicType < FFITypeSingleFloat.
  
  	atomicType = FFITypeBool ifTrue:[
  			"Make sure bool honors the byte size requested"
  			byteSize := calloutState ffiRetHeader bitAnd: FFIStructSizeMask.
  			value := byteSize = 4
  						ifTrue:[retVal]
  						ifFalse:[retVal bitAnd: 1 << (byteSize * 8) - 1].
  			^value = 0
  				ifTrue:[interpreterProxy falseObject]
  				ifFalse:[interpreterProxy trueObject]].
  	atomicType <= FFITypeSignedInt ifTrue:[
  		"these are all generall integer returns"
  		atomicType <= FFITypeSignedShort ifTrue:[
  			"byte/short. first extract partial word, then sign extend"
  			shift := (atomicType >> 1) * 8. "# of significant bits"
  			value := retVal bitAnd: (1 << shift - 1). 
  			(atomicType anyMask: 1) ifTrue:[
  				"make the guy signed"
  				mask := 1 << (shift-1).
  				value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  			^interpreterProxy integerObjectOf: value].
  		"32bit integer return"
  		^(atomicType anyMask: 1)
  			ifTrue:[interpreterProxy signed32BitIntegerFor: retVal] "signed return"
  			ifFalse:[interpreterProxy positive32BitIntegerFor: retVal]]. "unsigned return"
  
  	"longlong, char"
+ 	^(atomicType >> 1) = (FFITypeSignedLongLong >> 1) 
+ 		ifTrue:
+ 			[(atomicType anyMask: 1)
- 	(atomicType >> 1) = (FFITypeSignedLongLong >> 1) 
- 		ifTrue:[^(atomicType anyMask: 1)
  				ifTrue:[interpreterProxy signed64BitIntegerFor: retVal] "signed return"
  				ifFalse:[interpreterProxy positive64BitIntegerFor: retVal]]
+ 		ifFalse:
+ 			[interpreterProxy characterObjectOf:
+ 				(retVal bitAnd: (self cppIf: #SPURVM
+ 									ifTrue: [16rFFFFFFFF]
+ 									ifFalse: [255]))]!
- 		ifFalse:[^interpreterProxy 
- 					fetchPointer: (retVal bitAnd: 255)
- 					ofObject: interpreterProxy characterTable]!

Item was added:
+ ----- Method: VMMaker class>>generateAllSistaConfigurationsUnderVersionControl (in category 'configurations') -----
+ generateAllSistaConfigurationsUnderVersionControl
+ 	self generateSqueakCogSistaVM;
+ 		generateSqueakSpurCogSistaVM!



More information about the Vm-dev mailing list