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

commits at source.squeak.org commits at source.squeak.org
Sat Apr 16 22:52:52 UTC 2016


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

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

Name: VMMaker.oscog-cb.1811
Author: cb
Time: 16 April 2016, 3:51:06.783848 pm
UUID: fd4b3b24-5fd4-45ea-bae5-725bb30b6f12
Ancestors: VMMaker.oscog-cb.1810

Rename ScratchNReg to ExtraNReg.  Provide availableRegisterOrNoneFor: in ARM & X64 to allocate ExtraNRegs when available.
Provide isCallerSavedReg: as a convenience and use it where (self register: ReceiverResultReg isInMask: callerSavedRegMask) was.
Abstract away the simStackEntryClass for RegisterAllocatingCogit that will appear soon.

P.S.  Don't merge with VMMaker.oscog-nice.1811, which is experimental.  The API Eliot & Clément would like to see is something like
#if SQUEAK_INTERNAL_PLUGIN
# define isLargeIntegerOop(oop) \
     (!isImmediate(oop) && (unsigned sqInt)(classIndexOf(oop) - ClassLargeNegativeIntegerCompactIndex) <= 1)
#else
extern sqInt isLargeIntegerOop(sqInt)
#endif
(ClassLargeNegativeIntegerCompactIndex = 32, ClassLargePositiveIntegerCompactIndex = 33, so the above allows us to fetch the class index once, not twice)
This is way quicker than three calls through the interpreterProxy.  Internal plugins should have to pay minimal costs for class tests.

=============== Diff against VMMaker.oscog-cb.1810 ===============

Item was changed:
  ----- Method: CogARMCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"N.B. According to BSABI, R0-R3 are caller-save, R4-R12 are callee save.
  	 Note that R9 might be a special register for the implementation. In some slides
  	 it is refered to as sb. R10 can contain the stack limit (sl), R11 the fp. R12 is an
  	 intra-procedure scratch instruction pointer for link purposes. It can also be used.
  	 R10 is used as temporary inside a single abstract opcode implementation"
  	"R0-R3 are used when calling back to the interpreter. Using them would require
  	 saving and restoring their values, so they are omitted so far. R12 is the only
  	 scratch register at the moment.."
  
  	super initializeAbstractRegisters.
  
  	TempReg			:= R0.
  	ClassReg			:= R8.
  	ReceiverResultReg	:= R7.
  	SendNumArgsReg	:= R6.
  	SPReg				:= SP. "R13"
  	FPReg				:= R11.
  	Arg0Reg			:= R4.
  	Arg1Reg			:= R5.
  	VarBaseReg		:= ConcreteVarBaseReg. "Must be callee saved"
  	RISCTempReg		:= ConcreteIPReg. "a.k.a. IP"
+ 	Extra0Reg			:= R12.
- 	Scratch0Reg		:= R12.
  	LinkReg				:= LR. "R14"
  	PCReg				:= PC. "R15"	
  
  	DPFPReg0			:= D0.
  	DPFPReg1			:= D1.
  	DPFPReg2			:= D2.
  	DPFPReg3			:= D3.
  	DPFPReg4			:= D4.
  	DPFPReg5			:= D5.
  	DPFPReg6			:= D6.
  	DPFPReg7			:= D7
  !

Item was added:
+ ----- Method: CogARMCompiler>>availableRegisterOrNoneFor: (in category 'register allocation') -----
+ availableRegisterOrNoneFor: liveRegsMask
+ 	"Answer an unused abstract register in the liveRegMask.
+ 	 Subclasses with more registers can override to answer them.
+ 	 N.B. Do /not/ allocate TempReg."
+ 	<returnTypeC: #sqInt>
+ 	(cogit register: Extra0Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra0Reg].
+ 	^super availableRegisterOrNoneFor: liveRegsMask!

Item was changed:
  ----- Method: CogAbstractInstruction>>availableRegisterOrNoneFor: (in category 'register allocation') -----
  availableRegisterOrNoneFor: liveRegsMask
  	"Answer an unused abstract register in the liveRegMask.
+ 	 Subclasses with more registers can override to answer them.
+ 	 N.B. Do /not/ allocate TempReg."
- 	 Subclasses with more registers can override to answer them."
  	<returnTypeC: #sqInt>
- 	self flag: 'searching physical registers that are not assigned to abstract registers first will do a better job and allocate with fewer conflicts.  But this will be much easier if we use the same range for concrete and abstract registers (0-N) and simply number abstract registers the same as their corresponding concrete registers.'.
  	(cogit register: Arg1Reg isInMask: liveRegsMask) ifFalse:
  		[^Arg1Reg].
  	(cogit register: Arg0Reg isInMask: liveRegsMask) ifFalse:
  		[^Arg0Reg].
  	(cogit register: SendNumArgsReg isInMask: liveRegsMask) ifFalse:
  		[^SendNumArgsReg].
  	(cogit register: ClassReg isInMask: liveRegsMask) ifFalse:
  		[^ClassReg].
  	(cogit register: ReceiverResultReg isInMask: liveRegsMask) ifFalse:
  		[^ReceiverResultReg].
  	^NoReg!

Item was changed:
  SharedPool subclass: #CogAbstractRegisters
  	instanceVariableNames: ''
