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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 04:40:36 UTC 2013


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

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

Name: VMMaker.oscog-eem.549
Author: eem
Time: 8 December 2013, 3:42:35.391 pm
UUID: d2a4f1c3-8b11-4e93-9ad1-3e3ab35bbddd
Ancestors: VMMaker.oscog-eem.548

Fix allocateSlots:format:classIndex: to not chew into the interpreter
reserve.  That's only for allocateNewSpaceSlots:format:classIndex:.

Fix enumeration of newSpace objects to be in addfressSpace order,
survivor space first, eden second. This allows printObjectsFrom:to:
to determine the start of a newSpace object correctly.

Fix the store check on SpurMemMgr>>clone:.

Add cmUsesMethodClass flag and use it to reduce
 use of followForwardedLiteralsIn: in CoInterpreter's
followNecessaryForwardingInMethod:.
Make makeBaseFrameFor: call followNecessaryForwardingInMethod:.

Add StackToRegisterMapping2RegArgsCogit although it is decidedly
non-functional at the moment.

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

Item was added:
+ ----- Method: CoInterpreter>>followNecessaryForwardingInMethod: (in category 'lazy become') -----
+ followNecessaryForwardingInMethod: methodObj
+ 	"To avoid any chance of a forwarded object during super sends we follow the
+ 	 methodClassAssociation.  The forwarded object send fault only copes with
+ 	 normal sends to instances."
+ 	| cogMethod header |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	super followNecessaryForwardingInMethod: methodObj.
+ 	header := self rawHeaderOf: methodObj.
+ 	(self isCogMethodReference: header) ifTrue:
+ 		[cogMethod := self cCoerceSimple: header to: #'CogMethod *'.
+ 		 cogMethod cmUsesMethodClass ifTrue:
+ 			[cogit followForwardedLiteralsIn: cogMethod]]!