+ 	classVariableNames: 'Arg0Reg Arg1Reg ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg FPReg LinkReg NoReg PCReg RISCTempReg ReceiverResultReg SPReg SendNumArgsReg TempReg VarBaseReg'
- 	classVariableNames: 'Arg0Reg Arg1Reg ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 FPReg LinkReg NoReg PCReg RISCTempReg ReceiverResultReg SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg TempReg VarBaseReg'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogAbstractRegisters commentStamp: 'eem 12/26/2015 14:06' prior: 0!
  I am a pool for the abstract register set that the Cogit uses to define its model of Smalltalk compiled to machine code.!

Item was changed:
  ----- Method: CogAbstractRegisters class>>initialize (in category 'class initialization') -----
  initialize
  	"Define a fixed set of abstract register names used in code generation for Smalltalk code.
  	 These are given concrete values by the currently in-use back end, which is a subclass of
  	 CogAbstractInstruction; see implementors of initializeAbstractRegisters.
  
  	 We assume concrete registers defined by the back ends are in the range 0 to N, possibly
  	 with integer registers and floating-point registers using overlapping ranges of indices.
  	 Here we initialize all registers to #undefined, leaving it to initializeAbstractRegisters to
  	 initialize the subset of the abstract registers that a platform actually uses."
  
  	"NoReg encodes no register, e.g. for parameters that supply an optional register.
  	 Being negative it is distinct from abstract and concrete registers in the 0 to N range."
  	NoReg := -1.
  
  	"The core set of abstract registers that define the Cogit's model of Smalltalk code
  	 provide for a register-based calling convention oriented towards inline cacheing and
  	 executing a core set of machine code primitives in registers.  The set is composed of
  	 8 registers, dictated by the available registers on IA32."
  	"Smalltalk machine code executes on stack pages in the stack zone, requiring frame and stack pointers."
  	FPReg				:= #undefined.	"A frame pointer is used for Smalltalk frames."
  	SPReg				:= #undefined.
  	ReceiverResultReg	:= #undefined.	"The receiver at point of send, and return value of a send"
  	ClassReg			:= #undefined.	"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg	:= #undefined.	"Sends > 2 args set the arg count in this reg"
  	Arg0Reg			:= #undefined.	"In the StackToRegisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg			:= #undefined.
  	TempReg			:= #undefined.
  
  	"A small fixed set of abstract scratch registers for register-rich machines (ARM can use 1, x64 can use 6 or 7)."
+ 	Extra0Reg := #undefined.
+ 	Extra1Reg := #undefined.
+ 	Extra2Reg := #undefined.
+ 	Extra3Reg := #undefined.
+ 	Extra4Reg := #undefined.
+ 	Extra5Reg := #undefined.
+ 	Extra6Reg := #undefined.
+ 	Extra7Reg := #undefined.
- 	Scratch0Reg := #undefined.
- 	Scratch1Reg := #undefined.
- 	Scratch2Reg := #undefined.
- 	Scratch3Reg := #undefined.
- 	Scratch4Reg := #undefined.
- 	Scratch5Reg := #undefined.
- 	Scratch6Reg := #undefined.
- 	Scratch7Reg := #undefined.
  
  	"RISC-specific registers"
  	LinkReg			:= #undefined.
  	RISCTempReg	:= #undefined.		"Used to synthesize CISC instructions from multiple RISC instructions."
  	PCReg			:= #undefined.		"If the processor has an assignable pc, e.g. ARM"
  	VarBaseReg	:= #undefined.		"If useful, points to base of interpreter variables."
  
  	"Up to 16 floating-point registers. e.g. IA32+SSE2 can use 8, x64 can use 16."
  	DPFPReg0	:= #undefined.
  	DPFPReg1	:= #undefined.
  	DPFPReg2	:= #undefined.
  	DPFPReg3	:= #undefined.
  	DPFPReg4	:= #undefined.
  	DPFPReg5	:= #undefined.
  	DPFPReg6	:= #undefined.
  	DPFPReg7	:= #undefined.
  	DPFPReg8	:= #undefined.
  	DPFPReg9	:= #undefined.
  	DPFPReg10	:= #undefined.
  	DPFPReg11	:= #undefined.
  	DPFPReg12	:= #undefined.
  	DPFPReg13	:= #undefined.
  	DPFPReg14	:= #undefined.
  	DPFPReg15	:= #undefined!

Item was changed:
  ----- Method: CogMIPSELCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"See MIPSConstants>>initializeRegisters for a description of the C ABI."
  
  	"Note we can fit all of the abstract registers in C preserved registers, and
  	 not need to save or restore them at runtime calls."
  	super initializeAbstractRegisters.
  
  	ReceiverResultReg		:= S0.
  	Arg0Reg				:= S1.
  	Arg1Reg				:= S2.
  	ClassReg				:= S3.
  	SendNumArgsReg		:= S4.
  	TempReg				:= S5.
  	VarBaseReg			:= S6. "Must be callee saved"
  	SPReg					:= SP.
  	FPReg					:= FP.
  	RISCTempReg			:= AT.
  	LinkReg					:= RA.
  
  	self flag: #todo.
+ 	"Extra0Reg			:= ??.
+ 	Extra1Reg			:= ??.
+ 	Extra2Reg			:= ??.
+ 	Extra3Reg			:= ??.
+ 	Extra4Reg			:= ??.
+ 	Extra5Reg			:= ??.
+ 	Extra6Reg			:= ??.
+ 	Extra7Reg			:= ??."
- 	"Scratch0Reg			:= ??.
- 	Scratch1Reg			:= ??.
- 	Scratch2Reg			:= ??.
- 	Scratch3Reg			:= ??.
- 	Scratch4Reg			:= ??.
- 	Scratch5Reg			:= ??.
- 	Scratch6Reg			:= ??.
- 	Scratch7Reg			:= ??."
  
  	self flag: #todo.
  	"DPFPReg0				:= ??.
  	DPFPReg1				:= ??.
  	DPFPReg2				:= ??.
  	DPFPReg3				:= ??.
  	DPFPReg4				:= ??.
  	DPFPReg5				:= ??.
  	DPFPReg6				:= ??.
  	DPFPReg7				:= ??.
  	DPFPReg8				:= ??.
  	DPFPReg9				:= ??.
  	DPFPReg10				:= ??.
  	DPFPReg11				:= ??.
  	DPFPReg12				:= ??.
  	DPFPReg13				:= ??.
  	DPFPReg14				:= ??.
  	DPFPReg15				:= ??"!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genGetSizeOf:into:formatReg:scratchReg:abortJumpsInto: (in category 'primitive generators') -----
  genGetSizeOf: sourceReg into: destReg formatReg: formatReg scratchReg: scratchReg abortJumpsInto: aBinaryBlock
  	"Get the size of the non-immediate object in sourceReg into destReg using formatReg
  	 and scratchReg as temps.  None of these registers can overlap.  Supply the jumps
  	 taken if the object in sourceReg is not indexable, or if the object in sourceReg is a
  	 context.. Hack: If the object has a pointer format other than 2 leave the number of
  	 fixed fields in formatReg.  Used by primitiveSize, primitiveAt, and primitiveAtPut"
  	<returnTypeC: #'AbstractInstruction *'>
  	| jumpNotIndexable
  	  jumpBytesDone jumpShortsDone jumpArrayDone jump32BitLongsDone jump64BitLongsDone
  	  jumpIsBytes jumpHasFixedFields jumpIsShorts jumpIs32BitLongs jumpIsContext  |
  	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpArrayDone type: #'AbstractInstruction *'>
  	<var: #jumpIs32BitLongs type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jump32BitLongsDone type: #'AbstractInstruction *'>
  	<var: #jump64BitLongsDone type: #'AbstractInstruction *'>
  
  	"formatReg := self formatOf: sourceReg"
  	self genGetFormatOf: sourceReg
  		into: formatReg
  		leastSignificantHalfOfBaseHeaderIntoScratch: scratchReg.
  
  	self genGetNumSlotsOf: sourceReg into: destReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpArrayDone := cogit JumpZero: 0.
  	jumpNotIndexable := cogit JumpLess: 0.
  					cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpHasFixedFields := cogit JumpLessOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpIs32BitLongs := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: formatReg.
  	jump64BitLongsDone := cogit JumpZero: 0.
  	jumpNotIndexable jmpTarget: cogit Label.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: destReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  		cogit SubR: formatReg R: destReg.
  	jumpBytesDone := cogit Jump: 0.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: destReg).
  		cogit AndCq: objectMemory wordSize >> 1 - 1 R: formatReg.
  		cogit SubR: formatReg R: destReg.
  	jumpShortsDone := cogit Jump: 0.
  
  	jumpIs32BitLongs jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: destReg).
  		cogit AndCq: objectMemory wordSize >> 2 - 1 R: formatReg.
  		cogit SubR: formatReg R: destReg.
  	jump32BitLongsDone := cogit Jump: 0.
  
  	"formatReg contains fmt, now up for grabs.
  	 destReg contains numSlots, precious.
  	 sourceReg must be preserved"
  	jumpHasFixedFields jmpTarget:
  		(cogit AndCq: objectMemory classIndexMask R: scratchReg).
  	cogit MoveR: scratchReg R: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: scratchReg.
  	jumpIsContext := cogit JumpZero: 0.