Item was changed:
  ----- Method: CoInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page.  Override to
  	 hold the caller context in a different place,  In the StackInterpreter we use
  	 the caller saved ip, but in the Cog VM caller saved ip is the ceBaseReturn:
  	 trampoline.  Simply hold the caller context in the first word of the stack."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	"theIP must be typed as signed because it is assigned ceCannotResumePC and so maybe implicitly typed as unsigned."
  	<var: #theIP type: #sqInt>
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC signedIntFromLong < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory followNonImmediateField: MethodIndex ofObject: aContext.
+ 	self followNecessaryForwardingInMethod: theMethod.
  	page := self newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: aContext.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 self cppIf: MULTIPLEBYTECODESETS
  				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  					[(theIP signedIntFromLong > 0
  					  and: [(self methodHeaderHasPrimitive: header)
  					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) ifTrue:
  						[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)]].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: 0.
  	"N.B.  Don't set the baseFP, which marks the page as in use, until after
  	 ensureMethodIsCogged: and/or instructionPointer:forContext:frame:. These
  	 can cause a compiled code compaction which, if marked as in use, will
  	 examine this partially initialized page and crash."
  	page headFP: pointer.
  	"Create either a machine code frame or an interpreter frame based on the pc.  If the pc is -ve
  	 it is a machine code pc and so we produce a machine code frame.  If +ve an interpreter frame.
  	 N.B. Do *not* change this to try and map from a bytecode pc to a machine code frame under
  	 any circumstances.  See ensureContextIsExecutionSafeAfterAssignToStackPointer:"
  	theIP signedIntFromLong < 0
  		ifTrue:
  			[| cogMethod |
  			 "Since we would have to generate a machine-code method to be able to map
  			  the native pc anyway we should create a native method and native frame."
  			 cogMethod := self ensureMethodIsCogged: theMethod.
  			 theMethod := cogMethod asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
  					["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP = HasBeenReturnedFromMCPC signedIntFromLong
  						ifTrue:
  							[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
  												inHomeMethod: (self cCoerceSimple: theMethod
  																	to: #'CogMethod *')) asInteger.
  							 theMethod = 0 ifTrue:
  								[self error: 'cannot find machine code block matching closure''s startpc'].
  							 theIP := cogit ceCannotResumePC]
  						ifFalse:
  							[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
  							 theMethod := theMethod - ((theIP signedBitShift: -16) * cogit blockAlignment).
  							 theIP := theMethod - theIP signedIntFromShort].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						put: theMethod + MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag]
  				ifFalse:
  					[self assert: (theIP signedBitShift: -16) >= -1.
  					 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP := theIP = HasBeenReturnedFromMCPC signedIntFromLong
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: 0. "FoxIFSavedIP"
  			theIP := self iframeInstructionPointerForIndex: theIP method: theMethod].
  	page baseFP: page headFP.
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - BytesPerWord) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was changed:
  VMStructType subclass: #CogBlockMethod
+ 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cmUsesMethodClass cmUnusedFlags stackCheckOffset'
- 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cmUnusedFlags stackCheckOffset'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
  !CogBlockMethod commentStamp: 'eem 1/9/2011 08:41' prior: 0!
  I am the rump method header for a block method embedded in a full CogMethod.  I am the superclass of CogMethod, which is a Cog method header proper.  Instances of both classes have the same second word.  The homeOffset abd startpc fields are overlaid on the objectHeader in a CogMethod.  In C I look like
  
  	typedef struct {
  		unsigned short	homeOffset;
  		unsigned short	startpc;
  
  		unsigned		cmNumArgs : 8;
  		unsigned		cmType : 3;
  		unsigned		cmRefersToYoung : 1;
  		unsigned		cmIsUnlinked : 1;
  		unsigned		cmUsageCount : 3;
  		unsigned		stackCheckOffset : 16;
  	} CogBlockMethod;
  
  My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64.!

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"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
  								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
  								['cmUsageCount']			-> [#(unsigned ' : 3')]. "see CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUsesMethodClass']		-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUnusedFlags']			-> [#(unsigned ' : 2')].
- 								['cmUnusedFlags']			-> [#(unsigned ' : 3')].
  								['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"
  							otherwise:
  								[#sqInt])]]!

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

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

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cmUsesMethodClass (in category 'accessing') -----
+ cmUsesMethodClass
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cmUsesMethodClass: (in category 'accessing') -----
+ cmUsesMethodClass: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cmUsesMethodClass (in category 'accessing') -----
+ cmUsesMethodClass
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cmUsesMethodClass: (in category 'accessing') -----
+ cmUsesMethodClass: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^aValue!

Item was added:
+ ----- Method: CogMethodSurrogate32>>cmUsesMethodClass (in category 'accessing') -----
+ cmUsesMethodClass
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogMethodSurrogate32>>cmUsesMethodClass: (in category 'accessing') -----
+ cmUsesMethodClass: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^aValue!

Item was added:
+ ----- Method: CogMethodSurrogate64>>cmUsesMethodClass (in category 'accessing') -----
+ cmUsesMethodClass
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogMethodSurrogate64>>cmUsesMethodClass: (in category 'accessing') -----
+ cmUsesMethodClass: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^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 postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall 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 ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs 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 primitiveIndex backEnd postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall 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 ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs 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 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>>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.
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogMethod: selector!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	<var: #originalMethod type: #'CogMethod *'>
  	| methodHeader originalMethod |
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	methodHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: methodHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			methodHeader := originalMethod methodHeader.
  			self cppIf: NewspeakVM ifTrue: [methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((coInterpreter literalCountOfHeader: methodHeader) - 2).
+ 	method cmUsesMethodClass: usesMethodClass.
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	^method!

Item was changed:
  ----- Method: NewObjectMemory>>printObjectsFrom:to: (in category 'debug printing') -----
  printObjectsFrom: startAddress to: endAddress
  	<api>
  	| oop |
  	oop := startAddress.
+ 	[self oop: oop isLessThan: endAddress] whileTrue:
- 	[oop < endAddress] whileTrue:
  		[(self isFreeObject: oop) ifFalse:
  			[self printOop: oop].
  		oop := self objectAfter: oop].!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genSendDynamicSuper: selector numArgs: numArgs
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	self MoveMw: numArgs * BytesPerWord r: SPReg R: ReceiverResultReg.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	self MoveCw: selector R: ClassReg.
  	self CallNewspeakSend: (dynamicSuperSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 	usesMethodClass := true.
  	self flag: 'currently caller pushes result'.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendSuper:numArgs: (in category 'bytecode generators') -----
  genSendSuper: selector numArgs: numArgs
  	<inline: false>
  	self assert: needsFrame.
  	self assert: (numArgs between: 0 and: 256). "say"
  	self assert: (objectMemory addressCouldBeOop: selector).
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self MoveMw: numArgs * BytesPerWord r: SPReg R: ReceiverResultReg.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	self MoveCw: selector R: ClassReg.
  	self CallSend: (superSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 	usesMethodClass := true.
  	self flag: 'currently caller pushes result'.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateNewSpaceSlots:format:classIndex: (in category 'allocation') -----
  allocateNewSpaceSlots: numSlots format: formatField classIndex: classIndex
  	"Allocate an object with numSlots in newSpace.  This is for the `ee' execution engine allocations,
+ 	 and must be satisfied.  If no memory is available, abort.  If the allocation pushes freeStart past
+ 	 scavengeThreshold and a scavenge is not already scheduled, schedule a scavenge."
- 	 and must be satisfied.  If no memory is available, abort."
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
  	 16 bytes otherwise (num slots in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[newObj := freeStart + self baseHeaderSize.
  			 numBytes := self baseHeaderSize + self baseHeaderSize "double header"
  						+ (numSlots + (numSlots bitAnd: 1) * self bytesPerSlot)] "roundTo allocationUnit"
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots <= 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots + (numSlots bitAnd: 1) * self bytesPerSlot])]. "roundTo allocationUnit"
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
  		 freeStart + numBytes > scavenger eden limit ifTrue:
  			[self error: 'no room in eden for allocateNewSpaceSlots:format:classIndex:'.
  			 ^0]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
+ 	"Allocate an object with numSlots space.  If there is room beneath scavengeThreshold
+ 	 allocate in newSpace, otherwise alocate in oldSpace.  If there is not room in newSpace
+ 	 and a scavenge is not already scheduled, schedule a scavenge."
  	<inline: true>
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
  	 16 bytes otherwise (num slots in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[newObj := freeStart + self baseHeaderSize.
  			 numBytes := self baseHeaderSize + self baseHeaderSize "double header"
  						+ (numSlots + (numSlots bitAnd: 1) * self bytesPerSlot)] "roundTo allocationUnit"
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots <= 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots + (numSlots bitAnd: 1) * self bytesPerSlot])]. "roundTo allocationUnit"
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
+ 		 ^self allocateSlotsInOldSpace: numSlots bytes: numBytes format: formatField classIndex: classIndex].
- 		 freeStart + numBytes > scavenger eden limit ifTrue:
- 			[^self allocateSlotsInOldSpace: numSlots bytes: numBytes format: formatField classIndex: classIndex]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateNewSpaceSlots:format:classIndex: (in category 'allocation') -----
  allocateNewSpaceSlots: numSlots format: formatField classIndex: classIndex
  	"Allocate an object with numSlots in newSpace.  This is for the `ee' execution engine allocations,
+ 	 and must be satisfied.  If no memory is available, abort.  If the allocation pushes freeStart past
+ 	 scavengeThreshold and a scavenge is not already scheduled, schedule a scavenge."
- 	 and must be satisfied.  If no memory is available, abort."
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
  	 16 bytes otherwise (num slots in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[numSlots > 16rffffffff ifTrue:
  				[^nil].
  			 newObj := freeStart + self baseHeaderSize.
  			 numBytes := (self baseHeaderSize + self baseHeaderSize) "double header"
  						+ (numSlots * self bytesPerSlot)]
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots < 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots * self bytesPerSlot])].
  	
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
  		 freeStart + numBytes > scavenger eden limit ifTrue:
  			[self error: 'no room in eden for allocateNewSpaceSlots:format:classIndex:'.
  			 ^0]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
+ 	"Allocate an object with numSlots space.  If there is room beneath scavengeThreshold
+ 	 allocate in newSpace, otherwise alocate in oldSpace.  If there is not room in newSpace
+ 	 and a scavenge is not already scheduled, schedule a scavenge."
  	<inline: true>
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
  	 16 bytes otherwise (num slots in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[numSlots > 16rffffffff ifTrue:
  				[^nil].
  			 newObj := freeStart + self baseHeaderSize.
  			 numBytes := (self baseHeaderSize + self baseHeaderSize) "double header"
  						+ (numSlots * self bytesPerSlot)]
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots < 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots * self bytesPerSlot])].
  	
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
+ 		 ^self allocateSlotsInOldSpace: numSlots bytes: numBytes format: formatField classIndex: classIndex].
- 		 freeStart + numBytes > scavenger eden limit ifTrue:
- 			[^self allocateSlotsInOldSpace: numSlots bytes: numBytes format: formatField classIndex: classIndex]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was changed:
  ----- Method: SpurMemoryManager>>allNewSpaceEntitiesDo: (in category 'object enumeration') -----
  allNewSpaceEntitiesDo: aBlock
  	"Enumerate all new space objects, including free objects."
  	<inline: true>
  	| prevObj prevPrevObj objOop limit |
  	prevPrevObj := prevObj := nil.
  	"After a scavenge eden is empty, futureSpace is empty, and all newSpace objects are