+ 	self genGetClassObjectOfClassIndex: formatReg into: Extra0Reg scratchReg: scratchReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Extra0Reg destReg: formatReg.
- 	self genGetClassObjectOfClassIndex: formatReg into: Scratch0Reg scratchReg: scratchReg.
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Scratch0Reg destReg: formatReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit
  		AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg;
  		SubR: formatReg R: destReg.
  
  	jumpArrayDone jmpTarget:
  	(jump64BitLongsDone jmpTarget:
  	(jump32BitLongsDone jmpTarget:
  	(jumpShortsDone jmpTarget:
  	(jumpBytesDone jmpTarget:
  		cogit Label)))).
  	aBinaryBlock value: jumpNotIndexable value: jumpIsContext!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveAt (in category 'primitive generators') -----
  genPrimitiveAt
  	| formatReg convertToIntAndReturn methodInBounds
  	  jumpNotIndexable jumpImmediate jumpBadIndex
  	  jumpIsBytes jumpIsShorts jumpIsWords jumpIsMethod jumpIsArray jumpIsContext
  	  jumpHasFixedFields jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
  	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsMethod type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #methodInBounds type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #convertToIntAndReturn type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpFixedFieldsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpIsArray := cogit JumpZero: 0.
  	jumpNotIndexable := cogit JumpBelow: 0.
  					cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpHasFixedFields := cogit JumpBelowOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpIsWords := cogit JumpAboveOrEqual: 0.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexable jmpTarget: cogit Label.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsArray jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.	
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg R: TempReg.
  		cogit SubR: TempReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsMethod := cogit JumpAboveOrEqual: 0.
  	methodInBounds :=
  	(cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg).
  	cogit backEnd byteReadsZeroExtend
  		ifTrue:
  			[cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg]
  		ifFalse:
  			[cogit "formatReg already contains a value <= 16r1f, so no need to zero it"
  				MoveXbr: Arg1Reg R: ReceiverResultReg R: formatReg;
  				MoveR: formatReg R: ReceiverResultReg].
  	convertToIntAndReturn := cogit Label.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
  		cogit AndCq: 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpIsWords jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >>  (objectMemory shiftForWord - 1) R: Arg1Reg.
  	cogit MoveX32r: Arg1Reg R: ReceiverResultReg R: TempReg.
  	cogit MoveR: TempReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpHasFixedFields jmpTarget:
  		(cogit AndCq: objectMemory classIndexMask R: TempReg).
  	cogit MoveR: TempReg R: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: TempReg.
  	jumpIsContext := cogit JumpZero: 0.
+ 	self genGetClassObjectOfClassIndex: formatReg into: Extra0Reg scratchReg: TempReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Extra0Reg destReg: formatReg.
- 	self genGetClassObjectOfClassIndex: formatReg into: Scratch0Reg scratchReg: TempReg.
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Scratch0Reg destReg: formatReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit
  		AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg;
  		SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	"index is (formatReg (fixed fields) + Arg1Reg (0-rel index)) * wordSize + baseHeaderSize"
  	cogit AddR: formatReg R: Arg1Reg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsMethod jmpTarget: cogit Label.
  	"Now check that the index is beyond the method's literals..."
  	self getLiteralCountOf: ReceiverResultReg plusOne: true inBytes: true into: ClassReg scratch: TempReg.
  	cogit CmpR: Arg1Reg R: ClassReg.
  	cogit JumpBelow: methodInBounds.
  
  	jumpFixedFieldsOutOfBounds jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexable jmpTarget:
  	(jumpIsContext jmpTarget:
  	(jumpBadIndex jmpTarget:
  	(jumpImmediate jmpTarget: cogit Label)))))))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveAtPut (in category 'primitive generators') -----
  genPrimitiveAtPut
  	| formatReg methodInBounds
  	  jumpImmediate jumpBadIndex jumpImmutable jumpNotIndexablePointers jumpNotIndexableBits
  	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpIsShorts jumpHasFixedFields
  	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
  	  jumpWordsOutOfBounds jumpShortsOutOfBounds jumpBytesOutOfBounds
  	  jumpShortsOutOfRange jumpWordsOutOfRange jumpBytesOutOfRange
  	  jumpNonSmallIntegerValue jumpNotPointers
  	  |
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #methodInBounds type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexablePointers type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self cppIf: IMMUTABILITY
  		ifTrue:
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
  		ifFalse: 
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpNotPointers := cogit JumpAbove: 0.
  	"optimistic store check; assume index in range (almost always is)."
  	self genStoreCheckReceiverReg: ReceiverResultReg
  		valueReg: Arg1Reg
  		scratchReg: TempReg
  		inFrame: false.
  
  	cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpNotIndexablePointers := cogit JumpBelow: 0.
  	jumpHasFixedFields := cogit JumpNonZero: 0.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpHasFixedFields jmpTarget: cogit Label.
  	self genGetClassIndexOfNonImm: ReceiverResultReg into: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: formatReg.
  	jumpIsContext := cogit JumpZero: 0.
  	"get # fixed fields in formatReg"
+ 	self genGetClassObjectOfClassIndex: formatReg into: Extra0Reg scratchReg: TempReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Extra0Reg destReg: formatReg.
- 	self genGetClassObjectOfClassIndex: formatReg into: Scratch0Reg scratchReg: TempReg.
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Scratch0Reg destReg: formatReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: formatReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: formatReg R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpNotPointers jmpTarget: cogit Label.
  	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
  					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexableBits := cogit JumpBelow: 0.
  
  	"fall through to words"
  	cogit CmpCq: (objectMemory integerObjectOf: 16rFFFFFFFF) R: Arg1Reg.
  	jumpWordsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg.
  	cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize >> (objectMemory shiftForWord - 1) R: Arg0Reg.
  	cogit MoveR: TempReg X32r: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsBytes jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 255) R: Arg1Reg).
  	jumpBytesOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	cogit AndCq: objectMemory wordSize - 1 R: formatReg R: TempReg.
  	cogit SubR: TempReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
  	methodInBounds :=
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
  	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsShorts jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
  	jumpShortsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddR: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	"Now check that the index is beyond the method's literals..."
  	jumpIsCompiledMethod jmpTarget: cogit Label.
  	self getLiteralCountOf: ReceiverResultReg plusOne: true inBytes: true into: ClassReg scratch: TempReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	cogit JumpBelow: methodInBounds.
  
  	jumpIsContext jmpTarget:
  	(jumpNotIndexableBits jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
  	(jumpShortsOutOfRange jmpTarget:
  	(jumpWordsOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexablePointers jmpTarget:
  	(jumpNonSmallIntegerValue jmpTarget:
  	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label)))))))))))).
  	
  	self cppIf: IMMUTABILITY
  		ifTrue: [jumpImmutable jmpTarget: jumpIsContext getJmpTarget].
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
  
  	^0 "Can't be complete because of contexts."!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveMirrorNewWithArg (in category 'primitive generators') -----
  genPrimitiveMirrorNewWithArg
  	"Implement instantiateVariableClass:withSize: for convenient cases:
  	- the class argument has a hash
  	- the class argument is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	<option: #NewspeakVM>
  	| headerReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpTooSmall jumpImmediate
  	  jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  
  	self assert: cogit methodNumArgs = 2.
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg. "class arg"
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg. "num indexable slots arg"
  	"header will contain classIndex/class's hash & format & numSlots/fixed size"
  	headerReg := SendNumArgsReg.
  	"Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"
+ 	fillReg := Extra0Reg.
- 	fillReg := Scratch0Reg.
  	self assert: fillReg > 0.
  	"inst spec will hold class's instance specification and then byte size"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"check size and fail if not a +ve integer"
  	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
  
  	"Is the class arg pointers with at least 3 fields?"
  	jumpImmediate := self genJumpImmediate: Arg0Reg.
  	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
  	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
  	jumpTooSmall := cogit JumpLess: 0.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
  	jumpUnhashed := cogit JumpZero: 0.
  
  	"The basicNew: code below (copied from genPrimitiveNewWithArg) expects class
  	 in ReceiverResultReg and size in Arg0Reg.  Shuffle args to match, undoing on failure."
  	cogit
  		PushR: ReceiverResultReg;
  		MoveR: Arg0Reg R: ReceiverResultReg;
  		MoveR: Arg1Reg R: Arg0Reg.
  
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"get integer value of num fields in fillReg now"
  	cogit MoveR: Arg0Reg R: fillReg.
  	self genConvertSmallIntegerToIntegerInReg: fillReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"
  	cogit MoveCq: objectMemory wordSize / 4 R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	cogit MoveCq: objectMemory nilObject R: fillReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"store numSlots to headerReg"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"compute byte size; remember 0-sized objects still need 1 slot."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	jumpHasSlots jmpTarget:
  	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"check if allocation fits"
  	(cogit AddR: Arg1Reg R: byteSizeReg).
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.
  	"now fill"
  	cogit PopR: TempReg. "discard pushed receiver"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit genPrimReturn.
  
  	jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget:
  	(jumpNoSpace jmpTarget:  cogit Label)))).
  
  	"unshuffle arguments"
  	cogit
  		MoveR: Arg0Reg R: Arg1Reg;
  		MoveR: ReceiverResultReg R: Arg0Reg;
  		PopR: ReceiverResultReg.
  
  	jumpUnhashed jmpTarget:
  	(jumpImmediate jmpTarget:
  	(jumpTooSmall jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveNewWithArg (in category 'primitive generators') -----
  genPrimitiveNewWithArg
  	"Implement primitiveNewWithArg for convenient cases:
  	- the receiver has a hash
  	- the receiver is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	| headerReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  
  	NewspeakVM ifTrue:
  		[cogit methodNumArgs = 2 ifTrue:
  			[^self genPrimitiveMirrorNewWithArg]].
  	cogit methodNumArgs ~= 1 ifTrue:
  		[^UnimplementedPrimitive].
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  
  	"header will contain classIndex/class's hash & format & numSlots/fixed size"
  	headerReg := SendNumArgsReg.
  	"Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"
+ 	fillReg := Extra0Reg.
- 	fillReg := Scratch0Reg.
  	self assert: fillReg > 0.
  	"inst spec will hold class's instance specification and then byte size"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
  	jumpUnhashed := cogit JumpZero: 0.
  	"get index and fail if not a +ve integer"
  	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"get integer value of num fields in fillReg now"
  	cogit MoveR: Arg0Reg R: fillReg.
  	self genConvertSmallIntegerToIntegerInReg: fillReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 2) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"
  	cogit MoveCq: objectMemory wordSize / 4 R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	cogit MoveCq: objectMemory nilObject R: fillReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"store numSlots to headerReg"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"compute byte size; remember 0-sized objects still need 1 slot."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	jumpHasSlots jmpTarget:
  	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"check if allocation fits"
  	(cogit AddR: Arg1Reg R: byteSizeReg).
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.
  	"now fill"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit genPrimReturn.
  	
  	jumpNoSpace jmpTarget:
  	(jumpUnhashed jmpTarget:
  	(jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label)))))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>maybeGenerateSelectorIndexDereferenceRoutine (in category 'initialization') -----
  maybeGenerateSelectorIndexDereferenceRoutine
  	"Generate the routine that converts selector indices into selector objects.
  	 It is called from the send trampolines.
  	 If the selector index is negative, convert it into a positive index into the
  	 special selectors array and index that.  Otherwise, index the current method.