+ 	  in pastSpace.  Objects are allocated in eden.  So enumerate only pastSpace and eden."
+ 	self assert: scavenger pastSpace start < scavenger eden start.
- 	  in pastSpace.  Objects are allocated in eden.  So enumerate only eden and pastSpace."
- 	objOop := self objectStartingAt: scavenger eden start.
- 	[self oop: objOop isLessThan: freeStart] whileTrue:
- 		[aBlock value: objOop.
- 		 prevPrevObj := prevObj.
- 		 prevObj := objOop.
- 		 objOop := self objectAfter: objOop limit: freeStart].
  	objOop := self objectStartingAt: scavenger pastSpace start.
  	limit := pastSpaceStart.
  	[self oop: objOop isLessThan: limit] whileTrue:
  		[aBlock value: objOop.
  		 prevPrevObj := prevObj.
  		 prevObj := objOop.
  		 objOop := self objectAfter: objOop limit: limit].
+ 	objOop := self objectStartingAt: scavenger eden start.
+ 	[self oop: objOop isLessThan: freeStart] whileTrue:
+ 		[aBlock value: objOop.
+ 		 prevPrevObj := prevObj.
+ 		 prevObj := objOop.
+ 		 objOop := self objectAfter: objOop limit: freeStart].
  	self touch: prevPrevObj.
  	self touch: prevObj!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateNewSpaceSlots:format:classIndex: (in category 'allocation') -----
  allocateNewSpaceSlots: numSlots format: formatField classIndex: classIndex