+ 	 The routine uses Extra0Reg & Extra1Reg, which are available, since they
- 	 The routine uses Scratch0Reg & Scratch1Reg, which are available, since they
  	 are not live at point of send."
  	| jumpNegative jumpNotBlock jumpFullBlock |
  	<var: 'jumpNegative' type: #'AbstractInstruction *'>
  	<var: 'jumpNotBlock' type: #'AbstractInstruction *'>
  	<var: 'jumpFullBlock' type: #'AbstractInstruction *'>
  	cogit zeroOpcodeIndex.
  	cogit CmpCq: 0 R: ClassReg.
  	jumpNegative := cogit JumpLess: 0.
  	cogit
+ 		MoveMw: FoxMethod r: FPReg R: Extra0Reg;
- 		MoveMw: FoxMethod r: FPReg R: Scratch0Reg;
  		AddCq: 2 R: ClassReg; "Change selector index to 1-relative, skipping the method header"
+ 		TstCq: MFMethodFlagIsBlockFlag R: Extra0Reg.
- 		TstCq: MFMethodFlagIsBlockFlag R: Scratch0Reg.
  	jumpNotBlock := cogit JumpZero: 0.
  	"If in a block, need to find the home method...  If using full blocks, need to test the cpicHasMNUCaseOrCMIsFullBlock bit"
+ 	cogit AndCq: methodZone alignment negated R: Extra0Reg.
- 	cogit AndCq: methodZone alignment negated R: Scratch0Reg.
  	SistaV1BytecodeSet ifTrue:
  		[self bitAndByteOffsetOfIsFullBlockBitInto:
  			[:bitmask :byteOffset|
  			jumpFullBlock := cogit
+ 				MoveMb: byteOffset r: Extra0Reg R: Extra1Reg;
+ 				TstCq: bitmask R: Extra1Reg;
- 				MoveMb: byteOffset r: Scratch0Reg R: Scratch1Reg;
- 				TstCq: bitmask R: Scratch1Reg;
  				JumpNonZero: 0]].
  	cogit 
+ 		MoveM16: 0 r: Extra0Reg R: Extra1Reg;
+ 		SubR: Extra1Reg R: Extra0Reg.
- 		MoveM16: 0 r: Scratch0Reg R: Scratch1Reg;
- 		SubR: Scratch1Reg R: Scratch0Reg.
  	jumpNotBlock jmpTarget: cogit Label.
  	SistaV1BytecodeSet ifTrue:
  		[jumpFullBlock jmpTarget: jumpNotBlock getJmpTarget].
  	cogit "Now fetch the method object and index with the literal index to retrieve the selector"
+ 		AndCq: methodZone alignment negated R: Extra0Reg;
+ 		MoveMw: (cogit offset: CogMethod of: #methodObject) r: Extra0Reg R: Extra1Reg;
+ 		MoveXwr: ClassReg R: Extra1Reg R: ClassReg;
- 		AndCq: methodZone alignment negated R: Scratch0Reg;
- 		MoveMw: (cogit offset: CogMethod of: #methodObject) r: Scratch0Reg R: Scratch1Reg;
- 		MoveXwr: ClassReg R: Scratch1Reg R: ClassReg;
  		RetN: 0.
  	jumpNegative jmpTarget: cogit Label.
  	cogit
  		NegateR: ClassReg;
  		LogicalShiftLeftCq: 1 R: ClassReg;
+ 		MoveAw: objectMemory specialObjectsArrayAddress R: Extra0Reg;
- 		MoveAw: objectMemory specialObjectsArrayAddress R: Scratch0Reg;
  		SubCq: 1 R: ClassReg;
+ 		MoveMw: SpecialSelectors + 1 * objectMemory wordSize r: Extra0Reg R: Extra1Reg; "Index, including header size"
+ 		MoveXwr: ClassReg R: Extra1Reg R: ClassReg;
- 		MoveMw: SpecialSelectors + 1 * objectMemory wordSize r: Scratch0Reg R: Scratch1Reg; "Index, including header size"
- 		MoveXwr: ClassReg R: Scratch1Reg R: ClassReg;
  		RetN: 0.
  	ceDereferenceSelectorIndex := cogit methodZoneBase.
  	cogit
  		outputInstructionsForGeneratedRuntimeAt: ceDereferenceSelectorIndex;
  		recordGeneratedRunTime: 'ceDereferenceSelectorIndex' address: ceDereferenceSelectorIndex;
  		recordRunTimeObjectReferences!

Item was changed:
  ----- Method: CogOutOfLineLiteralsX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	super initializeAbstractRegisters.
+ 	Extra6Reg := R8!
- 	Scratch6Reg := R8!

Item was added:
+ ----- Method: CogOutOfLineLiteralsX64Compiler>>availableRegisterOrNoneFor: (in category 'register allocation') -----
+ availableRegisterOrNoneFor: liveRegsMask
+ 	"Answer an unused abstract register in the liveRegMask.
+ 	 Subclasses with more registers can override to answer them.
+ 	 N.B. Do /not/ allocate TempReg."
+ 	<returnTypeC: #sqInt>
+ 	(cogit register: Extra6Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra6Reg].
+ 	^super availableRegisterOrNoneFor: liveRegsMask!

Item was added:
+ ----- Method: CogSimStackEntry class>>byteSizeForSimulator: (in category 'simulation only') -----
+ byteSizeForSimulator: aVMClass
+ 	"Answer an approximation of the byte size of an AbstractInstruction struct.
+ 	 This is for estimating the alloca in allocateOpcodes:bytecodes:ifFail:"
+ 	^self instSize * (aVMClass sizeof: #'void *')!

Item was changed:
  ----- Method: CogX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  	"[1] Figure 3.4 Register Usage in
  		System V Application Binary Interface
  		AMD64 Architecture Processor Supplement
  
  	N.B. RAX RCX & RDX are caller-save (scratch) registers.  Hence we use RCX for class and RDX for
  		receiver/result since these are written in all normal sends."
  
  	super initializeAbstractRegisters.
  
  	TempReg				:= RAX.
  	ClassReg				:= RCX.
  	ReceiverResultReg		:= RDX.
  	SendNumArgsReg		:= R9.
  	SPReg					:= RSP.
  	FPReg					:= RBP.
  	Arg0Reg				:= RDI. "So as to agree with C ABI arg 0"
  	Arg1Reg				:= RSI. "So as to agree with C ABI arg 1"
  	VarBaseReg			:= RBX. "Must be callee saved"
+ 	"R8 is either RISCTempReg or Extra6Reg depending on subclass."
+ 	Extra0Reg				:= R10.
+ 	Extra1Reg				:= R11.
+ 	Extra2Reg				:= R12.
+ 	Extra3Reg				:= R13.
+ 	Extra4Reg				:= R14.
+ 	Extra5Reg				:= R15.
- 	"R8 is either RISCTempReg or Scratch6Reg depending on subclass."
- 	Scratch0Reg			:= R10.
- 	Scratch1Reg			:= R11.
- 	Scratch2Reg			:= R12.
- 	Scratch3Reg			:= R13.
- 	Scratch4Reg			:= R14.
- 	Scratch5Reg			:= R15.
  
  	DPFPReg0				:= XMM0L.
  	DPFPReg1				:= XMM1L.
  	DPFPReg2				:= XMM2L.
  	DPFPReg3				:= XMM3L.
  	DPFPReg4				:= XMM4L.
  	DPFPReg5				:= XMM5L.
  	DPFPReg6				:= XMM6L.
  	DPFPReg7				:= XMM7L.
  	DPFPReg8				:= XMM8L.
  	DPFPReg9				:= XMM9L.
  	DPFPReg10				:= XMM10L.
  	DPFPReg11				:= XMM11L.
  	DPFPReg12				:= XMM12L.
  	DPFPReg13				:= XMM13L.
  	DPFPReg14				:= XMM14L.
  	DPFPReg15				:= XMM15L!

Item was added:
+ ----- Method: CogX64Compiler>>availableRegisterOrNoneFor: (in category 'register allocation') -----
+ availableRegisterOrNoneFor: liveRegsMask
+ 	"Answer an unused abstract register in the liveRegMask.
+ 	 Subclasses with more registers can override to answer them.
+ 	 N.B. Do /not/ allocate TempReg."
+ 	<returnTypeC: #sqInt>
+ 	(cogit register: Extra5Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra5Reg].
+ 	(cogit register: Extra4Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra4Reg].
+ 	(cogit register: Extra3Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra3Reg].
+ 	(cogit register: Extra2Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra2Reg].
+ 	(cogit register: Extra1Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra1Reg].
+ 	(cogit register: Extra0Reg isInMask: liveRegsMask) ifFalse:
+ 		[^Extra0Reg].
+ 	^super availableRegisterOrNoneFor: liveRegsMask!

Item was added:
+ ----- Method: Cogit>>sizeof: (in category 'translation support') -----
+ sizeof: aCType
+ 	<doNotGenerate>
+ 	| bfc |
+ 	aCType == #BytecodeFixup ifTrue:
+ 		[bfc := self class bytecodeFixupClass.
+ 		 ^bfc alignedByteSizeOf: bfc forClient: self].
+ 	^super sizeof: aCType!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails."
  	| cacheBaseReg jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self preenMethodLabel.
  	self compilePICAbort: numArgs.
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  	self MoveR: ClassReg R: SendNumArgsReg.
  
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  
  	cacheBaseReg := NoReg.
  	(backEnd isWithinMwOffsetRange: coInterpreter methodCacheAddress) ifFalse:
+ 		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Extra0Reg)].
- 		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Scratch0Reg)].
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 0 baseRegOrNone: cacheBaseReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	itsAHit := self MoveMw: (cacheBaseReg = NoReg
  								ifTrue: [coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << objectMemory shiftForWord)]
  								ifFalse: [MethodCacheMethod << objectMemory shiftForWord])
  					r: ClassReg
  					R: SendNumArgsReg.
  			.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpImmediate: ClassReg.
  	jumpBCMethod jmpTarget: picInterpretAbort.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 1 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 2 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	self numRegArgs > 0 ifTrue:
  		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg].
  	self genSmalltalkToCStackSwitch: true.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	self 
  		compileCallFor: #ceSendFromInLineCacheMiss:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: NoReg
  		regsToSave: self emptyRegisterMask
  	"Note that this call does not return."!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genLookupForPerformNumArgs: (in category 'primitive generators') -----
  genLookupForPerformNumArgs: numArgs
  	"Compile the code for a probe of the first-level method cache for a perform primtiive.
  	 The selector is assumed to be in Arg0Reg.  Defer to adjustArgumentsForPerform: to
  	 adjust the arguments before the jump to the method."
  	| jumpSelectorMiss jumpClassMiss jumpInterpret itsAHit cacheBaseReg |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #jumpInterpret type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  
  	"N.B.  Can't assume TempReg already contains the tag because a method can
  	 of course be invoked via the unchecked entry-point, e.g. as does perform:."
  	objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: SendNumArgsReg forEntry: false.
  
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  
  	cacheBaseReg := NoReg.
  	(backEnd isWithinMwOffsetRange: coInterpreter methodCacheAddress) ifFalse:
+ 		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Extra0Reg)].
- 		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Scratch0Reg)].
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 0 baseRegOrNone: cacheBaseReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	"Fetch the method, and check if it is cogged."
  	itsAHit := self MoveMw: (cacheBaseReg = NoReg
  								ifTrue: [coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << objectMemory shiftForWord)]
  								ifFalse: [MethodCacheMethod << objectMemory shiftForWord])
  					r: ClassReg
  					R: SendNumArgsReg.
  	"If the method is not compiled fall back on the interpreter primitive."
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpInterpret := objectRepresentation genJumpImmediate: ClassReg.
  	"Adjust arguments and jump to the method's unchecked entry-point."
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self adjustArgumentsForPerform: numArgs.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 1 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 1 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Caller will generate the call to fall back on the interpreter primitive."
  	jumpSelectorMiss jmpTarget:
  	(jumpInterpret jmpTarget: self Label).
  	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>isCallerSavedReg: (in category 'register management') -----
+ isCallerSavedReg: reg
+ 	<inline: true>
+ 	^self register: reg isInMask: callerSavedRegMask!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>returnRegForStoreCheck (in category 'trampolines') -----
  returnRegForStoreCheck
  	"We must ensure the ReceiverResultReg is live across the store check so that
  	 we can store into receiver inst vars in a frameless method since self exists
  	 only in ReceiverResultReg in a frameless method.  So if ReceiverResultReg is
  	 caller-saved we use the fact that ceStoreCheck: answers its argument to
  	 reload ReceiverResultReg cheaply.  Otherwise we don't care about the result
  	 and use the cResultRegister, effectively a no-op (see compileTrampoline...)"
+ 	<inline: true>
+ 	^(self isCallerSavedReg: ReceiverResultReg)
- 
- 	^(self register: ReceiverResultReg isInMask: callerSavedRegMask)
  		ifTrue: [ReceiverResultReg]
  		ifFalse: [backEnd cResultRegister]!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushMaybeContextSlotIndex: (in category 'bytecode generator support') -----
  genPushMaybeContextSlotIndex: slotIndex
  	<inline: true>
  	"This method expects ReceiverResultReg to hold the object read"
  	| jmpSingle jmpDone |
  	<var: #jmpSingle type: #'AbstractInstruction *'>
  	<var: #jmpDone type: #'AbstractInstruction *'>
  	self assert: needsFrame.
+ 	(self isCallerSavedReg: ReceiverResultReg) ifTrue:
- 	(self register: ReceiverResultReg isInMask: callerSavedRegMask) ifTrue:
  		["We have no way of reloading ReceiverResultReg since we need the inst var value as the result."
  		optStatus isReceiverResultRegLive: false].
  	"See CoInterpreter>>contextInstructionPointer:frame: for an explanation
  	 of the instruction pointer slot handling."
  	slotIndex = InstructionPointerIndex ifTrue:
  		[self MoveCq: slotIndex R: SendNumArgsReg.
  		 self CallRT: ceFetchContextInstVarTrampoline.
  		 ^self ssPushRegister: SendNumArgsReg].
  	objectRepresentation
  		genLoadSlot: SenderIndex
  		sourceReg: ReceiverResultReg
  		destReg: TempReg.
  	jmpSingle := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self MoveCq: slotIndex R: SendNumArgsReg.
  	self CallRT: ceFetchContextInstVarTrampoline.
  	jmpDone := self Jump: 0.
  	jmpSingle jmpTarget: self Label.
  	objectRepresentation
  		genLoadSlot: slotIndex
  		sourceReg: ReceiverResultReg
  		destReg: SendNumArgsReg.
  	jmpDone jmpTarget: self Label.
  	^self ssPushRegister: SendNumArgsReg!

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

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>simStackEntryClass (in category 'initialization') -----
+ simStackEntryClass
+ 	<doNotGenerate>
+ 	^CogSimStackEntry!



More information about the Vm-dev mailing list