+ 	"Allocate an object with numSlots in newSpace.  This is for the `ee' execution engine allocations,
+ 	 and must be satisfied.  If no memory is available, abort.  If the allocation pushes freeStart past
+ 	 scavengeThreshold and a scavenge is not already scheduled, schedule a scavenge."
  	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
+ 	"Allocate an object with numSlots space.  If there is room beneath scavengeThreshold
+ 	 allocate in newSpace, otherwise alocate in oldSpace.  If there is not room in newSpace
+ 	 and a scavenge is not already scheduled, schedule a scavenge."
  	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>clone: (in category 'allocation') -----
  clone: objOop
  	| numSlots newObj |
  	numSlots := self numSlotsOf: objOop.
  	
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[newObj := self allocateSlotsInOldSpace: numSlots
  							format: (self formatOf: objOop)
  							classIndex: (self classIndexOf: objOop)]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots
  							format: (self formatOf: objOop)
  							classIndex: (self classIndexOf: objOop)].
  	(self isPointersNonImm: objOop)
  		ifTrue:
+ 			[| hasYoung |
+ 			 hasYoung := false.
+ 			 0 to: numSlots - 1 do:
- 			[0 to: numSlots - 1 do:
  				[:i| | oop |
  				oop := self fetchPointer: i ofObject: objOop.
  				((self isNonImmediate: oop)
  				 and: [self isForwarded: oop]) ifTrue:
  					[oop := self followForwarded: oop].
+ 				((self isNonImmediate: oop)
+ 				 and: [self isYoungObject: oop]) ifTrue:
+ 					[hasYoung := true].
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: oop].
+ 			(hasYoung
- 			((self isRemembered: objOop)
  			 and: [(self isYoungObject: newObj) not]) ifTrue:
  				[scavenger remember: newObj.
  				 self setIsRememberedOf: newObj to: true]]
  		ifFalse:
  			[0 to: numSlots - 1 do:
  				[:i|
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: (self fetchPointer: i ofObject: objOop)]].
  	^newObj!

Item was added:
+ ----- Method: SpurMemoryManager>>printObjectsFrom:to: (in category 'debug printing') -----
+ printObjectsFrom: startAddress to: endAddress
+ 	<api>
+ 	| oop |
+ 	oop := self objectBefore: startAddress.
+ 	oop := oop
+ 				ifNil: [startAddress]
+ 				ifNotNil: [(self objectAfter: oop) = startAddress
+ 							ifTrue: [startAddress]
+ 							ifFalse: [oop]].
+ 	[self oop: oop isLessThan: endAddress] whileTrue:
+ 		[(self isFreeObject: oop) ifFalse:
+ 			[self printOop: oop].
+ 		oop := self objectAfter: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>shortPrintObjectsFrom:to: (in category 'debug printing') -----
+ shortPrintObjectsFrom: startAddress to: endAddress
+ 	<api>
+ 	| oop |
+ 	oop := self objectBefore: startAddress.
+ 	oop := oop
+ 				ifNil: [startAddress]
+ 				ifNotNil: [(self objectAfter: oop) = startAddress
+ 							ifTrue: [startAddress]
+ 							ifFalse: [oop]].
+ 	[self oop: oop isLessThan: endAddress] whileTrue:
+ 		[(self isFreeObject: oop) ifFalse:
+ 			[self shortPrintOop: oop].
+ 		oop := self objectAfter: oop]!

Item was changed:
  ----- Method: StackInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	page := self newStackPage.
  	pointer := page baseAddress.
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	theMethod := objectMemory followNonImmediateField: MethodIndex ofObject: aContext.
+ 	self followNecessaryForwardingInMethod: theMethod.
  	(objectMemory isIntegerObject: theIP) ifFalse:
  		[self error: 'context is not resumable'].
  	theIP := objectMemory integerValueOf: theIP.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory followField: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 self cppIf: MULTIPLEBYTECODESETS
  				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  					[(theIP signedIntFromLong > 0
  					  and: [(self methodHeaderHasPrimitive: header)
  					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) ifTrue:
  						[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)]].
  			 stackPages longAt: pointer put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is sender context in base frame"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: 0.
  	page baseFP: pointer; headFP: pointer.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: theMethod.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: aContext.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	theIP := self iframeInstructionPointerForIndex: theIP method: theMethod.
  	stackPages longAt: (pointer := pointer - BytesPerWord) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was added:
+ StackToRegisterMappingCogit subclass: #StackToRegisterMapping2RegArgsCogit
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: StackToRegisterMapping2RegArgsCogit>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	<api>
+ 	"Use of the macro allows the compiler to avoid the call and test in cointerpreter.c"
+ 	<cmacro: '() 2'>
+ 	^2!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSendDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genMarshalledSendDynamicSuper: selector numArgs: numArgs
  	<inline: false>
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	self MoveCw: selector R: ClassReg.
  	self CallNewspeakSend: (dynamicSuperSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 	usesMethodClass := true.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSendSuper:numArgs: (in category 'bytecode generators') -----
  genMarshalledSendSuper: selector numArgs: numArgs
  	<inline: false>
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	self MoveCw: selector R: ClassReg.
  	self CallSend: (superSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 	usesMethodClass := true.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list