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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 8 23:05:10 UTC 2016


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

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

Name: VMMaker.oscog-eem.1620
Author: eem
Time: 7 January 2016, 3:03:10.883236 pm
UUID: 2b2d0809-32ab-49a2-887e-a61d1efb2c17
Ancestors: VMMaker.oscog-cb.1619

Cogit:
Refactor primitive generation so that all primitives reside in CogObjectRepresentation and subclasses, except for genPrimitiveClosureValue and genPrimitivePerform.  This eliminates the outer/inner distinction and the need for a separate compileFallbackToInterpreterPrimitive:.  It aklso eliminates the difference between SimpleStackBasedCogit and StackToRegisterMappingCogit versions, having the object representation ask the cogits to load args into registers as required, and hence StackToRegisterMappingCogit>>#genLoadArgAtDepth:into: is now a no-op instead of an error.

Eliminate the enabled function from a CogPrimitiveDescriptor, adding the enablement calls to the relevant primitives, and discarding the unused primitiveIndex arguments.

Handle optional floating-point (i.e. the current MIPSEL) by adding <option: #DPFPReg0> to all floating point routines (except 64-bit Spur, which currently insists, but this could change) and modifying Slang to not output these methods (but the C generation hans not been tested yet; very soon...).

Status: The simulator works.  I will test generation of cogitMIPSEL.c very soon, but want to commit this now rather than continue to sit on it.

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

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.
+ 	"Scratch0Reg			:= ??.
+ 	Scratch1Reg			:= ??.
+ 	Scratch2Reg			:= ??.
+ 	Scratch3Reg			:= ??.
+ 	Scratch4Reg			:= ??.
+ 	Scratch5Reg			:= ??.
+ 	Scratch6Reg			:= ??.
+ 	Scratch7Reg			:= ??."
- 	Scratch0Reg			:= NoReg.
- 	Scratch1Reg			:= NoReg.
- 	Scratch2Reg			:= NoReg.
- 	Scratch3Reg			:= NoReg.
- 	Scratch4Reg			:= NoReg.
- 	Scratch5Reg			:= NoReg.
- 	Scratch6Reg			:= NoReg.
- 	Scratch7Reg			:= NoReg.
  
  	self flag: #todo.
+ 	"DPFPReg0				:= ??.
+ 	DPFPReg1				:= ??.
+ 	DPFPReg2				:= ??.
+ 	DPFPReg3				:= ??.
+ 	DPFPReg4				:= ??.
+ 	DPFPReg5				:= ??.
+ 	DPFPReg6				:= ??.
+ 	DPFPReg7				:= ??.
+ 	DPFPReg8				:= ??.
+ 	DPFPReg9				:= ??.
+ 	DPFPReg10				:= ??.
+ 	DPFPReg11				:= ??.
+ 	DPFPReg12				:= ??.
+ 	DPFPReg13				:= ??.
+ 	DPFPReg14				:= ??.
+ 	DPFPReg15				:= ??"!
- 	DPFPReg0				:= NoReg.
- 	DPFPReg1				:= NoReg.
- 	DPFPReg2				:= NoReg.
- 	DPFPReg3				:= NoReg.
- 	DPFPReg4				:= NoReg.
- 	DPFPReg5				:= NoReg.
- 	DPFPReg6				:= NoReg.
- 	DPFPReg7				:= NoReg.
- 	DPFPReg8				:= NoReg.
- 	DPFPReg9				:= NoReg.
- 	DPFPReg10				:= NoReg.
- 	DPFPReg11				:= NoReg.
- 	DPFPReg12				:= NoReg.
- 	DPFPReg13				:= NoReg.
- 	DPFPReg14				:= NoReg.
- 	DPFPReg15				:= NoReg.
- 					
- !

Item was added:
+ ----- Method: CogObjectRepresentation>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
+ genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
+ 	<option: #DPFPReg0>
+ 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
+ 	<var: #jumpFailClass type: #'AbstractInstruction *'>
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
+ 	<var: #doOp type: #'AbstractInstruction *'>
+ 	cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
+ 	jumpFailClass := cogit JumpNonZero: 0.
+ 	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
+ 	doOp := cogit Label.
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck := cogit perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
+ 	cogit gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
+ 	jumpFailAlloc := self
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpImmediate jmpTarget: cogit Label.
+ 	self maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
+ 	self smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
+ 	self genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	cogit ConvertR: ClassReg Rd: DPFPReg1.
+ 	cogit Jump: doOp.
+ 	jumpFailAlloc jmpTarget:  (jumpFailClass jmpTarget: cogit Label).
+ 	self smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genDoubleComparison:invert: (in category 'primitive generators') -----
+ genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
+ 	<option: #DPFPReg0>
+ 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
+ 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpCond type: #'AbstractInstruction *'>
+ 	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
+ 	jumpFail := cogit JumpNonZero: 0.
+ 	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
+ 	invertComparison "May need to invert for NaNs"
+ 		ifTrue: [compare := cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
+ 		ifFalse: [compare := cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
+ 	jumpCond := cogit perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
+ 	cogit genMoveFalseR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpCond jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 	jumpImmediate jmpTarget: cogit Label.
+ 	self maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
+ 	self smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit ConvertR: Arg0Reg Rd: DPFPReg1.
+ 	cogit Jump: compare.
+ 	jumpFail jmpTarget: cogit Label.
+ 	self smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genFastPrimFail (in category 'primitive generators') -----
+ genFastPrimFail
+ 	<doNotGenerate>
+ 	^cogit genFastPrimFail!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveAsCharacter:inReg: (in category 'primitive generators') -----
- genInnerPrimitiveAsCharacter: retNOffset inReg: reg
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveAt: (in category 'primitive generators') -----
- genInnerPrimitiveAt: retNoffset
- 	"Implement the guts of primitiveAt"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveAtPut: (in category 'primitive generators') -----
- genInnerPrimitiveAtPut: retNoffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveCharacterValue: (in category 'primitive generators') -----
- genInnerPrimitiveCharacterValue: retNOffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveMirrorNew: (in category 'primitive generators') -----
- genInnerPrimitiveMirrorNew: retNoffset
- 	<option: #NewspeakVM>
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveMirrorNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveMirrorNewWithArg: retNoffset
- 	<option: #NewspeakVM>
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveNew: (in category 'primitive generators') -----
- genInnerPrimitiveNew: retNoffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewMethod: (in category 'primitive generators') -----
- genInnerPrimitiveNewMethod: retNoffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveNewWithArg: retNoffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveObjectAt: (in category 'primitive generators') -----
- genInnerPrimitiveObjectAt: retNOffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>genInnerPrimitiveStringAtPut: (in category 'primitive generators') -----
- genInnerPrimitiveStringAtPut: retNoffset
- 	"subclasses override if they can"
- 	^cogit unimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveAdd (in category 'primitive generators') -----
+ genPrimitiveAdd
+ 	| jumpNotSI jumpOvfl |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpOvfl type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genRemoveSmallIntegerTagsInScratchReg: ClassReg.
+ 	cogit AddR: ReceiverResultReg R: ClassReg.
+ 	jumpOvfl := cogit JumpOverflow: 0.
+ 	cogit MoveR: ClassReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveAsCharacter (in category 'primitive generators') -----
+ genPrimitiveAsCharacter
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveAsFloat (in category 'primitive generators') -----
+ genPrimitiveAsFloat
+ 	<option: #DPFPReg0>
+ 	| jumpFailAlloc |
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit ConvertR: TempReg Rd: DPFPReg0.
+ 	jumpFailAlloc := self
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpFailAlloc jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveAt (in category 'primitive generators') -----
+ genPrimitiveAt
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveAtPut (in category 'primitive generators') -----
+ genPrimitiveAtPut
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveBitAnd (in category 'primitive generators') -----
+ genPrimitiveBitAnd
+ 	| jumpNotSI |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"Whether the SmallInteger tags are zero or non-zero, anding them together will preserve them."
+ 	cogit AndR: Arg0Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNotSI jmpTarget: cogit Label.
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveBitOr (in category 'primitive generators') -----
+ genPrimitiveBitOr
+ 	| jumpNotSI |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them."
+ 	cogit OrR: Arg0Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNotSI jmpTarget: cogit Label.
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveBitShift (in category 'primitive generators') -----
+ genPrimitiveBitShift
+ 	"rTemp := rArg0
+ 	rClass := tTemp
+ 	rTemp := rTemp & 1
+ 	jz nonInt
+ 	rClass >>= 1
+ 	cmp 0,rClass
+ 	jge neg
+ 	cmp 31,rClass // numSmallIntegerBits, jge for sign
+ 	jge tooBig
+ 	rTemp := rReceiver
+ 	rTemp <<= rClass
+ 	rTemp >>= rClass (arithmetic)
+ 	cmp rTemp,rReceiver
+ 	jnz ovfl
+ 	rReceiver := rReceiver - 1
+ 	rReceiver := rReceiver <<= rClass
+ 	rReceiver := rReceiver + 1
+ 	ret
+ neg:
+ 	rClass := 0 - rClass
+ 	cmp 31,rClass // numSmallIntegerBits
+ 	jge inRange
+ 	rClass := 31
+ inRange
+ 	rReceiver := rReceiver >>= rClass.
+ 	rReceiver := rReceiver | smallIntegerTags.
+ 	ret
+ ovfl
+ tooBig
+ nonInt:
+ 	fail"
+ 	| jumpNotSI jumpOvfl jumpNegative jumpTooBig jumpInRange |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpOvfl type: #'AbstractInstruction *'>
+ 	<var: #jumpNegative type: #'AbstractInstruction *'>
+ 	<var: #jumpTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpInRange type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
+ 		[cogit CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
+ 	jumpNegative := cogit JumpNegative: 0.
+ 	cogit CmpCq: self numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - numSmallIntegerBits"
+ 	jumpTooBig := cogit JumpGreaterOrEqual: 0.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	cogit LogicalShiftLeftR: ClassReg R: TempReg.
+ 	cogit ArithmeticShiftRightR: ClassReg R: TempReg.
+ 	cogit CmpR: TempReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - TempReg"
+ 	jumpOvfl := cogit JumpNonZero: 0.
+ 	self genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
+ 	cogit LogicalShiftLeftR: ClassReg R: ReceiverResultReg.
+ 	self genAddSmallIntegerTagsTo: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNegative jmpTarget: (cogit NegateR: ClassReg).
+ 	cogit CmpCq: self numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - numSmallIntegerBits"
+ 	jumpInRange := cogit JumpLessOrEqual: 0.
+ 	cogit MoveCq: self numSmallIntegerBits R: ClassReg.
+ 	jumpInRange jmpTarget: (cogit ArithmeticShiftRightR: ClassReg R: ReceiverResultReg).
+ 	self genClearAndSetSmallIntegerTagsIn: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNotSI jmpTarget: (jumpTooBig jmpTarget: (jumpOvfl jmpTarget: cogit Label)).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveBitXor (in category 'primitive generators') -----
+ genPrimitiveBitXor
+ 	| jumpNotSI |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"Clear one or the other tag so that xoring will preserve them."
+ 	self genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
+ 	cogit XorR: Arg0Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNotSI jmpTarget: cogit Label.
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveCharacterValue (in category 'primitive generators') -----
+ genPrimitiveCharacterValue
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveClass (in category 'primitive generators') -----
+ genPrimitiveClass
+ 	| reg |
+ 	reg := ReceiverResultReg.
+ 	cogit methodNumArgs > 0 ifTrue:
+ 		[cogit methodNumArgs > 1 ifTrue:
+ 			[^UnimplementedPrimitive].
+ 		 cogit genLoadArgAtDepth: 0 into: (reg := Arg0Reg)].
+ 	(self
+ 			genGetClassObjectOf: reg
+ 			into: ReceiverResultReg
+ 			scratchReg: TempReg
+ 			instRegIsReceiver: reg = ReceiverResultReg) = BadRegisterSet ifTrue:
+ 		[self
+ 			genGetClassObjectOf: reg
+ 			into: ClassReg
+ 			scratchReg: TempReg
+ 			instRegIsReceiver: reg = ReceiverResultReg.
+ 		 cogit MoveR: ClassReg R: ReceiverResultReg].
+ 	cogit genPrimReturn.
+ 	^UnfailingPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveClosureValue (in category 'primitive generators') -----
+ genPrimitiveClosureValue
+ 	"Defer to the cogit for this one.  This is for two reasons:
+ 	 a)	Cogit's version speeds up cull: et al by not calling the interpreter primitive if numArgs is wrong.
+ 		Our convention for compiling the interpreter primitive call doesn't agree with this usage.
+ 	b)	Cogit refuses to compile primitiveClosureValueNoContextSwitch until the blockNoContextSwitchOffset
+ 		is known, and that isn't information the CogObjectRepresentation is privvy to."
+ 	<doNotGenerate>
+ 	^cogit genPrimitiveClosureValue!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveDiv (in category 'primitive generators') -----
+ genPrimitiveDiv
+ 	| jumpNotSI jumpIsSI jumpZero jumpExact jumpSameSign convert |
+ 	<var: #convert type: #'AbstractInstruction *'>
+ 	<var: #jumpIsSI type: #'AbstractInstruction *'>
+ 	<var: #jumpZero type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpExact type: #'AbstractInstruction *'>
+ 	<var: #jumpSameSign type: #'AbstractInstruction *'>
+ 	cogit processorHasDivQuoRemAndMClassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"We must shift away the tags, not just subtract them, so that the
+ 	 overflow case doesn't actually overflow the machine instruction."
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ 		[cogit CmpCq: 0 R: ClassReg].
+ 	jumpZero := cogit JumpZero: 0.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
+ 	cogit DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
+ 	"If remainder is zero we must check for overflow."
+ 	cogit CmpCq: 0 R: ClassReg.
+ 	jumpExact := cogit JumpZero: 0.
+ 	"If arg and remainder signs are different we must round down."
+ 	cogit XorR: ClassReg R: Arg1Reg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ 		[cogit CmpCq: 0 R: Arg1Reg].
+ 	jumpSameSign := cogit JumpGreaterOrEqual: 0.
+ 	cogit SubCq: 1 R: TempReg.
+ 	jumpSameSign jmpTarget: (convert := cogit Label).
+ 	self genConvertIntegerToSmallIntegerInReg: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	"test for overflow; the only case is SmallInteger minVal // -1"
+ 	jumpExact jmpTarget: cogit Label.
+ 	jumpIsSI := self genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
+ 	jumpIsSI jmpTarget: convert.
+ 	jumpZero jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveDivide (in category 'primitive generators') -----
+ genPrimitiveDivide
+ 	| jumpNotSI jumpZero jumpInexact jumpOverflow |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpZero type: #'AbstractInstruction *'>
+ 	<var: #jumpInexact type: #'AbstractInstruction *'>
+ 	<var: #jumpOverflow type: #'AbstractInstruction *'>
+ 	cogit processorHasDivQuoRemAndMClassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"We must shift away the tags, not just subtract them, so that the
+ 	 overflow case doesn't actually overflow the machine instruction."
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
+ 	jumpZero := cogit JumpZero: 0.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
+ 	cogit DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
+ 	"If remainder is non-zero fail."
+ 	cogit CmpCq: 0 R: ClassReg.
+ 	jumpInexact := cogit JumpNonZero: 0.
+ 	"test for overflow; the only case is SmallInteger minVal / -1"
+ 	jumpOverflow := self genJumpNotSmallIntegerValue: TempReg scratch: Arg1Reg.
+ 	self genConvertIntegerToSmallIntegerInReg: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpOverflow jmpTarget: (jumpInexact jmpTarget: (jumpZero jmpTarget: (jumpNotSI jmpTarget: cogit Label))).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveEqual (in category 'primitive generators') -----
+ genPrimitiveEqual
+ 	^self 
+ 		genSmallIntegerComparison: JumpZero
+ 		orDoubleComparison: #JumpFPEqual:
+ 		invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatAdd (in category 'primitive generators') -----
+ genPrimitiveFloatAdd
+ 	<option: #DPFPReg0>
+ 	^self genDoubleArithmetic: AddRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatDivide (in category 'primitive generators') -----
+ genPrimitiveFloatDivide
+ 	<option: #DPFPReg0>
+ 	^self 
+ 		genDoubleArithmetic: DivRdRd
+ 		preOpCheck: #genDoubleFailIfZeroArgRcvr:arg:!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatEqual (in category 'primitive generators') -----
+ genPrimitiveFloatEqual
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatGreaterOrEqual (in category 'primitive generators') -----
+ genPrimitiveFloatGreaterOrEqual
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPGreaterOrEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatGreaterThan (in category 'primitive generators') -----
+ genPrimitiveFloatGreaterThan
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPGreater: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatLessOrEqual (in category 'primitive generators') -----
+ genPrimitiveFloatLessOrEqual
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPGreaterOrEqual: invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatLessThan (in category 'primitive generators') -----
+ genPrimitiveFloatLessThan
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPGreater: invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatMultiply (in category 'primitive generators') -----
+ genPrimitiveFloatMultiply
+ 	<option: #DPFPReg0>
+ 	^self genDoubleArithmetic: MulRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatNotEqual (in category 'primitive generators') -----
+ genPrimitiveFloatNotEqual
+ 	<option: #DPFPReg0>
+ 	^self genDoubleComparison: #JumpFPNotEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
+ genPrimitiveFloatSquareRoot
+ 	<option: #DPFPReg0>
+ 	| jumpFailAlloc |
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ 	cogit SqrtRd: DPFPReg0.
+ 	jumpFailAlloc := self
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpFailAlloc jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveFloatSubtract (in category 'primitive generators') -----
+ genPrimitiveFloatSubtract
+ 	<option: #DPFPReg0>
+ 	^self genDoubleArithmetic: SubRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveGreaterOrEqual (in category 'primitive generators') -----
+ genPrimitiveGreaterOrEqual
+ 	^self 
+ 		genSmallIntegerComparison: JumpGreaterOrEqual
+ 		orDoubleComparison: #JumpFPGreaterOrEqual:
+ 		invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveGreaterThan (in category 'primitive generators') -----
+ genPrimitiveGreaterThan
+ 	^self
+ 		genSmallIntegerComparison: JumpGreater
+ 		orDoubleComparison: #JumpFPGreater:
+ 		invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveIdentical (in category 'primitive generators') -----
+ genPrimitiveIdentical
+ 	^self genPrimitiveIdenticalOrNotIf: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveLessOrEqual (in category 'primitive generators') -----
+ genPrimitiveLessOrEqual
+ 	^self
+ 		genSmallIntegerComparison: JumpLessOrEqual
+ 		orDoubleComparison: #JumpFPGreaterOrEqual:
+ 		invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveLessThan (in category 'primitive generators') -----
+ genPrimitiveLessThan
+ 	^self
+ 		genSmallIntegerComparison: JumpLess
+ 		orDoubleComparison: #JumpFPGreater:
+ 		invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveMod (in category 'primitive generators') -----
+ genPrimitiveMod
+ 	| jumpNotSI jumpZero jumpExact jumpSameSign |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpZero type: #'AbstractInstruction *'>
+ 	<var: #jumpExact type: #'AbstractInstruction *'>
+ 	<var: #jumpSameSign type: #'AbstractInstruction *'>
+ 	cogit processorHasDivQuoRemAndMClassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genRemoveSmallIntegerTagsInScratchReg: ClassReg.
+ 	jumpZero := cogit JumpZero: 0.
+ 	cogit MoveR: ClassReg R: Arg1Reg.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	self genRemoveSmallIntegerTagsInScratchReg: TempReg.
+ 	cogit DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
+ 	"If remainder is zero we're done."
+ 	cogit CmpCq: 0 R: ClassReg.
+ 	jumpExact := cogit JumpZero: 0.
+ 	"If arg and remainder signs are different we must reflect around zero."
+ 	cogit XorR: ClassReg R: Arg1Reg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ 		[cogit CmpCq: 0 R: Arg1Reg].
+ 	jumpSameSign := cogit JumpGreaterOrEqual: 0.
+ 	cogit XorR: ClassReg R: Arg1Reg.
+ 	cogit AddR: Arg1Reg R: ClassReg.
+ 	jumpSameSign jmpTarget: (jumpExact jmpTarget: cogit Label).
+ 	self genSetSmallIntegerTagsIn: ClassReg.
+ 	cogit MoveR: ClassReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpZero jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveMultiply (in category 'primitive generators') -----
+ genPrimitiveMultiply
+ 	| jumpNotSI jumpOvfl |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpOvfl type: #'AbstractInstruction *'>
+ 	(cogit processorHasMultiplyAndMClassIsSmallInteger) ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	cogit MoveR: ReceiverResultReg R: Arg1Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
+ 	self genRemoveSmallIntegerTagsInScratchReg: Arg1Reg.
+ 	cogit MulR: Arg1Reg R: ClassReg.
+ 	jumpOvfl := cogit JumpOverflow: 0.
+ 	self genSetSmallIntegerTagsIn: ClassReg.
+ 	cogit MoveR: ClassReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveNew (in category 'primitive generators') -----
+ genPrimitiveNew
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveNewMethod (in category 'primitive generators') -----
+ genPrimitiveNewMethod
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveNewWithArg (in category 'primitive generators') -----
+ genPrimitiveNewWithArg
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveNotEqual (in category 'primitive generators') -----
+ genPrimitiveNotEqual
+ 	^self
+ 		genSmallIntegerComparison: JumpNonZero
+ 		orDoubleComparison: #JumpFPNotEqual:
+ 		invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveNotIdentical (in category 'primitive generators') -----
+ genPrimitiveNotIdentical
+ 	^self genPrimitiveIdenticalOrNotIf: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveObjectAt (in category 'primitive generators') -----
+ genPrimitiveObjectAt
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitivePerform (in category 'primitive generators') -----
+ genPrimitivePerform
+ 	"Defer to the cogit for this one.  All the code is method-cache related."
+ 	<doNotGenerate>
+ 	^cogit genPrimitivePerform!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveQuo (in category 'primitive generators') -----
+ genPrimitiveQuo
+ 	| convert jumpNotSI jumpZero jumpIsSI jumpExact |
+ 	<var: #convert type: #'AbstractInstruction *'>
+ 	<var: #jumpIsSI type: #'AbstractInstruction *'>
+ 	<var: #jumpZero type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpExact type: #'AbstractInstruction *'>
+ 	cogit processorHasDivQuoRemAndMClassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"We must shift away the tags, not just subtract them, so that the
+ 	 overflow case doesn't actually overflow the machine instruction."
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ 		[cogit CmpCq: 0 R: ClassReg].
+ 	jumpZero := cogit JumpZero: 0.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	self genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
+ 	cogit DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
+ 	"If remainder is zero we must check for overflow."
+ 	cogit CmpCq: 0 R: ClassReg.
+ 	jumpExact := cogit JumpZero: 0.
+ 	convert := cogit Label.
+ 	self genConvertIntegerToSmallIntegerInReg: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpExact jmpTarget: cogit Label.
+ 	jumpIsSI := self genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
+ 	jumpIsSI jmpTarget: convert.
+ 	jumpZero jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatAdd (in category 'primitive generators') -----
+ genPrimitiveSmallFloatAdd
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: AddRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatDivide (in category 'primitive generators') -----
+ genPrimitiveSmallFloatDivide
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: DivRdRd preOpCheck: #genDoubleFailIfZeroArgRcvr:arg:!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatGreaterOrEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatGreaterOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatGreaterThan (in category 'primitive generators') -----
+ genPrimitiveSmallFloatGreaterThan
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreater: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatLessOrEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatLessOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatLessThan (in category 'primitive generators') -----
+ genPrimitiveSmallFloatLessThan
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreater: invert: true!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatMultiply (in category 'primitive generators') -----
+ genPrimitiveSmallFloatMultiply
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: MulRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatNotEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatNotEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPNotEqual: invert: false!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
+ genPrimitiveSmallFloatSquareRoot
+ 	<option: #Spur64BitMemoryManager>
+ 	| jumpFailAlloc |
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	cogit SqrtRd: DPFPReg0.
+ 	jumpFailAlloc := self
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpFailAlloc jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSubtract (in category 'primitive generators') -----
+ genPrimitiveSmallFloatSubtract
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: SubRdRd preOpCheck: nil!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveStringAtPut (in category 'primitive generators') -----
+ genPrimitiveStringAtPut
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveSubtract (in category 'primitive generators') -----
+ genPrimitiveSubtract
+ 	| jumpNotSI jumpOvfl |
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpOvfl type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	cogit SubR: Arg0Reg R: TempReg.
+ 	jumpOvfl := cogit JumpOverflow: 0.
+ 	self genAddSmallIntegerTagsTo: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genQuickReturnConst (in category 'primitive generators') -----
+ genQuickReturnConst
+ 	<doNotGenerate>
+ 	^cogit genQuickReturnConst!

Item was added:
+ ----- Method: CogObjectRepresentation>>genQuickReturnInstVar (in category 'primitive generators') -----
+ genQuickReturnInstVar
+ 	<doNotGenerate>
+ 	^cogit genQuickReturnInstVar!

Item was added:
+ ----- Method: CogObjectRepresentation>>genQuickReturnSelf (in category 'primitive generators') -----
+ genQuickReturnSelf
+ 	<doNotGenerate>
+ 	^cogit genQuickReturnSelf!

Item was added:
+ ----- Method: CogObjectRepresentation>>genSmallIntegerComparison: (in category 'primitive generators') -----
+ genSmallIntegerComparison: jumpOpcode
+ 	| jumpFail jumpTrue |
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	<var: #jumpTrue type: #'AbstractInstruction *'>
+ 	cogit mclassIsSmallInteger ifFalse:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpFail := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	cogit CmpR: Arg0Reg R: ReceiverResultReg. "N.B. FLAGS := RRReg - Arg0Reg"
+ 	jumpTrue := cogit genConditionalBranch: jumpOpcode operand: 0.
+ 	cogit genMoveFalseR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpTrue jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 	jumpFail jmpTarget: cogit Label.
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genSmallIntegerComparison:orDoubleComparison:invert: (in category 'primitive generators') -----
+ genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator invert: invertComparison
+ 	"Stack looks like
+ 		return address"
+ 	| jumpNonInt jumpFail jumpCond r |
+ 	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction *(*jumpFPOpcodeGenerator)(void *)'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpCond type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	r := self genSmallIntegerComparison: jumpOpcode.
+ 	r < 0 ifTrue:
+ 		[^r].
+ 	self cppIf: #DPFPReg0 defined ifTrue:
+ 	"Fall through on non-SmallInteger argument.  Argument may be a Float : let us check or fail"
+ 	[self smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := self genJumpImmediate: Arg0Reg].
+ 	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
+ 	jumpFail := cogit JumpNonZero: 0.
+ 
+ 	"It was a Float, so convert the receiver to double and perform the operation"
+ 	self genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
+ 	cogit ConvertR: ReceiverResultReg Rd: DPFPReg0.
+ 	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
+ 	invertComparison "May need to invert for NaNs"
+ 		ifTrue: [cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
+ 		ifFalse: [cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
+ 	jumpCond := cogit perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
+ 	cogit genMoveFalseR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpCond jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 
+ 	self smallIntegerIsOnlyImmediateType
+ 		ifTrue: [jumpFail jmpTarget: cogit Label]
+ 		ifFalse: [jumpNonInt jmpTarget: (jumpFail jmpTarget: cogit Label)]].
+ 	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveAt: (in category 'primitive generators') -----
- genInnerPrimitiveAt: retNoffset
- 	"Implement the guts of primitiveAt"
- 	| formatReg convertToIntAndReturn
- 	  jumpNotIndexable jumpImmediate jumpBadIndex
- 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig jumpIsArray jumpHasFixedFields jumpIsContext
- 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
- 	<inline: true>
- 	"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: #jumpWordTooBig 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 *'>
- 
- 	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.
- 
- 	jumpIsBytes jmpTarget:
- 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
- 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
- 		cogit SubR: formatReg R: ClassReg;
- 		CmpR: Arg1Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	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 RetN: retNoffset.
- 
- 	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 R: Arg1Reg.
- 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
- 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
- 	jumpWordTooBig := self jumpNotSmallIntegerUnsignedValueInRegister: 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.
- 	cogit PushR: ClassReg.
- 	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
- 	cogit PopR: ClassReg.
- 	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 RetN: retNoffset.
- 
- 	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 RetN: retNoffset.
- 
- 	jumpFixedFieldsOutOfBounds jmpTarget:
- 	(jumpArrayOutOfBounds jmpTarget:
- 	(jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsOutOfBounds jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget:
- 	(jumpWordTooBig jmpTarget:
- 	(jumpNotIndexable jmpTarget:
- 	(jumpIsContext jmpTarget:
- 	(jumpBadIndex jmpTarget:
- 	(jumpImmediate jmpTarget: cogit Label))))))))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveAtPut: (in category 'primitive generators') -----
- genInnerPrimitiveAtPut: retNoffset
- 	"Implement the guts of primitiveAtPut"
- 	| formatReg jumpImmediate jumpBadIndex jumpImmutable
- 	  jumpNotIndexablePointers jumpNotIndexableBits
- 	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpHasFixedFields
- 	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
- 	  jumpWordsOutOfBounds jumpBytesOutOfBounds jumpBytesOutOfRange
- 	  jumpNonSmallIntegerValue jumpNegative jumpShortsUnsupported jumpNotPointers
- 	  |
- 	<inline: true>
- 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
- 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
- 	<var: #jumpNegative type: #'AbstractInstruction *'>
- 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpIsContext type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
- 	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
- 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexablePointers type: #'AbstractInstruction *'>
- 
- 	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 RetN: retNoffset.
- 
- 	jumpHasFixedFields jmpTarget: cogit Label.
- 	self genGetClassIndexOfNonImm: ReceiverResultReg into: formatReg.
- 	cogit CmpCq: ClassMethodContextCompactIndex R: formatReg.
- 	jumpIsContext := cogit JumpZero: 0.
- 	"get # fixed fields in formatReg"
- 	cogit PushR: ClassReg.
- 	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
- 	cogit PopR: ClassReg.
- 	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 RetN: retNoffset.
- 
- 	jumpNotPointers jmpTarget:
- 		(cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg).
- 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
- 	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
- 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
- 	jumpIsBytes := cogit JumpAboveOrEqual: 0.
- 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
- 	jumpShortsUnsupported := cogit JumpAboveOrEqual: 0.
- 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
- 	"For now ignore 64-bit indexability."
- 	jumpNotIndexableBits := cogit JumpBelow: 0.
- 
- 	cogit CmpR: Arg0Reg R: ClassReg.
- 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
- 		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
- 	jumpNegative := cogit JumpNegative: 0.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
- 	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 
- 	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.
- 	cogit SubR: formatReg R: ClassReg;
- 	CmpR: Arg0Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	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 RetN: retNoffset.
- 
- 	"there are no shorts as yet.  so this is dead code:
- 	jumpIsShorts jmpTarget:
- 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
- 	jumpShortsOutOfRange := cogit JumpAbove: 0.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
- 	cogit AndCq: 1 R: formatReg.
- 	cogit SubR: formatReg R: ClassReg;
- 	CmpR: Arg0Reg R: ClassReg.
- 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit AddR: Arg0Reg R: ReceiverResultReg.
- 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	jumpShortsDone := cogit Jump: 0."
- 
- 	jumpIsContext jmpTarget: 
- 	(jumpNegative jmpTarget:
- 	(jumpNotIndexableBits jmpTarget:
- 	(jumpBytesOutOfRange jmpTarget:
- 	(jumpIsCompiledMethod jmpTarget:
- 	(jumpArrayOutOfBounds jmpTarget:
- 	(jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsUnsupported jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget:
- 	(jumpNotIndexablePointers jmpTarget:
- 	(jumpNonSmallIntegerValue jmpTarget:
- 	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label))))))))))).
- 	
- 	self cppIf: IMMUTABILITY ifTrue: [ jumpImmutable jmpTarget: cogit Label ].
- 
- 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
- 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
- 
- 	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
- genInnerPrimitiveIdentityHash: retNoffset
- 	| jumpImm jumpSI jumpNotSet ret |
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpImm type: #'AbstractInstruction *'>
- 	<var: #jumpNotSet type: #'AbstractInstruction *'>
- 	jumpImm := self genJumpImmediate: ReceiverResultReg.
- 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	cogit CmpCq: ConstZero R: TempReg.
- 	jumpNotSet := cogit JumpZero: 0.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	ret := cogit RetN: retNoffset.
- 	jumpImm jmpTarget: cogit Label.
- 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
- 	jumpSI jmpTarget: ret.
- 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
- 	cogit Jump: ret.
- 	jumpNotSet jmpTarget: cogit Label.
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveMirrorNew: (in category 'primitive generators') -----
- genInnerPrimitiveMirrorNew: retNoffset
- 	"Implement 1-arg (instantiateFixedClass:) primitiveNew for convenient cases:
- 	- the class argument has a hash
- 	- the class argument is fixed size (excluding ephemerons to save instructions & miniscule time)
- 	- single word header/num slots < numSlotsMask
- 	- the result fits in eden (actually below scavengeThreshold)"
- 
- 	<option: #NewspeakVM>
- 	| halfHeaderReg fillReg instSpecReg byteSizeReg
- 	  jumpImmediate jumpUnhashed jumpNotFixedPointers jumpTooSmall jumpBadFormat
- 	  jumpNoSpace jumpTooBig jumpHasSlots jumpVariableOrEphemeron
- 	  fillLoop skip |
- 	<var: 'skip' type: #'AbstractInstruction *'>
- 	<var: 'fillLoop' type: #'AbstractInstruction *'>
- 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
- 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
- 	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
- 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
- 	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
- 	<var: 'jumpBadFormat' type: #'AbstractInstruction *'>
- 	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
- 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
- 
- 	"half header will contain 1st half of header (classIndex/class's hash & format),
- 	 then 2nd half of header (numSlots/fixed size) and finally fill value (nilObject)."
- 	halfHeaderReg := fillReg := SendNumArgsReg.
- 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
- 	instSpecReg := byteSizeReg := ClassReg.
- 
- 	"get freeStart as early as possible so as not to wait later..."
- 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
- 
- 	"validate class arg; sigh, this mirror crap hobbles unfairly; there is a better way with selector namespaces..."
- 	jumpImmediate := self genJumpImmediate: Arg0Reg.
- 
- 	"Is the class arg pointers with at least 3 fields?"
- 	self genGetFormatOf: Arg0Reg
- 		into: TempReg
- 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
- 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
- 	jumpNotFixedPointers := cogit JumpNonZero: 0.
- 	
- 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
- 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
- 	jumpTooSmall := cogit JumpLess: 0.
- 
- 	"get class's hash & fail if 0"
- 	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
- 	jumpUnhashed := cogit JumpZero: 0.
- 
- 	"get class's format inst var for both inst spec (format field) and num fixed fields"
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Arg0Reg destReg: instSpecReg.
- 	jumpBadFormat := self genJumpNotSmallInteger: instSpecReg scratchReg: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: instSpecReg.
- 	cogit MoveR: instSpecReg R: TempReg.
- 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
- 	cogit AndCq: objectMemory formatMask R: TempReg.
- 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
- 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
- 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
- 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
- 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
- 	jumpTooBig := cogit JumpAboveOrEqual: 0.
- 	"Add format to classIndex/format half header; other word contains numSlots"
- 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
- 	cogit AddR: TempReg R: halfHeaderReg.
- 	"write half header now; it frees halfHeaderReg"
- 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
- 	"save unrounded numSlots for header"
- 	cogit MoveR: instSpecReg R: halfHeaderReg.
- 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
- 	 rounded up to 8 bytes."
- 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
- 	jumpHasSlots := cogit JumpNonZero: 0.
- 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
- 	skip := cogit Jump: 0.
- 	"round up to allocationUnit"
- 	jumpHasSlots jmpTarget:
- 	(cogit MoveR: byteSizeReg R: TempReg).
- 	cogit AndCq: 1 R: TempReg.
- 	cogit AddR: TempReg R: byteSizeReg.
- 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
- 	skip jmpTarget:
- 	"shift halfHeaderReg to put numSlots in correct place"
- 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
- 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
- 	cogit AddR: Arg1Reg R: byteSizeReg.
- 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
- 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
- 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
- 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	"write other half of header (numSlots/identityHash)"
- 	cogit MoveR: halfHeaderReg Mw: 4 r: Arg1Reg.
- 	"now fill"
- 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
- 	cogit MoveCq: objectMemory nilObject R: fillReg.
- 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
- 	fillLoop := 
- 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
- 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
- 	cogit AddCq: 8 R: Arg1Reg.
- 	cogit CmpR: Arg1Reg R: byteSizeReg.
- 	cogit JumpAbove: fillLoop.
- 	cogit RetN: retNoffset.
- 
- 	jumpNotFixedPointers jmpTarget:
- 	(jumpBadFormat jmpTarget:
- 	(jumpTooSmall jmpTarget:
- 	(jumpImmediate jmpTarget:
- 	(jumpUnhashed jmpTarget:
- 	(jumpVariableOrEphemeron jmpTarget:
- 	(jumpTooBig jmpTarget:
- 	(jumpNoSpace jmpTarget: cogit Label))))))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveMirrorNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveMirrorNewWithArg: retNoffset
- 	"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>
- 	| halfHeaderReg fillReg instSpecReg byteSizeReg maxSlots
- 	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
- 	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
- 	  jumpUnhashed jumpTooSmall jumpImmediate jumpNotFixedPointers
- 	  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 *'>
- 	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
- 
- 	"half header will contain 1st half of header (classIndex/class's hash & format),
- 	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
- 	halfHeaderReg := fillReg := SendNumArgsReg.
- 	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
- 	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 genGetFormatOf: Arg0Reg
- 		into: TempReg
- 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
- 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
- 	jumpNotFixedPointers := cogit JumpNonZero: 0.
- 	
- 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
- 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
- 	jumpTooSmall := cogit JumpLess: 0.
- 
- 	"get class's hash & fail if 0"
- 	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
- 	jumpUnhashed := cogit JumpZero: 0.
- 
- 	"The basicNew: code below (copied from genInnerPrimitiveNewWithArg:) 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 freeStart as early as possible so as not to wait later..."
- 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
- 	"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 half header now"
- 	cogit MoveR: instSpecReg R: TempReg.
- 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
- 	cogit AddR: TempReg R: halfHeaderReg.
- 	"get integer value of num fields in TempReg now"
- 	cogit MoveR: Arg0Reg R: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	"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: TempReg R: instSpecReg.
- 	"push fill value"
- 	cogit PushCq: 0.
- 	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: TempReg R: instSpecReg.
- 	"compute odd bits and add into halfHeaderReg; 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: halfHeaderReg.
- 	"round up num elements to numSlots in instSpecReg"
- 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
- 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
- 	"push fill value"
- 	cogit PushCq: 0.
- 	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: TempReg R: instSpecReg.
- 	"push fill value"
- 	cogit PushCw: objectMemory nilObject.
- 	"fall through to allocate"
- 
- 	jumpBytePrepDone jmpTarget:
- 	(jumpLongPrepDone jmpTarget: cogit Label).
- 
- 	"write half header now; it frees halfHeaderReg"
- 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
- 	"save numSlots to halfHeaderReg"
- 	cogit MoveR: instSpecReg R: halfHeaderReg.
- 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
- 	 rounded up to 8 bytes."
- 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
- 	jumpHasSlots := cogit JumpNonZero: 0.
- 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
- 	skip := cogit Jump: 0.
- 	"round up to allocationUnit"
- 	jumpHasSlots jmpTarget:
- 	(cogit MoveR: byteSizeReg R: TempReg).
- 	cogit AndCq: 1 R: TempReg.
- 	cogit AddR: TempReg R: byteSizeReg.
- 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
- 	skip jmpTarget:
- 	"shift halfHeaderReg to put numSlots in correct place"
- 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
- 	"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: halfHeaderReg Mw: 4 r: ReceiverResultReg.
- 	"now fill"
- 	cogit PopR: fillReg.
- 	cogit PopR: TempReg. "discard pushed receiver"
- 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
- 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
- 	fillLoop := 
- 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
- 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
- 	cogit AddCq: 8 R: Arg1Reg.
- 	cogit CmpR: Arg1Reg R: byteSizeReg.
- 	cogit JumpAbove: fillLoop.
- 	cogit RetN: retNoffset.
- 
- 	"pop discarded fill value & fall through to failure"
- 	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
- 
- 	jumpFailCuzFixed jmpTarget:
- 	(jumpArrayTooBig jmpTarget:
- 	(jumpByteTooBig jmpTarget:
- 	(jumpLongTooBig jmpTarget: cogit Label))).
- 
- 	"unshuffle arguments"
- 	cogit
- 		MoveR: Arg0Reg R: Arg1Reg;
- 		MoveR: ReceiverResultReg R: Arg0Reg;
- 		PopR: ReceiverResultReg.
- 
- 	jumpUnhashed jmpTarget:
- 	(jumpImmediate jmpTarget:
- 	(jumpNotFixedPointers jmpTarget:
- 	(jumpTooSmall jmpTarget:
- 	(jumpNElementsNonInt jmpTarget: cogit Label)))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveNew: (in category 'primitive generators') -----
- genInnerPrimitiveNew: retNoffset
- 	"Implement primitiveNew for convenient cases:
- 	- the receiver has a hash
- 	- the receiver is fixed size (excluding ephemerons to save instructions & miniscule time)
- 	- single word header/num slots < numSlotsMask
- 	- the result fits in eden (actually below scavengeThreshold)"
- 
- 	| halfHeaderReg fillReg instSpecReg byteSizeReg
- 	  jumpUnhashed jumpVariableOrEphemeron jumpNoSpace jumpTooBig jumpHasSlots
- 	  fillLoop skip |
- 	<var: 'skip' type: #'AbstractInstruction *'>
- 	<var: 'fillLoop' type: #'AbstractInstruction *'>
- 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
- 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
- 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
- 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
- 
- 	"half header will contain 1st half of header (classIndex/class's hash & format),
- 	 then 2nd half of header (numSlots/fixed size) and finally fill value (nilObject)."
- 	halfHeaderReg := fillReg := SendNumArgsReg.
- 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
- 	instSpecReg := byteSizeReg := ClassReg.
- 
- 	"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: halfHeaderReg.
- 	jumpUnhashed := cogit JumpZero: 0.
- 	"get class's format inst var for both inst spec (format field) and num fixed fields"
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit MoveR: TempReg R: instSpecReg.
- 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
- 	cogit AndCq: objectMemory formatMask R: TempReg.
- 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
- 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
- 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
- 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
- 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
- 	jumpTooBig := cogit JumpAboveOrEqual: 0.
- 	"Add format to classIndex/format half header; other word contains numSlots"
- 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
- 	cogit AddR: TempReg R: halfHeaderReg.
- 	"write half header now; it frees halfHeaderReg"
- 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
- 	"save unrounded numSlots for header"
- 	cogit MoveR: instSpecReg R: halfHeaderReg.
- 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
- 	 rounded up to 8 bytes."
- 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
- 	jumpHasSlots := cogit JumpNonZero: 0.
- 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
- 	skip := cogit Jump: 0.
- 	"round up to allocationUnit"
- 	jumpHasSlots jmpTarget:
- 	(cogit MoveR: byteSizeReg R: TempReg).
- 	cogit AndCq: 1 R: TempReg.
- 	cogit AddR: TempReg R: byteSizeReg.
- 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
- 	skip jmpTarget:
- 	"shift halfHeaderReg to put numSlots in correct place"
- 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
- 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
- 	cogit AddR: Arg1Reg R: byteSizeReg.
- 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
- 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
- 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
- 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	"write other half of header (numSlots/identityHash)"
- 	cogit MoveR: halfHeaderReg Mw: 4 r: Arg1Reg.
- 	"now fill"
- 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
- 	cogit MoveCq: objectMemory nilObject R: fillReg.
- 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
- 	fillLoop := 
- 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
- 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
- 	cogit AddCq: 8 R: Arg1Reg.
- 	cogit CmpR: Arg1Reg R: byteSizeReg.
- 	cogit JumpAbove: fillLoop.
- 	cogit RetN: retNoffset.
- 
- 	jumpUnhashed jmpTarget:
- 	(jumpVariableOrEphemeron jmpTarget:
- 	(jumpTooBig jmpTarget:
- 	(jumpNoSpace jmpTarget: cogit Label))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveNewWithArg: retNoffset
- 	"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"
- 
- 	| halfHeaderReg 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 *'>
- 
- 	"half header will contain 1st half of header (classIndex/class's hash & format),
- 	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
- 	halfHeaderReg := fillReg := SendNumArgsReg.
- 	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
- 	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: halfHeaderReg.
- 	jumpUnhashed := cogit JumpZero: 0.
- 	"get index and fail if not a +ve integer"
- 	jumpNElementsNonInt := self genJumpNotSmallInteger: 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 half header now"
- 	cogit MoveR: instSpecReg R: TempReg.
- 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
- 	cogit AddR: TempReg R: halfHeaderReg.
- 	"get integer value of num fields in TempReg now"
- 	cogit MoveR: Arg0Reg R: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	"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: TempReg R: instSpecReg.
- 	"push fill value"
- 	cogit PushCq: 0.
- 	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: TempReg R: instSpecReg.
- 	"compute odd bits and add into halfHeaderReg; 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: halfHeaderReg.
- 	"round up num elements to numSlots in instSpecReg"
- 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
- 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
- 	"push fill value"
- 	cogit PushCq: 0.
- 	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: TempReg R: instSpecReg.
- 	"push fill value"
- 	cogit PushCw: objectMemory nilObject.
- 	"fall through to allocate"
- 
- 	jumpBytePrepDone jmpTarget:
- 	(jumpLongPrepDone jmpTarget: cogit Label).
- 
- 	"write half header now; it frees halfHeaderReg"
- 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
- 	"save numSlots to halfHeaderReg"
- 	cogit MoveR: instSpecReg R: halfHeaderReg.
- 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
- 	 rounded up to 8 bytes."
- 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
- 	jumpHasSlots := cogit JumpNonZero: 0.
- 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
- 	skip := cogit Jump: 0.
- 	"round up to allocationUnit"
- 	jumpHasSlots jmpTarget:
- 	(cogit MoveR: byteSizeReg R: TempReg).
- 	cogit AndCq: 1 R: TempReg.
- 	cogit AddR: TempReg R: byteSizeReg.
- 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
- 	skip jmpTarget:
- 	"shift halfHeaderReg to put numSlots in correct place"
- 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
- 	"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: halfHeaderReg Mw: 4 r: ReceiverResultReg.
- 	"now fill"
- 	cogit PopR: fillReg.
- 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
- 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
- 	fillLoop := 
- 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
- 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
- 	cogit AddCq: 8 R: Arg1Reg.
- 	cogit CmpR: Arg1Reg R: byteSizeReg.
- 	cogit JumpAbove: fillLoop.
- 	cogit RetN: retNoffset.
- 
- 	"pop discarded fill value & fall through to failure"
- 	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
- 
- 	jumpUnhashed jmpTarget:
- 	(jumpFailCuzFixed jmpTarget:
- 	(jumpArrayTooBig jmpTarget:
- 	(jumpByteTooBig jmpTarget:
- 	(jumpLongTooBig jmpTarget:
- 	(jumpNElementsNonInt jmpTarget: cogit Label))))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveStringAtPut: (in category 'primitive generators') -----
- genInnerPrimitiveStringAtPut: retNoffset
- 	"Implement the guts of primitiveStringAtPut"
- 	| formatReg jumpBadIndex jumpBadArg jumpWordsDone jumpBytesOutOfRange
- 	  jumpIsBytes jumpNotString jumpIsCompiledMethod jumpImmutable
- 	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsUnsupported |
- 	<inline: true>
- 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
- 	<var: #jumpBadArg type: #'AbstractInstruction *'>
- 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
- 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpWordsDone type: #'AbstractInstruction *'>
- 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
- 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
- 
- 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	jumpBadArg := self genJumpNotCharacterInScratchReg: 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; words and/or bytes.
- 		  0 to 8 = pointer objects, forwarders, reserved.
- 		  9 (?) 64-bit indexable
- 		10 - 11 32-bit indexable
- 		12 - 15 16-bit indexable (but unused)
- 		16 - 23 byte indexable
- 		24 - 31 compiled method"
- 	cogit CmpCq: objectMemory firstLongFormat R: formatReg.
- 	jumpNotString := cogit JumpBelowOrEqual: 0.
- 					cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
- 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
- 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
- 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
- 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
- 	jumpShortsUnsupported := cogit JumpGreaterOrEqual: 0.
- 
- 	cogit CmpR: Arg0Reg R: ClassReg.
- 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
- 	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	jumpWordsDone := cogit Jump: 0.
- 
- 	"there are no shorts as yet.  so this is dead code:
- 	jumpIsShorts jmpTarget:
- 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
- 	jumpShortsOutOfRange := cogit JumpAbove: 0.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
- 	cogit AndCq: 1 R: formatReg.
- 	cogit SubR: formatReg R: ClassReg;
- 	CmpR: Arg0Reg R: ClassReg.
- 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit AddR: Arg0Reg R: ReceiverResultReg.
- 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	jumpShortsDone := cogit Jump: 0."
- 
- 	jumpIsBytes jmpTarget:
- 		(cogit CmpCq: (objectMemory characterObjectOf: 255) R: Arg1Reg).
- 	jumpBytesOutOfRange := cogit JumpAbove: 0.
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
- 	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
- 	cogit SubR: formatReg R: ClassReg;
- 	CmpR: Arg0Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit MoveR: Arg1Reg R: TempReg.
- 	self genConvertCharacterToCodeInReg: TempReg.
- 	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
- 	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 
- 	jumpWordsDone jmpTarget:
- 		(cogit RetN: retNoffset).
- 
- 	jumpBadArg jmpTarget:
- 	(jumpNotString jmpTarget:
- 	(jumpBytesOutOfRange jmpTarget:
- 	(jumpIsCompiledMethod jmpTarget:
- 	(jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsUnsupported jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget: cogit Label)))))).
- 
- 	self cppIf: IMMUTABILITY ifTrue: [ jumpImmutable jmpTarget: cogit Label ].
- 
- 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
- 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
- 
- 	jumpBadIndex jmpTarget: cogit Label.
- 
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveAt (in category 'primitive generators') -----
+ genPrimitiveAt
+ 	"Implement the guts of primitiveAt"
+ 	| formatReg convertToIntAndReturn
+ 	  jumpNotIndexable jumpImmediate jumpBadIndex
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig jumpIsArray jumpHasFixedFields jumpIsContext
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
+ 	<inline: true>
+ 	"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: #jumpWordTooBig 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.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	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 R: Arg1Reg.
+ 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	jumpWordTooBig := self jumpNotSmallIntegerUnsignedValueInRegister: 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.
+ 	cogit PushR: ClassReg.
+ 	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
+ 	cogit PopR: ClassReg.
+ 	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.
+ 
+ 	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.
+ 
+ 	jumpFixedFieldsOutOfBounds jmpTarget:
+ 	(jumpArrayOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpWordTooBig jmpTarget:
+ 	(jumpNotIndexable jmpTarget:
+ 	(jumpIsContext jmpTarget:
+ 	(jumpBadIndex jmpTarget:
+ 	(jumpImmediate jmpTarget: cogit Label))))))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveAtPut (in category 'primitive generators') -----
+ genPrimitiveAtPut
+ 	"Implement the guts of primitiveAtPut"
+ 	| formatReg jumpImmediate jumpBadIndex jumpImmutable
+ 	  jumpNotIndexablePointers jumpNotIndexableBits
+ 	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpHasFixedFields
+ 	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
+ 	  jumpWordsOutOfBounds jumpBytesOutOfBounds jumpBytesOutOfRange
+ 	  jumpNonSmallIntegerValue jumpNegative jumpShortsUnsupported jumpNotPointers
+ 	  |
+ 	<inline: true>
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpNegative type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpIsContext type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
+ 	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds 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"
+ 	cogit PushR: ClassReg.
+ 	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
+ 	cogit PopR: ClassReg.
+ 	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 CmpCq: objectMemory firstCompiledMethodFormat R: formatReg).
+ 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
+ 	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
+ 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpShortsUnsupported := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	"For now ignore 64-bit indexability."
+ 	jumpNotIndexableBits := cogit JumpBelow: 0.
+ 
+ 	cogit CmpR: Arg0Reg R: ClassReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
+ 		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
+ 	jumpNegative := cogit JumpNegative: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: TempReg Xwr: 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.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	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.
+ 
+ 	"there are no shorts as yet.  so this is dead code:
+ 	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
+ 	jumpShortsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
+ 	cogit AndCq: 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpShortsDone := cogit Jump: 0."
+ 
+ 	jumpIsContext jmpTarget: 
+ 	(jumpNegative jmpTarget:
+ 	(jumpNotIndexableBits jmpTarget:
+ 	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpIsCompiledMethod jmpTarget:
+ 	(jumpArrayOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsUnsupported jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpNotIndexablePointers jmpTarget:
+ 	(jumpNonSmallIntegerValue jmpTarget:
+ 	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label))))))))))).
+ 	
+ 	self cppIf: IMMUTABILITY ifTrue: [ jumpImmutable jmpTarget: cogit Label ].
+ 
+ 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
+ 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
+ 
+ 	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveIdentityHash (in category 'primitive generators') -----
+ genPrimitiveIdentityHash
+ 	| jumpImm jumpSI jumpNotSet ret |
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSet type: #'AbstractInstruction *'>
+ 	jumpImm := self genJumpImmediate: ReceiverResultReg.
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit CmpCq: ConstZero R: TempReg.
+ 	jumpNotSet := cogit JumpZero: 0.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	ret := cogit genPrimReturn.
+ 	jumpImm jmpTarget: cogit Label.
+ 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
+ 	jumpSI jmpTarget: ret.
+ 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit Jump: ret.
+ 	jumpNotSet jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveMirrorNew (in category 'primitive generators') -----
+ genPrimitiveMirrorNew
+ 	"Implement 1-arg (instantiateFixedClass:) primitiveNew for convenient cases:
+ 	- the class argument has a hash
+ 	- the class argument is fixed size (excluding ephemerons to save instructions & miniscule time)
+ 	- single word header/num slots < numSlotsMask
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	<option: #NewspeakVM>
+ 	| halfHeaderReg fillReg instSpecReg byteSizeReg
+ 	  jumpImmediate jumpUnhashed jumpNotFixedPointers jumpTooSmall jumpBadFormat
+ 	  jumpNoSpace jumpTooBig jumpHasSlots jumpVariableOrEphemeron
+ 	  fillLoop skip |
+ 	<var: 'skip' type: #'AbstractInstruction *'>
+ 	<var: 'fillLoop' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
+ 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
+ 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
+ 	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
+ 	<var: 'jumpBadFormat' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
+ 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
+ 
+ 	self assert: cogit methodNumArgs = 1.
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 
+ 	"half header will contain 1st half of header (classIndex/class's hash & format),
+ 	 then 2nd half of header (numSlots/fixed size) and finally fill value (nilObject)."
+ 	halfHeaderReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
+ 	instSpecReg := byteSizeReg := ClassReg.
+ 
+ 	"get freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
+ 
+ 	"validate class arg; sigh, this mirror crap hobbles unfairly; there is a better way with selector namespaces..."
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 
+ 	"Is the class arg pointers with at least 3 fields?"
+ 	self genGetFormatOf: Arg0Reg
+ 		into: TempReg
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpNotFixedPointers := cogit JumpNonZero: 0.
+ 	
+ 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
+ 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
+ 	jumpTooSmall := cogit JumpLess: 0.
+ 
+ 	"get class's hash & fail if 0"
+ 	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 
+ 	"get class's format inst var for both inst spec (format field) and num fixed fields"
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Arg0Reg destReg: instSpecReg.
+ 	jumpBadFormat := self genJumpNotSmallInteger: instSpecReg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: instSpecReg.
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
+ 	cogit AndCq: objectMemory formatMask R: TempReg.
+ 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
+ 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
+ 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
+ 	jumpTooBig := cogit JumpAboveOrEqual: 0.
+ 	"Add format to classIndex/format half header; other word contains numSlots"
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: halfHeaderReg.
+ 	"write half header now; it frees halfHeaderReg"
+ 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
+ 	"save unrounded numSlots for header"
+ 	cogit MoveR: instSpecReg R: halfHeaderReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
+ 	 rounded up to 8 bytes."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	"round up to allocationUnit"
+ 	jumpHasSlots jmpTarget:
+ 	(cogit MoveR: byteSizeReg R: TempReg).
+ 	cogit AndCq: 1 R: TempReg.
+ 	cogit AddR: TempReg R: byteSizeReg.
+ 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"shift halfHeaderReg to put numSlots in correct place"
+ 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 	cogit AddR: Arg1Reg R: byteSizeReg.
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	"write other half of header (numSlots/identityHash)"
+ 	cogit MoveR: halfHeaderReg Mw: 4 r: Arg1Reg.
+ 	"now fill"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	cogit MoveCq: objectMemory nilObject R: fillReg.
+ 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	jumpNotFixedPointers jmpTarget:
+ 	(jumpBadFormat jmpTarget:
+ 	(jumpTooSmall jmpTarget:
+ 	(jumpImmediate jmpTarget:
+ 	(jumpUnhashed jmpTarget:
+ 	(jumpVariableOrEphemeron jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpNoSpace jmpTarget: cogit Label))))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>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>
+ 	| halfHeaderReg fillReg instSpecReg byteSizeReg maxSlots
+ 	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
+ 	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
+ 	  jumpUnhashed jumpTooSmall jumpImmediate jumpNotFixedPointers
+ 	  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 *'>
+ 	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
+ 
+ 	self assert: cogit methodNumArgs = 2.
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg. "class arg"
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg. "num indexable slots arg"
+ 
+ 	"half header will contain 1st half of header (classIndex/class's hash & format),
+ 	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
+ 	halfHeaderReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
+ 	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 genGetFormatOf: Arg0Reg
+ 		into: TempReg
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpNotFixedPointers := cogit JumpNonZero: 0.
+ 	
+ 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
+ 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
+ 	jumpTooSmall := cogit JumpLess: 0.
+ 
+ 	"get class's hash & fail if 0"
+ 	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 
+ 	"The basicNew: code below (copied from genInnerPrimitiveNewWithArg:) 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 freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
+ 	"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 half header now"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: halfHeaderReg.
+ 	"get integer value of num fields in TempReg now"
+ 	cogit MoveR: Arg0Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	"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: TempReg R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCq: 0.
+ 	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: TempReg R: instSpecReg.
+ 	"compute odd bits and add into halfHeaderReg; 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: halfHeaderReg.
+ 	"round up num elements to numSlots in instSpecReg"
+ 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCq: 0.
+ 	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: TempReg R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCw: objectMemory nilObject.
+ 	"fall through to allocate"
+ 
+ 	jumpBytePrepDone jmpTarget:
+ 	(jumpLongPrepDone jmpTarget: cogit Label).
+ 
+ 	"write half header now; it frees halfHeaderReg"
+ 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
+ 	"save numSlots to halfHeaderReg"
+ 	cogit MoveR: instSpecReg R: halfHeaderReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
+ 	 rounded up to 8 bytes."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	"round up to allocationUnit"
+ 	jumpHasSlots jmpTarget:
+ 	(cogit MoveR: byteSizeReg R: TempReg).
+ 	cogit AndCq: 1 R: TempReg.
+ 	cogit AddR: TempReg R: byteSizeReg.
+ 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"shift halfHeaderReg to put numSlots in correct place"
+ 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
+ 	"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: halfHeaderReg Mw: 4 r: ReceiverResultReg.
+ 	"now fill"
+ 	cogit PopR: fillReg.
+ 	cogit PopR: TempReg. "discard pushed receiver"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	"pop discarded fill value & fall through to failure"
+ 	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
+ 
+ 	jumpFailCuzFixed jmpTarget:
+ 	(jumpArrayTooBig jmpTarget:
+ 	(jumpByteTooBig jmpTarget:
+ 	(jumpLongTooBig jmpTarget: cogit Label))).
+ 
+ 	"unshuffle arguments"
+ 	cogit
+ 		MoveR: Arg0Reg R: Arg1Reg;
+ 		MoveR: ReceiverResultReg R: Arg0Reg;
+ 		PopR: ReceiverResultReg.
+ 
+ 	jumpUnhashed jmpTarget:
+ 	(jumpImmediate jmpTarget:
+ 	(jumpNotFixedPointers jmpTarget:
+ 	(jumpTooSmall jmpTarget:
+ 	(jumpNElementsNonInt jmpTarget: cogit Label)))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveNew (in category 'primitive generators') -----
+ genPrimitiveNew
+ 	"Implement primitiveNew for convenient cases:
+ 	- the receiver has a hash
+ 	- the receiver is fixed size (excluding ephemerons to save instructions & miniscule time)
+ 	- single word header/num slots < numSlotsMask
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	| halfHeaderReg fillReg instSpecReg byteSizeReg
+ 	  jumpUnhashed jumpVariableOrEphemeron jumpNoSpace jumpTooBig jumpHasSlots
+ 	  fillLoop skip |
+ 	<var: 'skip' type: #'AbstractInstruction *'>
+ 	<var: 'fillLoop' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
+ 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
+ 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
+ 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
+ 
+ 	NewspeakVM ifTrue:
+ 		[cogit methodNumArgs = 1 ifTrue:
+ 			[^self genPrimitiveMirrorNew]].
+ 	cogit methodNumArgs ~= 0 ifTrue:
+ 		[^UnimplementedPrimitive].
+ 
+ 	"half header will contain 1st half of header (classIndex/class's hash & format),
+ 	 then 2nd half of header (numSlots/fixed size) and finally fill value (nilObject)."
+ 	halfHeaderReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
+ 	instSpecReg := byteSizeReg := ClassReg.
+ 
+ 	"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: halfHeaderReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 	"get class's format inst var for both inst spec (format field) and num fixed fields"
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit MoveR: TempReg R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
+ 	cogit AndCq: objectMemory formatMask R: TempReg.
+ 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
+ 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
+ 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
+ 	jumpTooBig := cogit JumpAboveOrEqual: 0.
+ 	"Add format to classIndex/format half header; other word contains numSlots"
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: halfHeaderReg.
+ 	"write half header now; it frees halfHeaderReg"
+ 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
+ 	"save unrounded numSlots for header"
+ 	cogit MoveR: instSpecReg R: halfHeaderReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
+ 	 rounded up to 8 bytes."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	"round up to allocationUnit"
+ 	jumpHasSlots jmpTarget:
+ 	(cogit MoveR: byteSizeReg R: TempReg).
+ 	cogit AndCq: 1 R: TempReg.
+ 	cogit AddR: TempReg R: byteSizeReg.
+ 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"shift halfHeaderReg to put numSlots in correct place"
+ 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 	cogit AddR: Arg1Reg R: byteSizeReg.
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	"write other half of header (numSlots/identityHash)"
+ 	cogit MoveR: halfHeaderReg Mw: 4 r: Arg1Reg.
+ 	"now fill"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	cogit MoveCq: objectMemory nilObject R: fillReg.
+ 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	jumpUnhashed jmpTarget:
+ 	(jumpVariableOrEphemeron jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpNoSpace jmpTarget: cogit Label))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>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"
+ 
+ 	| halfHeaderReg 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.
+ 
+ 	"half header will contain 1st half of header (classIndex/class's hash & format),
+ 	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
+ 	halfHeaderReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
+ 	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: halfHeaderReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 	"get index and fail if not a +ve integer"
+ 	jumpNElementsNonInt := self genJumpNotSmallInteger: 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 half header now"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: halfHeaderReg.
+ 	"get integer value of num fields in TempReg now"
+ 	cogit MoveR: Arg0Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	"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: TempReg R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCq: 0.
+ 	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: TempReg R: instSpecReg.
+ 	"compute odd bits and add into halfHeaderReg; 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: halfHeaderReg.
+ 	"round up num elements to numSlots in instSpecReg"
+ 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCq: 0.
+ 	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: TempReg R: instSpecReg.
+ 	"push fill value"
+ 	cogit PushCw: objectMemory nilObject.
+ 	"fall through to allocate"
+ 
+ 	jumpBytePrepDone jmpTarget:
+ 	(jumpLongPrepDone jmpTarget: cogit Label).
+ 
+ 	"write half header now; it frees halfHeaderReg"
+ 	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
+ 	"save numSlots to halfHeaderReg"
+ 	cogit MoveR: instSpecReg R: halfHeaderReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
+ 	 rounded up to 8 bytes."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	"round up to allocationUnit"
+ 	jumpHasSlots jmpTarget:
+ 	(cogit MoveR: byteSizeReg R: TempReg).
+ 	cogit AndCq: 1 R: TempReg.
+ 	cogit AddR: TempReg R: byteSizeReg.
+ 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"shift halfHeaderReg to put numSlots in correct place"
+ 	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
+ 	"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: halfHeaderReg Mw: 4 r: ReceiverResultReg.
+ 	"now fill"
+ 	cogit PopR: fillReg.
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	"pop discarded fill value & fall through to failure"
+ 	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
+ 
+ 	jumpUnhashed jmpTarget:
+ 	(jumpFailCuzFixed jmpTarget:
+ 	(jumpArrayTooBig jmpTarget:
+ 	(jumpByteTooBig jmpTarget:
+ 	(jumpLongTooBig jmpTarget:
+ 	(jumpNElementsNonInt jmpTarget: cogit Label))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveStringAtPut (in category 'primitive generators') -----
+ genPrimitiveStringAtPut
+ 	"Implement the guts of primitiveStringAtPut"
+ 	| formatReg jumpBadIndex jumpBadArg jumpWordsDone jumpBytesOutOfRange
+ 	  jumpIsBytes jumpNotString jumpIsCompiledMethod jumpImmutable
+ 	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsUnsupported |
+ 	<inline: true>
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpBadArg type: #'AbstractInstruction *'>
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsDone type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
+ 
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	jumpBadArg := self genJumpNotCharacterInScratchReg: 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; words and/or bytes.
+ 		  0 to 8 = pointer objects, forwarders, reserved.
+ 		  9 (?) 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable (but unused)
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpNotString := cogit JumpBelowOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpShortsUnsupported := cogit JumpGreaterOrEqual: 0.
+ 
+ 	cogit CmpR: Arg0Reg R: ClassReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpWordsDone := cogit Jump: 0.
+ 
+ 	"there are no shorts as yet.  so this is dead code:
+ 	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
+ 	jumpShortsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
+ 	cogit AndCq: 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpShortsDone := cogit Jump: 0."
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit CmpCq: (objectMemory characterObjectOf: 255) R: Arg1Reg).
+ 	jumpBytesOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertCharacterToCodeInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
+ 	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 
+ 	jumpWordsDone jmpTarget: cogit genPrimReturn.
+ 
+ 	jumpBadArg jmpTarget:
+ 	(jumpNotString jmpTarget:
+ 	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpIsCompiledMethod jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsUnsupported jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget: cogit Label)))))).
+ 
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable jmpTarget: cogit Label].
+ 
+ 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
+ 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
+ 
+ 	jumpBadIndex jmpTarget: cogit Label.
+ 
+ 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveAt: (in category 'primitive generators') -----
- genInnerPrimitiveAt: retNoffset
- 	"Implement the guts of primitiveAt"
- 	| formatReg convertToIntAndReturn
- 	  jumpNotIndexable jumpImmediate jumpBadIndex
- 	  jumpIsBytes jumpIsShorts jumpIsWords jumpIsArray jumpHasFixedFields jumpIsContext
- 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
- 	<inline: true>
- 	"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: #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 *'>
- 
- 	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.
- 
- 	jumpIsBytes jmpTarget:
- 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
- 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
- 		cogit SubR: formatReg R: ClassReg;
- 		CmpR: Arg1Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	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 RetN: retNoffset.
- 
- 	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: 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 RetN: retNoffset.
- 
- 	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 RetN: retNoffset.
- 
- 	jumpFixedFieldsOutOfBounds jmpTarget:
- 	(jumpArrayOutOfBounds jmpTarget:
- 	(jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsOutOfBounds jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget:
- 	(jumpNotIndexable jmpTarget:
- 	(jumpIsContext jmpTarget:
- 	(jumpBadIndex jmpTarget:
- 	(jumpImmediate jmpTarget: cogit Label)))))))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
- genInnerPrimitiveIdentityHash: retNoffset
- 	| jumpImm jumpSF jumpNotSet ret |
- 	<var: #jumpSF type: #'AbstractInstruction *'>
- 	<var: #jumpImm type: #'AbstractInstruction *'>
- 	<var: #jumpNotSet type: #'AbstractInstruction *'>
- 	jumpImm := self genJumpImmediate: ReceiverResultReg. "uses TstCqR"
- 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	cogit CmpCq: ConstZero R: TempReg.
- 	jumpNotSet := cogit JumpZero: 0.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	ret := cogit RetN: retNoffset.
- 	jumpImm jmpTarget: cogit Label.
- 	jumpSF := cogit "Fail SmallFloat because their hash uses rotatedFloatBitsOf: the oop"
- 		AndCq: objectMemory tagMask R: ReceiverResultReg R: TempReg;
- 		CmpCq: objectMemory smallIntegerTag R: TempReg;
- 		JumpZero: ret;
- 		CmpCq: objectMemory characterTag R: TempReg;
- 		JumpNonZero: 0.
- 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
- 	cogit Jump: ret.
- 	jumpNotSet jmpTarget: (jumpSF jmpTarget: cogit Label).
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveNew: (in category 'primitive generators') -----
- genInnerPrimitiveNew: retNoffset
- 	"Implement primitiveNew for convenient cases:
- 	- the receiver has a hash
- 	- the receiver is fixed size (excluding ephemerons to save instructions & miniscule time)
- 	- single word header/num slots < numSlotsMask
- 	- the result fits in eden (actually below scavengeThreshold)"
- 
- 	| headerReg fillReg instSpecReg byteSizeReg
- 	  jumpUnhashed jumpVariableOrEphemeron jumpNoSpace jumpTooBig jumpHasSlots
- 	  fillLoop skip |
- 	<var: 'skip' type: #'AbstractInstruction *'>
- 	<var: 'fillLoop' type: #'AbstractInstruction *'>
- 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
- 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
- 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
- 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
- 
- 	"header will contain classIndex/class's hash & format & numSlots/fixed size and finally fill value (nilObject)."
- 	headerReg := fillReg := SendNumArgsReg.
- 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
- 	instSpecReg := byteSizeReg := ClassReg.
- 
- 	"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 class's format inst var for both inst spec (format field) and num fixed fields"
- 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit MoveR: TempReg R: instSpecReg.
- 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
- 	cogit AndCq: objectMemory formatMask R: TempReg.
- 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
- 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
- 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
- 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
- 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
- 	jumpTooBig := cogit JumpAboveOrEqual: 0.
- 	"Add format to classIndex/format in header; the add in numSlots"
- 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
- 	cogit AddR: TempReg R: 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.
- 	"round up to allocationUnit"
- 	jumpHasSlots jmpTarget:
- 	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
- 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
- 	skip jmpTarget:
- 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
- 	(cogit AddR: Arg1Reg R: byteSizeReg).
- 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
- 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
- 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
- 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
- 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
- 	"write header"
- 	cogit MoveR: headerReg Mw: 0 r: Arg1Reg.
- 	"now fill"
- 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
- 	cogit MoveCq: objectMemory nilObject R: fillReg.
- 	fillLoop := 
- 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
- 	cogit AddCq: 8 R: Arg1Reg.
- 	cogit CmpR: Arg1Reg R: byteSizeReg.
- 	cogit JumpAbove: fillLoop.
- 	cogit RetN: retNoffset.
- 
- 	jumpUnhashed jmpTarget:
- 	(jumpVariableOrEphemeron jmpTarget:
- 	(jumpTooBig jmpTarget:
- 	(jumpNoSpace jmpTarget: cogit Label))).
- 
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveNewWithArg: retNoffset
- 	"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 *'>
- 
- 	"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 := 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 RetN: retNoffset.
- 	
- 	jumpNoSpace jmpTarget:
- 	(jumpUnhashed jmpTarget:
- 	(jumpFailCuzFixed jmpTarget:
- 	(jumpArrayTooBig jmpTarget:
- 	(jumpByteTooBig jmpTarget:
- 	(jumpLongTooBig jmpTarget:
- 	(jumpNElementsNonInt jmpTarget: cogit Label)))))).
- 
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveAt (in category 'primitive generators') -----
+ genPrimitiveAt
+ 	| formatReg convertToIntAndReturn
+ 	  jumpNotIndexable jumpImmediate jumpBadIndex
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpIsArray jumpHasFixedFields jumpIsContext
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
+ 	<inline: true>
+ 	"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: #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.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	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: 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.
+ 
+ 	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.
+ 
+ 	jumpFixedFieldsOutOfBounds jmpTarget:
+ 	(jumpArrayOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpNotIndexable jmpTarget:
+ 	(jumpIsContext jmpTarget:
+ 	(jumpBadIndex jmpTarget:
+ 	(jumpImmediate jmpTarget: cogit Label)))))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveIdentityHash (in category 'primitive generators') -----
+ genPrimitiveIdentityHash
+ 	| jumpImm jumpSF jumpNotSet ret |
+ 	<var: #jumpSF type: #'AbstractInstruction *'>
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSet type: #'AbstractInstruction *'>
+ 	jumpImm := self genJumpImmediate: ReceiverResultReg. "uses TstCqR"
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit CmpCq: ConstZero R: TempReg.
+ 	jumpNotSet := cogit JumpZero: 0.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	ret := cogit genPrimReturn.
+ 	jumpImm jmpTarget: cogit Label.
+ 	jumpSF := cogit "Fail SmallFloat because their hash uses rotatedFloatBitsOf: the oop"
+ 		AndCq: objectMemory tagMask R: ReceiverResultReg R: TempReg;
+ 		CmpCq: objectMemory smallIntegerTag R: TempReg;
+ 		JumpZero: ret;
+ 		CmpCq: objectMemory characterTag R: TempReg;
+ 		JumpNonZero: 0.
+ 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit Jump: ret.
+ 	jumpNotSet jmpTarget: (jumpSF jmpTarget: cogit Label).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveNew (in category 'primitive generators') -----
+ genPrimitiveNew
+ 	"Implement primitiveNew for convenient cases:
+ 	- the receiver has a hash
+ 	- the receiver is fixed size (excluding ephemerons to save instructions & miniscule time)
+ 	- single word header/num slots < numSlotsMask
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	| headerReg fillReg instSpecReg byteSizeReg
+ 	  jumpUnhashed jumpVariableOrEphemeron jumpNoSpace jumpTooBig jumpHasSlots
+ 	  fillLoop skip |
+ 	<var: 'skip' type: #'AbstractInstruction *'>
+ 	<var: 'fillLoop' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
+ 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
+ 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
+ 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
+ 
+ 	NewspeakVM ifTrue:
+ 		[cogit methodNumArgs = 1 ifTrue:
+ 			[^self genPrimitiveMirrorNew]].
+ 	cogit methodNumArgs ~= 0 ifTrue:
+ 		[^UnimplementedPrimitive].
+ 
+ 	"header will contain classIndex/class's hash & format & numSlots/fixed size and finally fill value (nilObject)."
+ 	headerReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
+ 	instSpecReg := byteSizeReg := ClassReg.
+ 
+ 	"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 class's format inst var for both inst spec (format field) and num fixed fields"
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit MoveR: TempReg R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
+ 	cogit AndCq: objectMemory formatMask R: TempReg.
+ 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
+ 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
+ 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
+ 	jumpTooBig := cogit JumpAboveOrEqual: 0.
+ 	"Add format to classIndex/format in header; the add in numSlots"
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: 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.
+ 	"round up to allocationUnit"
+ 	jumpHasSlots jmpTarget:
+ 	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 	(cogit AddR: Arg1Reg R: byteSizeReg).
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	"write header"
+ 	cogit MoveR: headerReg Mw: 0 r: Arg1Reg.
+ 	"now fill"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	cogit MoveCq: objectMemory nilObject R: fillReg.
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	jumpUnhashed jmpTarget:
+ 	(jumpVariableOrEphemeron jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpNoSpace jmpTarget: cogit Label))).
+ 
+ 	^0!

Item was added:
+ ----- 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 := 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 added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genSmallFloatArithmetic:preOpCheck: (in category 'primitive generators') -----
+ genSmallFloatArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
+ 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
+ 	<var: #jumpFailClass type: #'AbstractInstruction *'>
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
+ 	<var: #doOp type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	cogit MoveR: Arg0Reg R: ClassReg.
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
+ 	jumpFailClass := cogit JumpNonZero: 0.
+ 	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
+ 	doOp := cogit Label.
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck := cogit perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
+ 	cogit gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
+ 	jumpFailAlloc := self
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpImmediate jmpTarget: cogit Label.
+ 	self maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
+ 	jumpNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	cogit ConvertR: ClassReg Rd: DPFPReg1.
+ 	cogit Jump: doOp.
+ 	jumpFailClass jmpTarget: cogit Label.
+ 	jumpNonInt jmpTarget: jumpFailClass getJmpTarget.
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
+ 	jumpFailAlloc jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
+ genSmallFloatComparison: jumpOpcodeGenerator invert: invertComparison
+ 	"Receiver and arg in registers.
+ 	 Stack looks like
+ 		return address"
+ 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
+ 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpCond type: #'AbstractInstruction *'>
+ 	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
+ 	jumpFail := cogit JumpNonZero: 0.
+ 	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
+ 	invertComparison "May need to invert for NaNs"
+ 		ifTrue: [compare := cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
+ 		ifFalse: [compare := cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
+ 	jumpCond := cogit perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
+ 	cogit genMoveFalseR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpCond jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 	jumpImmediate jmpTarget: cogit Label.
+ 	self maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
+ 	jumpNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit ConvertR: Arg0Reg Rd: DPFPReg1.
+ 	cogit Jump: compare.
+ 	jumpNonInt jmpTarget:  (jumpFail jmpTarget: cogit Label).
+ 	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveAsCharacter:inReg: (in category 'primitive generators') -----
- genInnerPrimitiveAsCharacter: retNOffset inReg: reg
- 	| jumpNotInt jumpOutOfRange |
- 	<var: 'jumpNotInt' type: #'AbstractInstruction *'>
- 	<var: 'jumpOutOfRange' type: #'AbstractInstruction *'>
- 	reg ~= ReceiverResultReg ifTrue:
- 		[jumpNotInt := self genJumpNotSmallInteger: reg scratchReg: TempReg].
- 	cogit MoveR: reg R: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit CmpCq: 1 << 30 - 1 R: TempReg.
- 	jumpOutOfRange := cogit JumpAbove: 0.
- 	self genConvertSmallIntegerToCharacterInReg: reg.
- 	reg ~= ReceiverResultReg ifTrue:
- 		[cogit MoveR: reg R: ReceiverResultReg].
- 	cogit RetN: retNOffset.
- 	jumpOutOfRange jmpTarget: cogit Label.
- 	reg ~= ReceiverResultReg ifTrue:
- 		[jumpNotInt jmpTarget: jumpOutOfRange getJmpTarget].
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveCharacterValue: (in category 'primitive generators') -----
- genInnerPrimitiveCharacterValue: retNOffset
- 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
- 	cogit RetN: retNOffset.
- 	^UnfailingPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveIdentical:orNotIf: (in category 'primitive generators') -----
- genInnerPrimitiveIdentical: retNoffset orNotIf: orNot
- 	| jumpImmediate jumpCmp |
- 	<var: #jumpCmp type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	jumpImmediate := self genJumpImmediate: Arg0Reg.
- 	self genEnsureObjInRegNotForwarded: Arg0Reg scratchReg: TempReg.
- 	jumpImmediate jmpTarget:
- 		(cogit CmpR: Arg0Reg R: ReceiverResultReg).
- 	jumpCmp := orNot
- 					ifTrue: [cogit JumpZero: 0]
- 					ifFalse: [cogit JumpNonZero: 0].
- 	cogit genMoveTrueR: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpCmp jmpTarget: (cogit genMoveFalseR: ReceiverResultReg).
- 	cogit RetN: retNoffset.
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
- genInnerPrimitiveIdentityHash: retNoffset
- 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveNew: (in category 'primitive generators') -----
- genInnerPrimitiveNew: retNoffset
- 	"Implement primitiveNew for convenient cases:
- 	- the receiver has a hash
- 	- the receiver is fixed size (excluding ephemerons to save instructions & miniscule time)
- 	- single word header/num slots < numSlotsMask
- 	- the result fits in eden"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
- genInnerPrimitiveNewWithArg: retNoffset
- 	"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
- 
- 	Here are some dynamic frequencies of class formats in the interpreter doing startUp
- 	and recompiling ArrayedCollection in a Squeak4.1 image:
- 		{3251->#arrayFormat.		(Array)
- 		 1685->#firstByteFormat.	(ByteString, LargePositiveInteger, very few ByteArray)
- 		 1533->#firstLongFormat.	(Bitmaps, Floats, MatrixTransform2x3, WordArray)
- 		 110->#weakArrayFormat.	(WeakArray, WeakMessageSend)
- 		 35->#indexablePointersFormat.	(MethodContext)
- 		 5->#nonIndexablePointerFormat	(DirectoryEntry)}"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveObjectAt: (in category 'primitive generators') -----
- genInnerPrimitiveObjectAt: retNOffset
- 	| headerReg
- 	  jumpBadIndex jumpNotCogMethod jumpBounds jumpNotHeaderIndex |
- 	<var: #jumpBounds type: #'AbstractInstruction *'>
- 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpNotCogMethod type: #'AbstractInstruction *'>
- 	<var: #jumpNotHeaderIndex type: #'AbstractInstruction *'>
- 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"get header into Arg1Reg..."
- 	cogit MoveMw: objectMemory baseHeaderSize r: ReceiverResultReg R: (headerReg := Arg1Reg).
- 	jumpNotCogMethod := self genJumpSmallInteger: headerReg scratchReg: TempReg.
- 	cogit MoveMw: (cogit offset: CogMethod of: #methodHeader) r: headerReg R: headerReg.
- 	jumpNotCogMethod jmpTarget: (cogit
- 		CmpCq: (objectMemory integerObjectOf: 1) R: Arg0Reg).
- 	jumpNotHeaderIndex := cogit JumpNonZero: 0.
- 	cogit
- 		MoveR: headerReg R: ReceiverResultReg;
- 		RetN: retNOffset.
- 	jumpNotHeaderIndex jmpTarget: (cogit
- 		AndCq: (objectMemory integerObjectOf: coInterpreter alternateHeaderNumLiteralsMask) R: headerReg).
- 	cogit
- 		SubCq: (objectMemory integerObjectOf: 1) - objectMemory smallIntegerTag R: Arg0Reg;
- 		CmpR: headerReg R: Arg0Reg.
- 	jumpBounds := cogit JumpAbove: 0.
- 
- 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
- 	cogit
- 		AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg;
- 		MoveXwr: Arg0Reg R: ReceiverResultReg R: ReceiverResultReg;
- 		RetN: retNOffset.
- 
- 	jumpBounds jmpTarget: (cogit
- 		AddCq: (objectMemory integerObjectOf: 1) - objectMemory smallIntegerTag R: Arg0Reg).
- 	jumpBadIndex jmpTarget: cogit Label.
- 	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveSize: (in category 'primitive generators') -----
- genInnerPrimitiveSize: retNoffset
- 	| jumpImm jumpNotIndexable jumpIsContext |
- 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
- 	<var: #jumpImm type: #'AbstractInstruction *'>
- 	<var: #jumpIsContext type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
- 	jumpImm := self genJumpImmediate: ReceiverResultReg.
- 	self
- 		genGetSizeOf: ReceiverResultReg
- 		into: ClassReg
- 		formatReg: SendNumArgsReg
- 		scratchReg: TempReg
- 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
- 	self genConvertIntegerToSmallIntegerInReg: ClassReg.
- 	cogit MoveR: ClassReg R: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpImm jmpTarget: (jumpNotIndexable jmpTarget: (jumpIsContext jmpTarget: cogit Label)).
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveStringAt: (in category 'primitive generators') -----
- genInnerPrimitiveStringAt: retNoffset
- 	"Implement the guts of primitiveStringAt; dispatch on size"
- 	| formatReg jumpNotIndexable jumpBadIndex done
- 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
- 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
- 	<inline: true>
- 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
- 	<var: #done type: #'AbstractInstruction *'>
- 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
- 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
- 	<var: #jumpIsWords type: #'AbstractInstruction *'>
- 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
- 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
- 
- 	cogit MoveR: Arg0Reg R: Arg1Reg.
- 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
- 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
- 
- 	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 firstByteFormat R: formatReg.
- 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
- 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
- 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
- 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
- 	jumpIsWords := cogit JumpGreaterOrEqual: 0.
- 	jumpNotIndexable := cogit Jump: 0.
- 
- 	jumpIsBytes jmpTarget:
- 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
- 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
- 		cogit SubR: formatReg R: ClassReg;
- 		CmpR: Arg1Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
- 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
- 	cogit backEnd byteReadsZeroExtend ifFalse:
- 			[cogit AndCq: 255 R: ReceiverResultReg].
- 	done := cogit Label.
- 	self genConvertIntegerToCharacterInReg: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 
- 	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: done.
- 
- 	jumpIsWords jmpTarget:
- 		(cogit CmpR: Arg1Reg R: ClassReg).
- 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
- 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
- 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
- 	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	cogit Jump: done.
- 
- 	jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsOutOfBounds jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget:
- 	(jumpWordTooBig jmpTarget:
- 	(jumpNotIndexable jmpTarget: 
- 	(jumpBadIndex jmpTarget: cogit Label))))).
- 
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveAsCharacter (in category 'primitive generators') -----
+ genPrimitiveAsCharacter
+ 	| reg jumpNotInt jumpOutOfRange |
+ 	<var: 'jumpNotInt' type: #'AbstractInstruction *'>
+ 	<var: 'jumpOutOfRange' type: #'AbstractInstruction *'>
+ 	cogit methodNumArgs = 0
+ 		ifTrue: [reg := ReceiverResultReg]
+ 		ifFalse:
+ 			[cogit methodNumArgs > 1 ifTrue:
+ 				[^UnimplementedPrimitive].
+ 			 reg := Arg0Reg.
+ 			 cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 			 jumpNotInt := self genJumpNotSmallInteger: reg scratchReg: TempReg].
+ 	cogit MoveR: reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit CmpCq: 1 << 30 - 1 R: TempReg.
+ 	jumpOutOfRange := cogit JumpAbove: 0.
+ 	self genConvertSmallIntegerToCharacterInReg: reg.
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[cogit MoveR: reg R: ReceiverResultReg].
+ 	cogit genPrimReturn.
+ 	jumpOutOfRange jmpTarget: cogit Label.
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[jumpNotInt jmpTarget: jumpOutOfRange getJmpTarget].
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveCharacterValue (in category 'primitive generators') -----
+ genPrimitiveCharacterValue
+ 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	^UnfailingPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveIdenticalOrNotIf: (in category 'primitive generators') -----
+ genPrimitiveIdenticalOrNotIf: orNot
+ 	| jumpImmediate jumpCmp |
+ 	<var: #jumpCmp type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genEnsureObjInRegNotForwarded: Arg0Reg scratchReg: TempReg.
+ 	jumpImmediate jmpTarget:
+ 		(cogit CmpR: Arg0Reg R: ReceiverResultReg).
+ 	jumpCmp := orNot
+ 					ifTrue: [cogit JumpZero: 0]
+ 					ifFalse: [cogit JumpNonZero: 0].
+ 	cogit genMoveTrueR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpCmp jmpTarget: (cogit genMoveFalseR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 	^UnfailingPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveIdentityHash (in category 'primitive generators') -----
+ genPrimitiveIdentityHash
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveObjectAt (in category 'primitive generators') -----
+ genPrimitiveObjectAt
+ 	| headerReg
+ 	  jumpBadIndex jumpNotCogMethod jumpBounds jumpNotHeaderIndex |
+ 	<var: #jumpBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpNotCogMethod type: #'AbstractInstruction *'>
+ 	<var: #jumpNotHeaderIndex type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"get header into Arg1Reg..."
+ 	cogit MoveMw: objectMemory baseHeaderSize r: ReceiverResultReg R: (headerReg := Arg1Reg).
+ 	jumpNotCogMethod := self genJumpSmallInteger: headerReg scratchReg: TempReg.
+ 	cogit MoveMw: (cogit offset: CogMethod of: #methodHeader) r: headerReg R: headerReg.
+ 	jumpNotCogMethod jmpTarget: (cogit
+ 		CmpCq: (objectMemory integerObjectOf: 1) R: Arg0Reg).
+ 	jumpNotHeaderIndex := cogit JumpNonZero: 0.
+ 	cogit
+ 		MoveR: headerReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 	jumpNotHeaderIndex jmpTarget: (cogit
+ 		AndCq: (objectMemory integerObjectOf: coInterpreter alternateHeaderNumLiteralsMask) R: headerReg).
+ 	cogit
+ 		SubCq: (objectMemory integerObjectOf: 1) - objectMemory smallIntegerTag R: Arg0Reg;
+ 		CmpR: headerReg R: Arg0Reg.
+ 	jumpBounds := cogit JumpAbove: 0.
+ 
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit
+ 		AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg;
+ 		MoveXwr: Arg0Reg R: ReceiverResultReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 
+ 	jumpBounds jmpTarget: (cogit
+ 		AddCq: (objectMemory integerObjectOf: 1) - objectMemory smallIntegerTag R: Arg0Reg).
+ 	jumpBadIndex jmpTarget: cogit Label.
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveSize (in category 'primitive generators') -----
+ genPrimitiveSize
+ 	| jumpImm jumpNotIndexable jumpIsContext |
+ 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpIsContext type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	jumpImm := self genJumpImmediate: ReceiverResultReg.
+ 	self
+ 		genGetSizeOf: ReceiverResultReg
+ 		into: ClassReg
+ 		formatReg: SendNumArgsReg
+ 		scratchReg: TempReg
+ 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
+ 	self genConvertIntegerToSmallIntegerInReg: ClassReg.
+ 	cogit MoveR: ClassReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpImm jmpTarget: (jumpNotIndexable jmpTarget: (jumpIsContext jmpTarget: cogit Label)).
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveStringAt (in category 'primitive generators') -----
+ genPrimitiveStringAt
+ 	"Implement the guts of primitiveStringAt; dispatch on size"
+ 	| formatReg jumpNotIndexable jumpBadIndex done
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
+ 	<inline: true>
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #done type: #'AbstractInstruction *'>
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
+ 	<var: #jumpIsWords type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
+ 
+ 	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 firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpIsWords := cogit JumpGreaterOrEqual: 0.
+ 	jumpNotIndexable := cogit Jump: 0.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
+ 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit backEnd byteReadsZeroExtend ifFalse:
+ 			[cogit AndCq: 255 R: ReceiverResultReg].
+ 	done := cogit Label.
+ 	self genConvertIntegerToCharacterInReg: 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: done.
+ 
+ 	jumpIsWords jmpTarget:
+ 		(cogit CmpR: Arg1Reg R: ClassReg).
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit Jump: done.
+ 
+ 	jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpWordTooBig jmpTarget:
+ 	(jumpNotIndexable jmpTarget: 
+ 	(jumpBadIndex jmpTarget: cogit Label))))).
+ 
+ 	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveAt: (in category 'primitive generators') -----
- genInnerPrimitiveAt: retNoffset
- 	| jumpSI jumpNotSI jumpNotIndexable jumpIsContext jumpBounds jumpFmtGt4 jumpFmtEq2 jumpFmtLt8 jumpFmtGt11 jumpLarge |
- 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
- 	<var: #jumpIsContext type: #'AbstractInstruction *'>
- 	<var: #jumpBounds type: #'AbstractInstruction *'>
- 	<var: #jumpFmtGt4 type: #'AbstractInstruction *'>
- 	<var: #jumpFmtEq2 type: #'AbstractInstruction *'>
- 	<var: #jumpFmtLt8 type: #'AbstractInstruction *'>
- 	<var: #jumpFmtGt11 type: #'AbstractInstruction *'>
- 	<var: #jumpLarge type: #'AbstractInstruction *'>
- 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
- 	cogit MoveR: Arg0Reg R: Arg1Reg.
- 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg.
- 	self
- 		genGetSizeOf: ReceiverResultReg
- 		into: ClassReg
- 		formatReg: SendNumArgsReg
- 		scratchReg: TempReg
- 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
- 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
- 	cogit SubCq: 1 R: Arg1Reg.
- 	cogit CmpR: ClassReg R: Arg1Reg.
- 	jumpBounds := cogit JumpAboveOrEqual: 0.
- 	"This is tedious.  Because of register pressure on x86 (and the baroque
- 	 complexity of the size computation) we have to recompute the format
- 	 because it may have been smashed computing the fixed fields.  But at
- 	 least we have the fixed fields, if any, in formatReg and recomputing
- 	 these is more expensive than recomputing format.  In any case this
- 	 should still be faster than the interpreter and we hope this object
- 	 representation's days are numbered."
- 	cogit
- 		MoveMw: 0 r: ReceiverResultReg R: ClassReg;	"self baseHeader: receiver"
- 		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: ClassReg;
- 		AndCq: self instFormatFieldMask R: ClassReg;	"self formatOfHeader: ClassReg"
- 		CmpCq: 4 R: ClassReg.
- 	jumpFmtGt4 := cogit JumpGreater: 0.
- 	cogit CmpCq: 2 R: ClassReg.	"Common case, e.g. Array, has format = 2"
- 	jumpFmtEq2 := cogit JumpZero: 0.
- 	cogit AddR: SendNumArgsReg R: Arg1Reg. "Add fixed fields to index"
- 	jumpFmtEq2 jmpTarget: cogit Label.
- 	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
- 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: Arg1Reg;
- 		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
- 		RetN: retNoffset.
- 	jumpFmtGt4 jmpTarget: cogit Label.
- 	"Byte objects have formats 8 through 15, Compiled methods being 12 through 15;
- 	 fail for CompiledMethod allowing the CoInterpeter to impose stricter bounds checks."
- 	cogit CmpCq: 8 R: ClassReg.
- 	jumpFmtLt8 := cogit JumpLess: 0.
- 	cogit CmpCq: 11 R: ClassReg.
- 	jumpFmtGt11 := cogit JumpGreater: 0.
- 	cogit
- 		AddCq: objectMemory baseHeaderSize R: Arg1Reg;
- 		MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
- 	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpFmtLt8 jmpTarget: cogit Label.
- 	self assert: objectMemory wordSize = 4. "documenting my laziness"
- 	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
- 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: Arg1Reg;
- 		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
- 		CmpCq: 16r3FFFFFFF R: ReceiverResultReg.
- 	jumpLarge := cogit JumpAbove: 0.
- 	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpLarge jmpTarget: (cogit CallRT: cePositive32BitIntegerTrampoline).
- 	cogit
- 		MoveR: TempReg R: ReceiverResultReg;
- 		RetN: retNoffset.
- 	jumpSI jmpTarget:
- 	(jumpNotSI jmpTarget:
- 	(jumpNotIndexable jmpTarget:
- 	(jumpIsContext jmpTarget:
- 	(jumpBounds jmpTarget:
- 	(jumpFmtGt11 jmpTarget:
- 		cogit Label))))).
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveIdentical:orNotIf: (in category 'primitive generators') -----
- genInnerPrimitiveIdentical: retNoffset orNotIf: orNot
- 	| jumpCmp |
- 	<var: #jumpCmp type: #'AbstractInstruction *'>
- 	cogit CmpR: Arg0Reg R: ReceiverResultReg.
- 	jumpCmp := orNot
- 					ifTrue: [cogit JumpZero: 0]
- 					ifFalse: [cogit JumpNonZero: 0].
- 	cogit genMoveTrueR: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpCmp jmpTarget: (cogit genMoveFalseR: ReceiverResultReg).
- 	cogit RetN: retNoffset.
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
- genInnerPrimitiveIdentityHash: retNOffset
- 	| jumpSI |
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
- 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	cogit RetN: retNOffset.
- 	jumpSI jmpTarget: cogit Label.
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveSize: (in category 'primitive generators') -----
- genInnerPrimitiveSize: retNoffset
- 	| jumpSI jumpNotIndexable jumpIsContext |
- 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpIsContext type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
- 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
- 	self
- 		genGetSizeOf: ReceiverResultReg
- 		into: ClassReg
- 		formatReg: SendNumArgsReg
- 		scratchReg: TempReg
- 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
- 	self genConvertIntegerToSmallIntegerInReg: ClassReg.
- 	cogit MoveR: ClassReg R: ReceiverResultReg.
- 	cogit RetN: retNoffset.
- 	jumpSI jmpTarget: (jumpNotIndexable jmpTarget: (jumpIsContext jmpTarget: cogit Label)).
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveStringAt: (in category 'primitive generators') -----
- genInnerPrimitiveStringAt: retNOffset
- 	| jumpNotSI jumpNotByteIndexable jumpBounds jumpShortHeader jumpSkip |
- 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpNotByteIndexable type: #'AbstractInstruction *'>
- 	<var: #jumpBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortHeader type: #'AbstractInstruction *'>
- 	<var: #jumpSkip type: #'AbstractInstruction *'>
- 	cogit MoveR: Arg0Reg R: Arg1Reg.
- 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg.
- 	cogit
- 		MoveMw: 0 r: ReceiverResultReg R: TempReg;	"self baseHeader: receiver"
- 		MoveR: TempReg R: ClassReg;					"copy header word; we'll need it later"
- 		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: TempReg;
- 		AndCq: self instFormatFieldMask R: TempReg;	"self formatOfHeader: destReg"
- 		MoveR: TempReg R: SendNumArgsReg;
- 		AndCq: 3 R: SendNumArgsReg;					"get odd bytes from format (if it turns out to be bytes)"
- 		SubR: SendNumArgsReg R: TempReg;
- 		CmpCq: 8 R: TempReg.							"check format is 8"
- 	jumpNotByteIndexable := cogit JumpNonZero: 0.
- 	cogit
- 		MoveR: ClassReg R: TempReg;
- 		AndCq: TypeMask R: TempReg;
- 		CmpCq: HeaderTypeSizeAndClass R: TempReg.	"(hdr bitAnd: TypeMask) = HeaderTypeSizeAndClass"
- 	jumpShortHeader := cogit JumpNonZero: 0.
- 	self assert: Size4Bit = 0.
- 	cogit
- 		MoveMw: 0 - (2 * objectMemory wordSize) r: ReceiverResultReg R: ClassReg; "(self sizeHeader: oop) bitAnd: LongSizeMask"
- 		AndCq: LongSizeMask signedIntFromLong R: ClassReg.
- 	jumpSkip :=  cogit Jump: 0.
- 	jumpShortHeader jmpTarget: (cogit AndCq: SizeMask R: ClassReg).	"hdr bitAnd: SizeMask"
- 	jumpSkip jmpTarget: (cogit SubCq: objectMemory baseHeaderSize R: ClassReg). "sz - BaseHeaderSize"
- 	cogit SubR: SendNumArgsReg R: ClassReg. "sz - (fmt bitAnd: 3)"
- 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
- 	cogit SubCq: 1 R: Arg1Reg.
- 	cogit CmpR: ClassReg R: Arg1Reg.
- 	jumpBounds := cogit JumpAboveOrEqual: 0.
- 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
- 	cogit genMoveConstant: objectMemory characterTable R: Arg0Reg.
- 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
- 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: ReceiverResultReg.
- 	cogit MoveXwr: ReceiverResultReg R: Arg0Reg R: ReceiverResultReg.
- 	cogit RetN: retNOffset.
- 	jumpNotSI jmpTarget:
- 	(jumpNotByteIndexable jmpTarget:
- 	(jumpBounds jmpTarget:
- 		cogit Label)).
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genPrimitiveAt (in category 'primitive generators') -----
+ genPrimitiveAt
+ 	| jumpSI jumpNotSI jumpNotIndexable jumpIsContext jumpBounds jumpFmtGt4 jumpFmtEq2 jumpFmtLt8 jumpFmtGt11 jumpLarge |
+ 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	<var: #jumpIsContext type: #'AbstractInstruction *'>
+ 	<var: #jumpBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpFmtGt4 type: #'AbstractInstruction *'>
+ 	<var: #jumpFmtEq2 type: #'AbstractInstruction *'>
+ 	<var: #jumpFmtLt8 type: #'AbstractInstruction *'>
+ 	<var: #jumpFmtGt11 type: #'AbstractInstruction *'>
+ 	<var: #jumpLarge type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg.
+ 	self
+ 		genGetSizeOf: ReceiverResultReg
+ 		into: ClassReg
+ 		formatReg: SendNumArgsReg
+ 		scratchReg: TempReg
+ 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg.
+ 	cogit CmpR: ClassReg R: Arg1Reg.
+ 	jumpBounds := cogit JumpAboveOrEqual: 0.
+ 	"This is tedious.  Because of register pressure on x86 (and the baroque
+ 	 complexity of the size computation) we have to recompute the format
+ 	 because it may have been smashed computing the fixed fields.  But at
+ 	 least we have the fixed fields, if any, in formatReg and recomputing
+ 	 these is more expensive than recomputing format.  In any case this
+ 	 should still be faster than the interpreter and we hope this object
+ 	 representation's days are numbered."
+ 	cogit
+ 		MoveMw: 0 r: ReceiverResultReg R: ClassReg;	"self baseHeader: receiver"
+ 		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: ClassReg;
+ 		AndCq: self instFormatFieldMask R: ClassReg;	"self formatOfHeader: ClassReg"
+ 		CmpCq: 4 R: ClassReg.
+ 	jumpFmtGt4 := cogit JumpGreater: 0.
+ 	cogit CmpCq: 2 R: ClassReg.	"Common case, e.g. Array, has format = 2"
+ 	jumpFmtEq2 := cogit JumpZero: 0.
+ 	cogit AddR: SendNumArgsReg R: Arg1Reg. "Add fixed fields to index"
+ 	jumpFmtEq2 jmpTarget: cogit Label.
+ 	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
+ 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: Arg1Reg;
+ 		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 	jumpFmtGt4 jmpTarget: cogit Label.
+ 	"Byte objects have formats 8 through 15, Compiled methods being 12 through 15;
+ 	 fail for CompiledMethod allowing the CoInterpeter to impose stricter bounds checks."
+ 	cogit CmpCq: 8 R: ClassReg.
+ 	jumpFmtLt8 := cogit JumpLess: 0.
+ 	cogit CmpCq: 11 R: ClassReg.
+ 	jumpFmtGt11 := cogit JumpGreater: 0.
+ 	cogit
+ 		AddCq: objectMemory baseHeaderSize R: Arg1Reg;
+ 		MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
+ 	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpFmtLt8 jmpTarget: cogit Label.
+ 	self assert: objectMemory wordSize = 4. "documenting my laziness"
+ 	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
+ 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: Arg1Reg;
+ 		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
+ 		CmpCq: 16r3FFFFFFF R: ReceiverResultReg.
+ 	jumpLarge := cogit JumpAbove: 0.
+ 	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpLarge jmpTarget: (cogit CallRT: cePositive32BitIntegerTrampoline).
+ 	cogit
+ 		MoveR: TempReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 	jumpSI jmpTarget:
+ 	(jumpNotSI jmpTarget:
+ 	(jumpNotIndexable jmpTarget:
+ 	(jumpIsContext jmpTarget:
+ 	(jumpBounds jmpTarget:
+ 	(jumpFmtGt11 jmpTarget:
+ 		cogit Label))))).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genPrimitiveIdenticalOrNotIf: (in category 'primitive generators') -----
+ genPrimitiveIdenticalOrNotIf: orNot
+ 	| jumpCmp |
+ 	<var: #jumpCmp type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpCmp := orNot
+ 					ifTrue: [cogit JumpZero: 0]
+ 					ifFalse: [cogit JumpNonZero: 0].
+ 	cogit genMoveTrueR: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpCmp jmpTarget: (cogit genMoveFalseR: ReceiverResultReg).
+ 	cogit genPrimReturn.
+ 	^UnfailingPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genPrimitiveIdentityHash (in category 'primitive generators') -----
+ genPrimitiveIdentityHash
+ 	| jumpSI |
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpSI jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genPrimitiveSize (in category 'primitive generators') -----
+ genPrimitiveSize
+ 	| jumpSI jumpNotIndexable jumpIsContext |
+ 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	<var: #jumpIsContext type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	jumpSI := self genJumpSmallInteger: ReceiverResultReg.
+ 	self
+ 		genGetSizeOf: ReceiverResultReg
+ 		into: ClassReg
+ 		formatReg: SendNumArgsReg
+ 		scratchReg: TempReg
+ 		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
+ 	self genConvertIntegerToSmallIntegerInReg: ClassReg.
+ 	cogit MoveR: ClassReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpSI jmpTarget: (jumpNotIndexable jmpTarget: (jumpIsContext jmpTarget: cogit Label)).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genPrimitiveStringAt (in category 'primitive generators') -----
+ genPrimitiveStringAt
+ 	| jumpNotSI jumpNotByteIndexable jumpBounds jumpShortHeader jumpSkip |
+ 	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpNotSI type: #'AbstractInstruction *'>
+ 	<var: #jumpNotByteIndexable type: #'AbstractInstruction *'>
+ 	<var: #jumpBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortHeader type: #'AbstractInstruction *'>
+ 	<var: #jumpSkip type: #'AbstractInstruction *'>
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpNotSI := self genJumpNotSmallInteger: Arg0Reg.
+ 	cogit
+ 		MoveMw: 0 r: ReceiverResultReg R: TempReg;	"self baseHeader: receiver"
+ 		MoveR: TempReg R: ClassReg;					"copy header word; we'll need it later"
+ 		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: TempReg;
+ 		AndCq: self instFormatFieldMask R: TempReg;	"self formatOfHeader: destReg"
+ 		MoveR: TempReg R: SendNumArgsReg;
+ 		AndCq: 3 R: SendNumArgsReg;					"get odd bytes from format (if it turns out to be bytes)"
+ 		SubR: SendNumArgsReg R: TempReg;
+ 		CmpCq: 8 R: TempReg.							"check format is 8"
+ 	jumpNotByteIndexable := cogit JumpNonZero: 0.
+ 	cogit
+ 		MoveR: ClassReg R: TempReg;
+ 		AndCq: TypeMask R: TempReg;
+ 		CmpCq: HeaderTypeSizeAndClass R: TempReg.	"(hdr bitAnd: TypeMask) = HeaderTypeSizeAndClass"
+ 	jumpShortHeader := cogit JumpNonZero: 0.
+ 	self assert: Size4Bit = 0.
+ 	cogit
+ 		MoveMw: 0 - (2 * objectMemory wordSize) r: ReceiverResultReg R: ClassReg; "(self sizeHeader: oop) bitAnd: LongSizeMask"
+ 		AndCq: LongSizeMask signedIntFromLong R: ClassReg.
+ 	jumpSkip :=  cogit Jump: 0.
+ 	jumpShortHeader jmpTarget: (cogit AndCq: SizeMask R: ClassReg).	"hdr bitAnd: SizeMask"
+ 	jumpSkip jmpTarget: (cogit SubCq: objectMemory baseHeaderSize R: ClassReg). "sz - BaseHeaderSize"
+ 	cogit SubR: SendNumArgsReg R: ClassReg. "sz - (fmt bitAnd: 3)"
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg.
+ 	cogit CmpR: ClassReg R: Arg1Reg.
+ 	jumpBounds := cogit JumpAboveOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
+ 	cogit genMoveConstant: objectMemory characterTable R: Arg0Reg.
+ 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
+ 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: ReceiverResultReg.
+ 	cogit MoveXwr: ReceiverResultReg R: Arg0Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpNotSI jmpTarget:
+ 	(jumpNotByteIndexable jmpTarget:
+ 	(jumpBounds jmpTarget:
+ 		cogit Label)).
+ 	^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a PrimitiveDescriptor struct."
  
  	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
+ 			value: (ivn = 'primitiveGenerator'
+ 					ifTrue: [#('sqInt (*' ')(void)')]
+ 					ifFalse: [#sqInt])]!
- 			value: (ivn caseOf: {
- 							['primitiveGenerator']	->	[#('sqInt (*' ')(void)')].
- 							['enabled']				->	[#('sqInt (*' ')(sqInt)')] }
- 						otherwise: [#sqInt])]!

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

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

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

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #directedSuperSendTrampolines
  			declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  		var: #selfSendTrampolines
  			declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #implicitReceiverSendTrampolines
  			declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  		var: #outerSendTrampolines
  			declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
- 								in: aCCodeGenerator);
- 			var: #primitiveGeneratorTable
- 				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
- 							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was removed:
- ----- Method: Cogit class>>table:from: (in category 'class initialization') -----
- table: primArray from: specArray 
- 	"Fill in the specified entries in the primitive table."
- 	specArray do:
- 		[:spec | 
- 		 (self shouldIncludeMethodForSelector: spec second) ifTrue:
- 			[(primArray at: spec first put: CogPrimitiveDescriptor new)
- 				primitiveGenerator: spec second;
- 				primNumArgs: (spec at: 3 ifAbsent: -1);
- 				enabled: (spec at: 4 ifAbsent: nil)]].
- 	primArray object withIndexDo:
- 		[:generator :i|
- 		generator ifNil:
- 			[(primArray object at: i put: CogPrimitiveDescriptor new)
- 				primNumArgs: -1]]!

Item was removed:
- ----- Method: Cogit>>compilePrimitive (in category 'compile abstract instructions') -----
- compilePrimitive
- 	"Compile a primitive.  If possible, performance-critical primtiives will
- 	 be generated by their own routines (primitiveGenerator).  Otherwise,
- 	 if there is a primitive at all, we call the C routine with the usual
- 	 stack-switching dance, test the primFailCode and then either return
- 	 on success or continue to the method body."
- 	<inline: false>
- 	| primitiveDescriptor primitiveRoutine |
- 	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
- 	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
- 	primitiveIndex = 0 ifTrue: [^0].
- 	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
- 	 for the generated code to be correct.  For example for speed many primitives use
- 	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
- 	 numArgs down the stack.  Use the interpreter version if not.  Likewise if it has an
- 	 enabled function that must answer true for the generated code to be correct."
- 	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
- 	 and: [primitiveDescriptor primitiveGenerator notNil
- 	 and: [(primitiveDescriptor primNumArgs < 0 "means don't care"
- 		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])
- 	 and: [primitiveDescriptor enabled isNil
- 		   or: [self perform: primitiveDescriptor enabled with: primitiveIndex]]]]) ifTrue:
- 		[^self perform: primitiveDescriptor primitiveGenerator].
- 	((primitiveRoutine := coInterpreter
- 							functionPointerForCompiledMethod: methodObj
- 							primitiveIndex: primitiveIndex) isNil "no primitive"
- 	or: [primitiveRoutine = (coInterpreter functionPointerFor: 0 inClass: nil) "routine = primitiveFail"]) ifTrue:
- 		[^self genFastPrimFail].
- 	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
- 	^self compileInterpreterPrimitive: primitiveRoutine!

Item was added:
+ ----- Method: Cogit>>mclassIsSmallInteger (in category 'initialization') -----
+ mclassIsSmallInteger
+ 	^(coInterpreter methodClassOf: methodObj) = objectMemory classSmallInteger!

Item was removed:
- ----- Method: Cogit>>mclassIsSmallInteger: (in category 'initialization') -----
- mclassIsSmallInteger: ignoredPrimIndex 
- 	^(coInterpreter methodClassOf: methodObj) = objectMemory classSmallInteger!

Item was added:
+ ----- Method: Cogit>>methodNumArgs (in category 'accessing') -----
+ methodNumArgs
+ 	^methodOrBlockNumArgs!

Item was removed:
- ----- Method: Cogit>>primitiveGeneratorOrNil (in category 'compile abstract instructions') -----
- primitiveGeneratorOrNil
- 	"If there is a generator for the current primitive then answer it;
- 	 otherwise answer nil."
- 	<returnTypeC: #'PrimitiveDescriptor *'>
- 	| primitiveDescriptor |
- 	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
- 	(coInterpreter isQuickPrimitiveIndex: primitiveIndex) ifTrue:
- 		[primitiveDescriptor := self addressOf: (primitiveGeneratorTable at: 0). "an unused one"
- 		 primitiveDescriptor primitiveGenerator: (coInterpreter quickPrimitiveGeneratorFor: primitiveIndex).
- 		 ^primitiveDescriptor].
- 	(primitiveIndex between: 1 and: MaxCompiledPrimitiveIndex) ifTrue:
- 		[^self addressOf: (primitiveGeneratorTable at: primitiveIndex)].
- 	^nil!

Item was removed:
- ----- Method: Cogit>>processorHasDivQuoRem: (in category 'initialization') -----
- processorHasDivQuoRem: ignoredPrimIndex 
- 	^backEnd canDivQuoRem!

Item was added:
+ ----- Method: Cogit>>processorHasDivQuoRemAndMClassIsSmallInteger (in category 'initialization') -----
+ processorHasDivQuoRemAndMClassIsSmallInteger
+ 	^backEnd canDivQuoRem and: [self mclassIsSmallInteger]!

Item was removed:
- ----- Method: Cogit>>processorHasDivQuoRemAndMClassIsSmallInteger: (in category 'initialization') -----
- processorHasDivQuoRemAndMClassIsSmallInteger: ignoredPrimIndex
- 	^(self processorHasDivQuoRem: ignoredPrimIndex)
- 	   and: [self mclassIsSmallInteger: ignoredPrimIndex]!

Item was added:
+ ----- Method: Cogit>>processorHasDoublePrecisionFloatingPointSupport (in category 'initialization') -----
+ processorHasDoublePrecisionFloatingPointSupport
+ 	<option: #DPFPReg0>
+ 	<inline: true>
+ 	^backEnd hasDoublePrecisionFloatingPointSupport!

Item was removed:
- ----- Method: Cogit>>processorHasDoublePrecisionFloatingPointSupport: (in category 'initialization') -----
- processorHasDoublePrecisionFloatingPointSupport: ignoredPrimIndex 
- 	^backEnd hasDoublePrecisionFloatingPointSupport!

Item was removed:
- ----- Method: Cogit>>processorHasMultiply: (in category 'initialization') -----
- processorHasMultiply: ignoredPrimIndex 
- 	^backEnd canMulRR!

Item was added:
+ ----- Method: Cogit>>processorHasMultiplyAndMClassIsSmallInteger (in category 'initialization') -----
+ processorHasMultiplyAndMClassIsSmallInteger
+ 	^backEnd canMulRR and: [self mclassIsSmallInteger]!

Item was removed:
- ----- Method: Cogit>>processorHasMultiplyAndMClassIsSmallInteger: (in category 'initialization') -----
- processorHasMultiplyAndMClassIsSmallInteger: ignoredPrimIndex
- 	^(self processorHasMultiply: ignoredPrimIndex)
- 	   and: [self mclassIsSmallInteger: ignoredPrimIndex]!

Item was changed:
  ----- Method: Cogit>>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>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
  	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
- 	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
  					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  					ifFalse: [0].
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	backEnd := CogCompilerClass for: self.
  	methodLabel := CogCompilerClass for: self.
  	(literalsManager := backEnd class literalsManagerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	extA := extB := 0.
  
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
  	debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].!

Item was removed:
- ----- Method: Cogit>>unimplementedPrimitive (in category 'accessing') -----
- unimplementedPrimitive
- 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>characterObjectOf: (in category 'accessing') -----
+ characterObjectOf: anInteger
+ 	^objectMemory characterObjectOf: anInteger!

Item was changed:
  Cogit subclass: #SimpleStackBasedCogit
+ 	instanceVariableNames: 'primitiveGeneratorTable primSetFunctionLabel primInvokeInstruction externalPrimCallOffsets externalPrimJumpOffsets externalSetPrimOffsets'
- 	instanceVariableNames: 'primSetFunctionLabel primInvokeInstruction externalPrimCallOffsets externalPrimJumpOffsets externalSetPrimOffsets'
  	classVariableNames: ''
  	poolDictionaries: 'VMMethodCacheConstants VMObjectIndices'
  	category: 'VMMaker-JIT'!
  
  !SimpleStackBasedCogit commentStamp: '<historical>' prior: 0!
  I am the stage one JIT for Cog that does not attempt to eliminate the stack via deferred code generation.!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
+ 
+ 	aCCodeGenerator vmClass primitiveGeneratorTable ifNotNil:
+ 		[:bytecodeGenTable|
+ 		aCCodeGenerator
+ 			var: #primitiveGeneratorTable
+ 				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+ 							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+ 								in: aCCodeGenerator)].
  	aCCodeGenerator
  		var: #externalPrimCallOffsets
  			declareC: 'sqInt externalPrimCallOffsets[MaxNumArgs + 1]';
  		var: #externalPrimJumpOffsets
  			declareC: 'sqInt externalPrimJumpOffsets[MaxNumArgs + 1]';
  		var: #externalSetPrimOffsets
  			declareC: 'sqInt externalSetPrimOffsets[MaxNumArgs + 1]';
  		var: #primSetFunctionLabel type: #'AbstractInstruction *';
  		var: #primInvokeInstruction type: #'AbstractInstruction *'!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForNewsqueak (in category 'class initialization') -----
  initializePrimitiveTableForNewsqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
+ 	"SimpleStackBasedCogit initializePrimitiveTableForNewsqueak"
- 	"SimpleStackBasedCogit initializePrimitiveTableForSqueakV3"
  	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
  										ifTrue: [555]
  										ifFalse: [222].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
+ 		(1 genPrimitiveAdd				1)
+ 		(2 genPrimitiveSubtract			1)
+ 		(3 genPrimitiveLessThan		1)
+ 		(4 genPrimitiveGreaterThan		1)
+ 		(5 genPrimitiveLessOrEqual		1)
+ 		(6 genPrimitiveGreaterOrEqual	1)
+ 		(7 genPrimitiveEqual			1)
+ 		(8 genPrimitiveNotEqual		1)
+ 		(9 genPrimitiveMultiply			1)
+ 		(10 genPrimitiveDivide			1)
+ 		(11 genPrimitiveMod			1)
+ 		(12 genPrimitiveDiv				1)
+ 		(13 genPrimitiveQuo			1)
+ 		(14 genPrimitiveBitAnd			1)
+ 		(15 genPrimitiveBitOr			1)
+ 		(16 genPrimitiveBitXor			1)
+ 		(17 genPrimitiveBitShift			1)
- 		(1 genPrimitiveAdd				1	mclassIsSmallInteger:)
- 		(2 genPrimitiveSubtract			1	mclassIsSmallInteger:)
- 		(3 genPrimitiveLessThan		1	mclassIsSmallInteger:)
- 		(4 genPrimitiveGreaterThan		1	mclassIsSmallInteger:)
- 		(5 genPrimitiveLessOrEqual		1	mclassIsSmallInteger:)
- 		(6 genPrimitiveGreaterOrEqual	1	mclassIsSmallInteger:)
- 		(7 genPrimitiveEqual			1	mclassIsSmallInteger:)
- 		(8 genPrimitiveNotEqual		1	mclassIsSmallInteger:)
- 		(9 genPrimitiveMultiply			1	processorHasMultiplyAndMClassIsSmallInteger:)
- 		(10 genPrimitiveDivide			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(11 genPrimitiveMod			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(12 genPrimitiveDiv				1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(13 genPrimitiveQuo			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(14 genPrimitiveBitAnd			1	mclassIsSmallInteger:)
- 		(15 genPrimitiveBitOr			1	mclassIsSmallInteger:)
- 		(16 genPrimitiveBitXor			1	mclassIsSmallInteger:)
- 		(17 genPrimitiveBitShift			1	mclassIsSmallInteger:)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
+ 		"(38 genPrimitiveFloatAt)"
+ 		"(39 genPrimitiveFloatAtPut)"
+ 		(40 genPrimitiveAsFloat					0)
+ 		(41 genPrimitiveFloatAdd				1)
+ 		(42 genPrimitiveFloatSubtract			1)
+ 		(43 genPrimitiveFloatLessThan			1)
+ 		(44 genPrimitiveFloatGreaterThan		1)
+ 		(45 genPrimitiveFloatLessOrEqual		1)
+ 		(46 genPrimitiveFloatGreaterOrEqual	1)
+ 		(47 genPrimitiveFloatEqual				1)
+ 		(48 genPrimitiveFloatNotEqual			1)
+ 		(49 genPrimitiveFloatMultiply			1)
+ 		(50 genPrimitiveFloatDivide				1)
+ 		"(51 genPrimitiveTruncated)"
+ 		"(52 genPrimitiveFractionalPart)"
+ 		"(53 genPrimitiveExponent)"
+ 		"(54 genPrimitiveTimesTwoPower)"
+ 		(55 genPrimitiveFloatSquareRoot		0)
+ 		"(56 genPrimitiveSine)"
+ 		"(57 genPrimitiveArctan)"
+ 		"(58 genPrimitiveLogN)"
+ 		"(59 genPrimitiveExp)"
- 		"(38 primitiveFloatAt)"
- 		"(39 primitiveFloatAtPut)"
- 		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
- 		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(51 primitiveTruncated)"
- 		"(52 primitiveFractionalPart)"
- 		"(53 primitiveExponent)"
- 		"(54 primitiveTimesTwoPower)"
- 		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(56 primitiveSine)"
- 		"(57 primitiveArctan)"
- 		"(58 primitiveLogN)"
- 		"(59 primitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew)				"For VMMirror support 1 argument instantiateFixedClass: as well as baiscNew"
  		(71 genPrimitiveNewWithArg)		"For VMMirror support 2 argument instantiateVariableClass:withSize: as well as baiscNew:"
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)			"For objectClass: and VMMirror support 1 argument classOf: as well as class"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)			"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveCharacterValue 0)	"Character>>value"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
+ 		(541 genPrimitiveSmallFloatAdd				1)
+ 		(542 genPrimitiveSmallFloatSubtract			1)
+ 		(543 genPrimitiveSmallFloatLessThan			1)
+ 		(544 genPrimitiveSmallFloatGreaterThan		1)
+ 		(545 genPrimitiveSmallFloatLessOrEqual		1)
+ 		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
+ 		(547 genPrimitiveSmallFloatEqual				1)
+ 		(548 genPrimitiveSmallFloatNotEqual			1)
+ 		(549 genPrimitiveSmallFloatMultiply				1)
+ 		(550 genPrimitiveSmallFloatDivide				1)
+ 		"(551 genPrimitiveSmallFloatTruncated			0)"
+ 		"(552 genPrimitiveSmallFloatFractionalPart		0)"
+ 		"(553 genPrimitiveSmallFloatExponent			0)"
+ 		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
+ 		(555 genPrimitiveSmallFloatSquareRoot			0)
+ 		"(556 genPrimitiveSmallFloatSine				0)"
+ 		"(557 genPrimitiveSmallFloatArctan				0)"
+ 		"(558 genPrimitiveSmallFloatLogN				0)"
+ 		"(559 genPrimitiveSmallFloatExp				0)"
- 		(541 genPrimitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(542 genPrimitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(543 genPrimitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(544 genPrimitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(545 genPrimitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(546 genPrimitiveSmallFloatGreaterOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(547 genPrimitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(548 genPrimitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(549 genPrimitiveSmallFloatMultiply				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(550 genPrimitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(551 genPrimitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(552 genPrimitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(553 genPrimitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(554 genPrimitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		(555 genPrimitiveSmallFloatSquareRoot			0	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(556 genPrimitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(557 genPrimitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(558 genPrimitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(559 genPrimitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
  	)!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak (in category 'class initialization') -----
  initializePrimitiveTableForSqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueak"
  	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
  										ifTrue: [555]
  										ifFalse: [222].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
+ 		(1 genPrimitiveAdd				1)
+ 		(2 genPrimitiveSubtract			1)
+ 		(3 genPrimitiveLessThan		1)
+ 		(4 genPrimitiveGreaterThan		1)
+ 		(5 genPrimitiveLessOrEqual		1)
+ 		(6 genPrimitiveGreaterOrEqual	1)
+ 		(7 genPrimitiveEqual			1)
+ 		(8 genPrimitiveNotEqual		1)
+ 		(9 genPrimitiveMultiply			1)
+ 		(10 genPrimitiveDivide			1)
+ 		(11 genPrimitiveMod			1)
+ 		(12 genPrimitiveDiv				1)
+ 		(13 genPrimitiveQuo			1)
+ 		(14 genPrimitiveBitAnd			1)
+ 		(15 genPrimitiveBitOr			1)
+ 		(16 genPrimitiveBitXor			1)
+ 		(17 genPrimitiveBitShift			1)
- 		(1 genPrimitiveAdd				1	mclassIsSmallInteger:)
- 		(2 genPrimitiveSubtract			1	mclassIsSmallInteger:)
- 		(3 genPrimitiveLessThan		1	mclassIsSmallInteger:)
- 		(4 genPrimitiveGreaterThan		1	mclassIsSmallInteger:)
- 		(5 genPrimitiveLessOrEqual		1	mclassIsSmallInteger:)
- 		(6 genPrimitiveGreaterOrEqual	1	mclassIsSmallInteger:)
- 		(7 genPrimitiveEqual			1	mclassIsSmallInteger:)
- 		(8 genPrimitiveNotEqual		1	mclassIsSmallInteger:)
- 		(9 genPrimitiveMultiply			1	processorHasMultiplyAndMClassIsSmallInteger:)
- 		(10 genPrimitiveDivide			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(11 genPrimitiveMod			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(12 genPrimitiveDiv				1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(13 genPrimitiveQuo			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
- 		(14 genPrimitiveBitAnd			1	mclassIsSmallInteger:)
- 		(15 genPrimitiveBitOr			1	mclassIsSmallInteger:)
- 		(16 genPrimitiveBitXor			1	mclassIsSmallInteger:)
- 		(17 genPrimitiveBitShift			1	mclassIsSmallInteger:)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 genPrimitiveFloatAt)"
  		"(39 genPrimitiveFloatAtPut)"
+ 		(40 genPrimitiveAsFloat					0)
+ 		(41 genPrimitiveFloatAdd				1)
+ 		(42 genPrimitiveFloatSubtract			1)
+ 		(43 genPrimitiveFloatLessThan			1)
+ 		(44 genPrimitiveFloatGreaterThan		1)
+ 		(45 genPrimitiveFloatLessOrEqual		1)
+ 		(46 genPrimitiveFloatGreaterOrEqual	1)
+ 		(47 genPrimitiveFloatEqual				1)
+ 		(48 genPrimitiveFloatNotEqual			1)
+ 		(49 genPrimitiveFloatMultiply			1)
+ 		(50 genPrimitiveFloatDivide				1)
- 		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
- 		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
  		"(51 genPrimitiveTruncated)"
  		"(52 genPrimitiveFractionalPart)"
  		"(53 genPrimitiveExponent)"
  		"(54 genPrimitiveTimesTwoPower)"
+ 		(55 genPrimitiveFloatSquareRoot		0)
- 		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
  		"(56 genPrimitiveSine)"
  		"(57 genPrimitiveArctan)"
  		"(58 genPrimitiveLogN)"
  		"(59 genPrimitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew			0)
  		(71 genPrimitiveNewWithArg	1)
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)				"Support both class and Context>>objectClass:"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)			"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveCharacterValue 0)	"Character>>value"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
+ 		(541 genPrimitiveSmallFloatAdd				1)
+ 		(542 genPrimitiveSmallFloatSubtract			1)
+ 		(543 genPrimitiveSmallFloatLessThan			1)
+ 		(544 genPrimitiveSmallFloatGreaterThan		1)
+ 		(545 genPrimitiveSmallFloatLessOrEqual		1)
+ 		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
+ 		(547 genPrimitiveSmallFloatEqual				1)
+ 		(548 genPrimitiveSmallFloatNotEqual			1)
+ 		(549 genPrimitiveSmallFloatMultiply				1)
+ 		(550 genPrimitiveSmallFloatDivide				1)
+ 		"(551 genPrimitiveSmallFloatTruncated			0)"
+ 		"(552 genPrimitiveSmallFloatFractionalPart		0)"
+ 		"(553 genPrimitiveSmallFloatExponent			0)"
+ 		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
+ 		(555 genPrimitiveSmallFloatSquareRoot			0)
+ 		"(556 genPrimitiveSmallFloatSine				0)"
+ 		"(557 genPrimitiveSmallFloatArctan				0)"
+ 		"(558 genPrimitiveSmallFloatLogN				0)"
+ 		"(559 genPrimitiveSmallFloatExp				0)"
- 		(541 genPrimitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(542 genPrimitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(543 genPrimitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(544 genPrimitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(545 genPrimitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(546 genPrimitiveSmallFloatGreaterOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(547 genPrimitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(548 genPrimitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(549 genPrimitiveSmallFloatMultiply				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		(550 genPrimitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(551 genPrimitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(552 genPrimitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(553 genPrimitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(554 genPrimitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		(555 genPrimitiveSmallFloatSquareRoot			0	processorHasDoublePrecisionFloatingPointSupport:)
- 		"(556 genPrimitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(557 genPrimitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(558 genPrimitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(559 genPrimitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
  	)!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>table:from: (in category 'class initialization') -----
+ table: primArray from: specArray 
+ 	"Fill in the specified entries in the primitive table."
+ 	specArray do:
+ 		[:spec | 
+ 		 (spec second == #genFastPrimFail
+ 		  or: [self objectRepresentationClass shouldIncludeMethodForSelector: spec second]) ifTrue:
+ 			[(primArray at: spec first put: CogPrimitiveDescriptor new)
+ 				primitiveGenerator: spec second;
+ 				primNumArgs: (spec at: 3 ifAbsent: -1)]].
+ 	primArray object withIndexDo:
+ 		[:generator :i|
+ 		generator ifNil:
+ 			[(primArray object at: i put: CogPrimitiveDescriptor new)
+ 				primNumArgs: -1]]!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>compileFallbackToInterpreterPrimitive: (in category 'primitive generators') -----
- compileFallbackToInterpreterPrimitive: code
- 	<inline: false>
- 	(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
- 		[^code].
- 	code = UnfailingPrimitive ifTrue:
- 		[^0].
- 	(code = CompletePrimitive
- 	 and: [(self methodUsesPrimitiveErrorCode) not]) ifTrue:
- 		[^0].
- 	^self compileInterpreterPrimitive: (coInterpreter
- 											functionPointerForCompiledMethod: methodObj
- 											primitiveIndex: primitiveIndex)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>compilePrimitive (in category 'primitive generators') -----
+ compilePrimitive
+ 	"Compile a primitive.  If possible, performance-critical primtiives will
+ 	 be generated by their own routines (primitiveGenerator).  Otherwise,
+ 	 if there is a primitive at all, we call the C routine with the usual
+ 	 stack-switching dance, test the primFailCode and then either return
+ 	 on success or continue to the method body."
+ 	<inline: false>
+ 	| code opcodeIndexAtPrimitive primitiveDescriptor primitiveRoutine |
+ 	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
+ 	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
+ 	primitiveIndex = 0 ifTrue: [^0].
+ 	code := 0.
+ 	"Note opcodeIndex so that compileFallbackToInterpreterPrimitive:
+ 	 can discard arg load instructions for unimplemented primitives."
+ 	opcodeIndexAtPrimitive := opcodeIndex.
+ 	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
+ 	 for the generated code to be correct.  For example for speed many primitives use
+ 	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
+ 	 numArgs down the stack.  Use the interpreter version if not."
+ 	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
+ 	 and: [primitiveDescriptor primitiveGenerator notNil
+ 	 and: [(primitiveDescriptor primNumArgs < 0 "means don't care"
+ 		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])]]) ifTrue:
+ 		[code := objectRepresentation perform: primitiveDescriptor primitiveGenerator].
+ 	(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
+ 		[^code].
+ 	code = UnfailingPrimitive ifTrue:
+ 		[^0].
+ 	(code = CompletePrimitive
+ 	 and: [(self methodUsesPrimitiveErrorCode) not]) ifTrue:
+ 		[^0].
+ 	"Discard any arg load code generated by the primitive generator."
+ 	code = UnimplementedPrimitive ifTrue:
+ 		[opcodeIndex := opcodeIndexAtPrimitive].
+ 	((primitiveRoutine := coInterpreter
+ 							functionPointerForCompiledMethod: methodObj
+ 							primitiveIndex: primitiveIndex) isNil "no primitive"
+ 	or: [primitiveRoutine = (coInterpreter functionPointerFor: 0 inClass: nil) "routine = primitiveFail"]) ifTrue:
+ 		[^self genFastPrimFail].
+ 	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
+ 	^self compileInterpreterPrimitive: primitiveRoutine!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>evaluateTrampolineCallBlock:protectLinkRegIfNot: (in category 'trampoline support') -----
+ evaluateTrampolineCallBlock: block protectLinkRegIfNot: inFrame
+ 	<inline: true>
+ 	inFrame 
+ 		ifFalse: 
+ 			[ backEnd saveAndRestoreLinkRegAround: [ block value ] ]
+ 		ifTrue:
+ 			[ block value ].!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
- genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
- 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp fail |
- 	<var: #jumpFailClass type: #'AbstractInstruction *'>
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
- 	<var: #doOp type: #'AbstractInstruction *'>
- 	<var: #fail type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: ClassReg.
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFailClass := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
- 	doOp := self Label.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
- 	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 					genAllocFloatValue: DPFPReg0
- 					into: SendNumArgsReg
- 					scratchReg: ClassReg
- 					scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: doOp.
- 	jumpFailAlloc jmpTarget: self Label.
- 	self compileFallbackToInterpreterPrimitive: 0.
- 	fail := self Label.
- 	jumpFailClass jmpTarget: fail.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck jmpTarget: fail].
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: fail].
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genDoubleComparison:invert: (in category 'primitive generators') -----
- genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
- 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #compare type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 
- 	self genLoadArgAtDepth: 0 into: ClassReg.
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: ClassReg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: compare.
- 	jumpFail jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genDoubleFailIfZeroArgRcvr:arg: (in category 'primitive generators') -----
  genDoubleFailIfZeroArgRcvr: rcvrReg arg: argReg
+ 	<option: #DPFPReg0>
  	<returnTypeC: #'AbstractInstruction *'>
  	self MoveCq: 0 R: TempReg.
  	self ConvertR: TempReg Rd: DPFPReg2.
  	self CmpRd: DPFPReg2 Rd: argReg.
  	^self JumpFPEqual: 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genFastPrimFail (in category 'primitive generators') -----
  genFastPrimFail
  	primitiveIndex := 0.
+ 	^UnfailingPrimitive!
- 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimReturn (in category 'primitive generators') -----
+ genPrimReturn
+ 	"Generate a return that cuts back the stack to remove the receiver
+ 	 and arguments after an invocation of a primitive with nargs arguments.
+ 	 This is similar to a Pascal calling convention."
+ 	<inline: true>
+ 	^self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveAdd (in category 'primitive generators') -----
- genPrimitiveAdd
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	self AddR: ClassReg R: TempReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveAsCharacter (in category 'primitive generators') -----
- genPrimitiveAsCharacter
- 	| na r |
- 	na := coInterpreter argumentCountOf: methodObj.
- 	na <= 1
- 		ifTrue:
- 			[na = 1 ifTrue:
- 				[self genLoadArgAtDepth: 0 into: Arg0Reg].
- 			 r := objectRepresentation
- 					genInnerPrimitiveAsCharacter: (self primRetNOffsetFor: na)
- 					inReg: (na = 0 ifTrue: [ReceiverResultReg] ifFalse: [Arg0Reg])]
- 		ifFalse: [r := 0].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveAsFloat (in category 'primitive generators') -----
- genPrimitiveAsFloat
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		return address"
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	self MoveR: ReceiverResultReg R: ClassReg.
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 					genAllocFloatValue: DPFPReg0
- 					into: SendNumArgsReg
- 					scratchReg: ClassReg
- 					scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 0).
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveAt (in category 'primitive generators') -----
- genPrimitiveAt
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveAt: (self primRetNOffsetFor: 1))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveAtPut (in category 'primitive generators') -----
- genPrimitiveAtPut
- 	| savedIndex r |
- 	savedIndex := opcodeIndex.
- 	self genLoadArgAtDepth: 1 into: Arg0Reg.
- 	self genLoadArgAtDepth: 0 into: Arg1Reg.
- 	r := objectRepresentation genInnerPrimitiveAtPut: (self primRetNOffsetFor: 2).
- 	"If primitive is unimplemented, discard arg load."
- 	r = UnimplementedPrimitive ifTrue:
- 		[opcodeIndex := savedIndex].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveBitAnd (in category 'primitive generators') -----
- genPrimitiveBitAnd
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	"Whether the SmallInteger tags are zero or non-zero, anding them together will preserve them."
- 	self AndR: ClassReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveBitOr (in category 'primitive generators') -----
- genPrimitiveBitOr
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	"Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them."
- 	self OrR: ClassReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveBitShift (in category 'primitive generators') -----
- genPrimitiveBitShift
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address
- 
- 	rTemp := ArgOffset(SP)
- 	rClass := tTemp
- 	rTemp := rTemp & 1
- 	jz nonInt
- 	rClass >>= 1
- 	cmp 0,rClass
- 	jge neg
- 	cmp 31,rClass // numSmallIntegerBits, jge for sign
- 	jge tooBig
- 	rTemp := rReceiver
- 	rTemp <<= rClass
- 	rTemp >>= rClass (arithmetic)
- 	cmp rTemp,rReceiver
- 	jnz ovfl
- 	rReceiver := rReceiver - 1
- 	rReceiver := rReceiver <<= rClass
- 	rReceiver := rReceiver + 1
- 	ret
- neg:
- 	rClass := 0 - rClass
- 	cmp 31,rClass
- 	jge inRange
- 	rClass := 31
- inRange
- 	rReceiver := rReceiver >>= rClass.
- 	rReceiver := rReceiver | 1.
- 	ret
- ovfl
- tooBig
- nonInt:
- 	fail"
- 	| jumpNotSI jumpOvfl jumpNegative jumpTooBig jumpInRange |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	<var: #jumpNegative type: #'AbstractInstruction *'>
- 	<var: #jumpTooBig type: #'AbstractInstruction *'>
- 	<var: #jumpInRange type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
- 		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
- 	jumpNegative := self JumpNegative: 0.
- 	self CmpCq: objectRepresentation numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - 31"
- 	jumpTooBig := self JumpGreaterOrEqual: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	self LogicalShiftLeftR: ClassReg R: TempReg.
- 	self ArithmeticShiftRightR: ClassReg R: TempReg.
- 	self CmpR: TempReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - TempReg"
- 	jumpOvfl := self JumpNonZero: 0.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
- 	self LogicalShiftLeftR: ClassReg R: ReceiverResultReg.
- 	objectRepresentation genAddSmallIntegerTagsTo: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpNegative jmpTarget: (self NegateR: ClassReg).
- 	self CmpCq: objectRepresentation numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - 31"
- 	jumpInRange := self JumpLessOrEqual: 0.
- 	self MoveCq: objectRepresentation numSmallIntegerBits R: ClassReg.
- 	jumpInRange jmpTarget: (self ArithmeticShiftRightR: ClassReg R: ReceiverResultReg).
- 	objectRepresentation genClearAndSetSmallIntegerTagsIn: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpNotSI jmpTarget: (jumpTooBig jmpTarget: (jumpOvfl jmpTarget: self Label)).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveBitXor (in category 'primitive generators') -----
- genPrimitiveBitXor
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into:TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	"Clear one or the other tag so that xoring will preserve them."
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
- 	self XorR: ClassReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveCharacterValue (in category 'primitive generators') -----
- genPrimitiveCharacterValue
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveCharacterValue: (self primRetNOffsetFor: 0))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveClass (in category 'primitive generators') -----
- genPrimitiveClass
- 	methodOrBlockNumArgs > 0 ifTrue:
- 		[methodOrBlockNumArgs > 1 ifTrue:
- 			[^self compileFallbackToInterpreterPrimitive: 0].
- 		 self genLoadArgAtDepth: 0 into: ReceiverResultReg].
- 	(objectRepresentation
- 			genGetClassObjectOf: ReceiverResultReg
- 			into: ReceiverResultReg
- 			scratchReg: TempReg
- 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true])) = BadRegisterSet ifTrue:
- 		[objectRepresentation
- 			genGetClassObjectOf: ReceiverResultReg
- 			into: ClassReg
- 			scratchReg: TempReg
- 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true]).
- 		 self MoveR: ClassReg R: ReceiverResultReg].
- 	self RetN: (self primRetNOffsetFor: methodOrBlockNumArgs).
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveClosureValue (in category 'primitive generators') -----
  genPrimitiveClosureValue
  	"Check the argument count.  Fail if wrong.
  	 Get the method from the outerContext and see if it is cogged.  If so, jump to the
  	 block entry or the no-context-switch entry, as appropriate, and we're done.  If not,
  	 invoke the interpreter primitive."
  	| jumpFailNArgs jumpFail1 jumpFail2 jumpFail3 jumpFail4 jumpBCMethod primitiveRoutine result |
  	<var: #jumpFail1 type: #'AbstractInstruction *'>
  	<var: #jumpFail2 type: #'AbstractInstruction *'>
  	<var: #jumpFail3 type: #'AbstractInstruction *'>
  	<var: #jumpFail4 type: #'AbstractInstruction *'>
  	<var: #jumpFailNArgs type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)()'>
  	objectRepresentation genLoadSlot: ClosureNumArgsIndex sourceReg: ReceiverResultReg destReg: TempReg.
  	self CmpCq: (objectMemory integerObjectOf: methodOrBlockNumArgs) R: TempReg.
  	jumpFailNArgs := self JumpNonZero: 0.
  	objectRepresentation genLoadSlot: ClosureOuterContextIndex sourceReg: ReceiverResultReg destReg: ClassReg.
  	jumpFail1 := objectRepresentation genJumpImmediate: ClassReg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: TempReg.
  	objectRepresentation genCmpClassMethodContextCompactIndexR: TempReg.
  	jumpFail2 := self JumpNonZero: 0.
  	"We defer unforwarding the receiver to the prologue; scanning blocks
  	 for inst var refs and only unforwarding if the block refers to inst vars."
  	(false
  	 and: [objectRepresentation hasSpurMemoryManagerAPI]) ifTrue:
  		[objectRepresentation
  			genLoadSlot: ReceiverIndex sourceReg: ClassReg destReg: SendNumArgsReg;
  			genEnsureOopInRegNotForwarded: SendNumArgsReg
  			scratchReg: TempReg
  			updatingSlot: ReceiverIndex
  			in: ClassReg].
  	objectRepresentation genLoadSlot: MethodIndex sourceReg: ClassReg destReg: SendNumArgsReg.
  	jumpFail3 := objectRepresentation genJumpImmediate: SendNumArgsReg.
  	objectRepresentation genGetFormatOf: SendNumArgsReg into: TempReg.
  	self CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
  	jumpFail4 := self JumpLess: 0.
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpImmediate: ClassReg.
  	self MoveM16: (self offset: CogMethod of: #blockEntryOffset) r: ClassReg R: TempReg.
  	self AddR: ClassReg R: TempReg.
  	primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex.
  	primitiveRoutine = #primitiveClosureValueNoContextSwitch ifTrue:
  		[blockNoContextSwitchOffset = nil ifTrue:
  			[^NotFullyInitialized].
  		 self SubCq: blockNoContextSwitchOffset R: TempReg].
  	self JumpR: TempReg.
  	jumpBCMethod jmpTarget: (jumpFail1 jmpTarget: (jumpFail2 jmpTarget: (jumpFail3 jmpTarget: (jumpFail4 jmpTarget: self Label)))).
  	(result := self compileInterpreterPrimitive: primitiveRoutine) < 0 ifTrue:
  		[^result].
  	jumpFailNArgs jmpTarget: self Label.
+ 	^CompletePrimitive!
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveDiv (in category 'primitive generators') -----
- genPrimitiveDiv
- 	| jumpNotSI jumpIsSI jumpZero jumpExact jumpSameSign convert |
- 	<var: #convert type: #'AbstractInstruction *'>
- 	<var: #jumpIsSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	<var: #jumpSameSign type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	self MoveR: TempReg R: Arg1Reg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: ClassReg].
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we must check for overflow."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	"If arg and remainder signs are different we must round down."
- 	self XorR: ClassReg R: Arg1Reg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: Arg1Reg].
- 	jumpSameSign := self JumpGreaterOrEqual: 0.
- 	self SubCq: 1 R: TempReg.
- 	jumpSameSign jmpTarget: (convert := self Label).
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	"test for overflow; the only case is SmallInteger minVal // -1"
- 	jumpExact jmpTarget: self Label.
- 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	jumpIsSI jmpTarget: convert.
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveDivide (in category 'primitive generators') -----
- genPrimitiveDivide
- 	| jumpNotSI jumpZero jumpInexact jumpOverflow |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpInexact type: #'AbstractInstruction *'>
- 	<var: #jumpOverflow type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is non-zero fail."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpInexact := self JumpNonZero: 0.
- 	"test for overflow; the only case is SmallInteger minVal / -1"
- 	jumpOverflow := objectRepresentation genJumpNotSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpOverflow jmpTarget: (jumpInexact jmpTarget: (jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label))).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveEqual (in category 'primitive generators') -----
- genPrimitiveEqual
- 	^self genSmallIntegerComparison: JumpZero
- 		orDoubleComparison: #JumpFPEqual:
- 		invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatAdd (in category 'primitive generators') -----
- genPrimitiveFloatAdd
- 	^self genDoubleArithmetic: AddRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatDivide (in category 'primitive generators') -----
- genPrimitiveFloatDivide
- 	^self genDoubleArithmetic: DivRdRd preOpCheck: #genDoubleFailIfZeroArgRcvr:arg:!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatEqual (in category 'primitive generators') -----
- genPrimitiveFloatEqual
- 	^self genDoubleComparison: #JumpFPEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatGreaterOrEqual (in category 'primitive generators') -----
- genPrimitiveFloatGreaterOrEqual
- 	^self genDoubleComparison: #JumpFPGreaterOrEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatGreaterThan (in category 'primitive generators') -----
- genPrimitiveFloatGreaterThan
- 	^self genDoubleComparison: #JumpFPGreater: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatLessOrEqual (in category 'primitive generators') -----
- genPrimitiveFloatLessOrEqual
- 	^self genDoubleComparison: #JumpFPGreaterOrEqual: invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatLessThan (in category 'primitive generators') -----
- genPrimitiveFloatLessThan
- 	^self genDoubleComparison: #JumpFPGreater: invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatMultiply (in category 'primitive generators') -----
- genPrimitiveFloatMultiply
- 	^self genDoubleArithmetic: MulRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatNotEqual (in category 'primitive generators') -----
- genPrimitiveFloatNotEqual
- 	^self genDoubleComparison: #JumpFPNotEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
- genPrimitiveFloatSquareRoot
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		return address"
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	self SqrtRd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 					genAllocFloatValue: DPFPReg0
- 					into: SendNumArgsReg
- 					scratchReg: ClassReg
- 					scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 0).
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveFloatSubtract (in category 'primitive generators') -----
- genPrimitiveFloatSubtract
- 	^self genDoubleArithmetic: SubRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveGreaterOrEqual (in category 'primitive generators') -----
- genPrimitiveGreaterOrEqual
- 	^self genSmallIntegerComparison: JumpGreaterOrEqual
- 		orDoubleComparison: #JumpFPGreaterOrEqual:
- 		invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveGreaterThan (in category 'primitive generators') -----
- genPrimitiveGreaterThan
- 	^self genSmallIntegerComparison: JumpGreater
- 		orDoubleComparison: #JumpFPGreater:
- 		invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveIdentical (in category 'primitive generators') -----
- genPrimitiveIdentical
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	^objectRepresentation
- 		genInnerPrimitiveIdentical: (self primRetNOffsetFor: 1)
- 		orNotIf: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
- genPrimitiveIdentityHash
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveIdentityHash: (self primRetNOffsetFor: 0))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveLessOrEqual (in category 'primitive generators') -----
- genPrimitiveLessOrEqual
- 	^self
- 		genSmallIntegerComparison: JumpLessOrEqual
- 		orDoubleComparison: #JumpFPGreaterOrEqual:
- 		invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveLessThan (in category 'primitive generators') -----
- genPrimitiveLessThan
- 	^self
- 		genSmallIntegerComparison: JumpLess
- 		orDoubleComparison: #JumpFPGreater:
- 		invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveMod (in category 'primitive generators') -----
- genPrimitiveMod
- 	| jumpNotSI jumpZero jumpExact jumpSameSign |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	<var: #jumpSameSign type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ClassReg R: Arg1Reg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we're done."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	"If arg and remainder signs are different we must reflect around zero."
- 	self XorR: ClassReg R: Arg1Reg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: Arg1Reg].
- 	jumpSameSign := self JumpGreaterOrEqual: 0.
- 	self XorR: ClassReg R: Arg1Reg.
- 	self AddR: Arg1Reg R: ClassReg.
- 	jumpSameSign jmpTarget: (jumpExact jmpTarget: self Label).
- 	objectRepresentation genSetSmallIntegerTagsIn: ClassReg.
- 	self MoveR: ClassReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveMultiply (in category 'primitive generators') -----
- genPrimitiveMultiply
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: TempReg.
- 	self MulR: TempReg R: ClassReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	objectRepresentation genSetSmallIntegerTagsIn: ClassReg.
- 	self MoveR: ClassReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveNew (in category 'primitive generators') -----
- genPrimitiveNew
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveNew: (self primRetNOffsetFor: 0))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveNewMethod (in category 'primitive generators') -----
- genPrimitiveNewMethod
- 	| r savedIndex |
- 	savedIndex := opcodeIndex.
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	r := objectRepresentation genInnerPrimitiveNewMethod: (self primRetNOffsetFor: 2).
- 	"If primitive is unimplemented, discard arg load."
- 	r = UnimplementedPrimitive ifTrue:
- 		[opcodeIndex := savedIndex].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveNewWithArg (in category 'primitive generators') -----
- genPrimitiveNewWithArg
- 	| savedIndex r |
- 	savedIndex := opcodeIndex.
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	r := objectRepresentation genInnerPrimitiveNewWithArg: (self primRetNOffsetFor: 1).
- 	"If primitive is unimplemented, discard arg load."
- 	r = UnimplementedPrimitive ifTrue:
- 		[opcodeIndex := savedIndex].
- 	"Call the interpreter primitive either when the machine-code primitive
- 	 fails, or if the machine-code primitive is unimplemented."
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveNotEqual (in category 'primitive generators') -----
- genPrimitiveNotEqual
- 	^self genSmallIntegerComparison: JumpNonZero
- 		orDoubleComparison: #JumpFPNotEqual:
- 		invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveNotIdentical (in category 'primitive generators') -----
- genPrimitiveNotIdentical
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	^objectRepresentation
- 		genInnerPrimitiveIdentical: (self primRetNOffsetFor: 1)
- 		orNotIf: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveObjectAt (in category 'primitive generators') -----
- genPrimitiveObjectAt
- 	| savedIndex r |
- 	savedIndex := opcodeIndex.
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	r := objectRepresentation genInnerPrimitiveObjectAt: (self primRetNOffsetFor: 1).
- 	"If primitive is unimplemented, discard arg load."
- 	r = UnimplementedPrimitive ifTrue:
- 		[opcodeIndex := savedIndex].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitivePerform (in category 'primitive generators') -----
  genPrimitivePerform
  	"Generate an in-line perform primitive.  The lookup code requires the selector to be in Arg0Reg.
  	 adjustArgumentsForPerform: adjusts the arguments once genLookupForPerformNumArgs:
  	 has generated the code for the lookup."
+ 	self MoveMw: (backEnd hasLinkRegister
+ 					ifTrue: [methodOrBlockNumArgs - 1]
+ 					ifFalse: [methodOrBlockNumArgs]) * objectMemory wordSize
+ 		r: SPReg
+ 		R: Arg0Reg.
+ 	^self genLookupForPerformNumArgs: methodOrBlockNumArgs!
- 	self MoveMw: methodOrBlockNumArgs - 1 * objectMemory wordSize r: SPReg R: Arg0Reg.
- 	self genLookupForPerformNumArgs: methodOrBlockNumArgs.
- 	^self compileInterpreterPrimitive: (coInterpreter
- 										functionPointerForCompiledMethod: methodObj
- 										primitiveIndex: primitiveIndex)!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveQuo (in category 'primitive generators') -----
- genPrimitiveQuo
- 	| convert jumpNotSI jumpZero jumpIsSI jumpExact |
- 	<var: #convert type: #'AbstractInstruction *'>
- 	<var: #jumpIsSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: ClassReg].
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we must check for overflow."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	convert := self Label.
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpExact jmpTarget: self Label.
- 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	jumpIsSI jmpTarget: convert.
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSize (in category 'primitive generators') -----
- genPrimitiveSize
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveSize: (self primRetNOffsetFor: 0))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatAdd (in category 'primitive generators') -----
- genPrimitiveSmallFloatAdd
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatArithmetic: AddRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatDivide (in category 'primitive generators') -----
- genPrimitiveSmallFloatDivide
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatArithmetic: DivRdRd preOpCheck: #genDoubleFailIfZeroArgRcvr:arg:!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatEqual (in category 'primitive generators') -----
- genPrimitiveSmallFloatEqual
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatGreaterOrEqual (in category 'primitive generators') -----
- genPrimitiveSmallFloatGreaterOrEqual
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatGreaterThan (in category 'primitive generators') -----
- genPrimitiveSmallFloatGreaterThan
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPGreater: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatLessOrEqual (in category 'primitive generators') -----
- genPrimitiveSmallFloatLessOrEqual
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatLessThan (in category 'primitive generators') -----
- genPrimitiveSmallFloatLessThan
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPGreater: invert: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatMultiply (in category 'primitive generators') -----
- genPrimitiveSmallFloatMultiply
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatArithmetic: MulRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatNotEqual (in category 'primitive generators') -----
- genPrimitiveSmallFloatNotEqual
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatComparison: #JumpFPNotEqual: invert: false!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
- genPrimitiveSmallFloatSquareRoot
- 	<option: #Spur64BitMemoryManager>
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		return address"
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	self SqrtRd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 					genAllocFloatValue: DPFPReg0
- 					into: SendNumArgsReg
- 					scratchReg: ClassReg
- 					scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 0).
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatSubtract (in category 'primitive generators') -----
- genPrimitiveSmallFloatSubtract
- 	<option: #Spur64BitMemoryManager>
- 	^self genSmallFloatArithmetic: SubRdRd preOpCheck: nil!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveStringAt (in category 'primitive generators') -----
- genPrimitiveStringAt
- 	self genLoadArgAtDepth: 0 into: Arg0Reg.
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveStringAt: (self primRetNOffsetFor: 1))!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveStringAtPut (in category 'primitive generators') -----
- genPrimitiveStringAtPut
- 	| savedIndex r |
- 	savedIndex := opcodeIndex.
- 	self genLoadArgAtDepth: 1 into: Arg0Reg.
- 	self genLoadArgAtDepth: 0 into: Arg1Reg.
- 	r := objectRepresentation genInnerPrimitiveStringAtPut: (self primRetNOffsetFor: 2).
- 	"If primitive is unimplemented, discard arg load."
- 	r = UnimplementedPrimitive ifTrue:
- 		[opcodeIndex := savedIndex].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPrimitiveSubtract (in category 'primitive generators') -----
- genPrimitiveSubtract
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	self SubR: ClassReg R: TempReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	objectRepresentation genAddSmallIntegerTagsTo: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genQuickReturnConst (in category 'primitive generators') -----
  genQuickReturnConst
  	<api> "because selected by CoInterpreter>>quickPrimitiveGeneratorFor:"
  	| constant |
  	constant := coInterpreter quickPrimitiveConstantFor: primitiveIndex.
  	self annotate:
  			((objectRepresentation isImmediate: constant)
  				ifTrue: [self MoveCq: constant R: ReceiverResultReg]
  				ifFalse: [self MoveCw: constant R: ReceiverResultReg])
  		objRef: constant.
+ 	self genUpArrowReturn.
+ 	^UnfailingPrimitive!
- 	^self genUpArrowReturn!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genQuickReturnInstVar (in category 'primitive generators') -----
  genQuickReturnInstVar
  	<api> "because selected by CoInterpreter>>quickPrimitiveGeneratorFor:"
  	| index |
  	index := coInterpreter quickPrimitiveInstVarIndexFor: primitiveIndex.
  	objectRepresentation genLoadSlot: index sourceReg: ReceiverResultReg destReg: ReceiverResultReg.
+ 	self genUpArrowReturn.
+ 	^UnfailingPrimitive!
- 	^self genUpArrowReturn!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genQuickReturnSelf (in category 'primitive generators') -----
  genQuickReturnSelf
  	<api> "because selected by CoInterpreter>>quickPrimitiveGeneratorFor:"
+ 	self genUpArrowReturn.
+ 	^UnfailingPrimitive!
- 	^self genUpArrowReturn!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genSmallFloatArithmetic:preOpCheck: (in category 'primitive generators') -----
- genSmallFloatArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
- 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp fail |
- 	<var: #jumpFailClass type: #'AbstractInstruction *'>
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
- 	<var: #doOp type: #'AbstractInstruction *'>
- 	<var: #fail type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: ClassReg.
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFailClass := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
- 	doOp := self Label.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
- 	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 					genAllocFloatValue: DPFPReg0
- 					into: SendNumArgsReg
- 					scratchReg: ClassReg
- 					scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: doOp.
- 	jumpFailAlloc jmpTarget: self Label.
- 	self compileFallbackToInterpreterPrimitive: 0.
- 	fail := self Label.
- 	jumpFailClass jmpTarget: fail.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck jmpTarget: fail].
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: fail].
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
- genSmallFloatComparison: jumpOpcodeGenerator invert: invertComparison
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
- 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #compare type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 
- 	self genLoadArgAtDepth: 0 into: ClassReg.
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: ClassReg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: compare.
- 	jumpFail jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genSmallIntegerComparison: (in category 'primitive generators') -----
- genSmallIntegerComparison: jumpOpcode
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	| jumpFail jumpTrue |
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	<var: #jumpTrue type: #'AbstractInstruction *'>
- 	self genLoadArgAtDepth: 0 into: TempReg.
- 	self MoveR: TempReg R: ClassReg.
- 	jumpFail := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
- 	self CmpR: ClassReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - ClassReg"
- 	jumpTrue := self gen: jumpOpcode.
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpFail jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genSmallIntegerComparison:orDoubleComparison:invert: (in category 'primitive generators') -----
- genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator invert: invertComparison
- 	"Stack looks like
- 		receiver (also in ResultReceiverReg)
- 		arg
- 		return address"
- 	| jumpDouble jumpNonInt jumpFail jumpTrue jumpCond |
- 	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction *(*jumpFPOpcodeGenerator)(void *)'>
- 	<var: #jumpDouble type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #jumpTrue type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	backEnd hasDoublePrecisionFloatingPointSupport ifFalse:
- 		[^self genSmallIntegerComparison: jumpOpcode].
- 	self genLoadArgAtDepth: 0 into: ClassReg.
- 	jumpDouble := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg.
- 	self CmpR: ClassReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - ClassReg"
- 	jumpTrue := self gen: jumpOpcode.
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: (self primRetNOffsetFor: 1).
- 	
- 	"Argument may be a Float : let us check or fail"
- 	jumpDouble jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpImmediate: ClassReg].
- 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 
- 	"It was a Float, so convert the receiver to double and perform the operation"
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: TempReg.
- 	self ConvertR: TempReg Rd: DPFPReg0.
- 	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: (self primRetNOffsetFor: 1).
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: (self primRetNOffsetFor: 1).
- 
- 	objectRepresentation smallIntegerIsOnlyImmediateType
- 		ifTrue: [jumpFail jmpTarget: self Label]
- 		ifFalse: [jumpNonInt jmpTarget: (jumpFail jmpTarget: self Label)].
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>primRetNOffsetFor: (in category 'primitive generators') -----
- primRetNOffsetFor: nargs
- 	"Answer how many bytes to cut back the stack to remove the receiver
- 	 and arguments after an invocation of a primitive with nargs arguments. "
- 	^nargs + 1 * objectMemory wordSize!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>primitiveGeneratorOrNil (in category 'primitive generators') -----
+ primitiveGeneratorOrNil
+ 	"If there is a generator for the current primitive then answer it;
+ 	 otherwise answer nil."
+ 	<returnTypeC: #'PrimitiveDescriptor *'>
+ 	| primitiveDescriptor |
+ 	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
+ 	(coInterpreter isQuickPrimitiveIndex: primitiveIndex) ifTrue:
+ 		[primitiveDescriptor := self addressOf: (primitiveGeneratorTable at: 0). "an unused one"
+ 		 primitiveDescriptor primitiveGenerator: (coInterpreter quickPrimitiveGeneratorFor: primitiveIndex).
+ 		 ^primitiveDescriptor].
+ 	(primitiveIndex between: 1 and: MaxCompiledPrimitiveIndex) ifTrue:
+ 		[^self addressOf: (primitiveGeneratorTable at: primitiveIndex)].
+ 	^nil!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>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.
+ 	primitiveGeneratorTable := self class primitiveTable.
  	externalPrimJumpOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1).
  	externalPrimCallOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1).
  	externalSetPrimOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1)!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>callingConvention (in category 'documentation') -----
  callingConvention
  	"The Smalltalk-to-Smalltalk calling convention aims to trade simplicity of compilation against
  	 effectiveness of optimization.  Most Smalltalk methods, and certainly most performance-
  	 critical primitives have two or less arguments.  So arranging that the receiver and up to two
+ 	 args are in registers means that performance-critical primitives can access their arguments
+ 	 in registers.  So if the argument count is <= numRegArgs nothing is passed on the stack and
+ 	 everything is passed in ReceiverResultReg, Arg0Reg et al.  Above numRegArgs everything is
+ 	 passed on the stack.
- 	 args args are in registers arranges that performance-critical primitives can access their
- 	 arguments in registers.  So if the argument count is <= numRegArgs nothing is passed on
- 	 the stack and everything is passed in ReceiverResultReg, Arg0Reg et al.  Above numRegArgs
- 	 everything is passed on the stack.
  
  	 To save the CoInterpreter from change we shuffle the retpc and push the register args in
  	 the prolog so that the frame format is unchanged by register args.  Also, the trampolines for
  	 unlinked sends do the same, as does the code preceding an interpreter primitive.  It turns
  	 out that this protocol is faster than always pushing arguments.  Comparing benchFib with the
  	 shuffling protocol against an always-push protocol on a 2.66 GHz Core i7 (MacBook Pro) , the
  	 shuffling protocol is 6.3% faster than the always push protocol.
  
  	 Not shuffling the stack and pushing register arguments after frame build is faster yet again,
  	 5.8% faster that the stack shuffle.  So it might be worth-while to change the CoInterpreter's
  	 frame management to allow numArgs <= numRegArgs frames to push receiver and arguments
  	 after saving the return pc.  This implies changes in stack-to-context mapping, GC,
  	 interpreter-to-machine code frame conversion and no doubt else where.
  
  	 Hence the calling convention is
  
+ 		- if the number of arguments is less than or equal to numRegArgs then the receiver and
+ 		  arguments are passed in registers.  numRegArgs is 1 for V3, and 2 for Spur.  The receiver
+ 		  is passed in ReceiverResultReg, the first argument in Arg0Reg (esi on x86) and the second
+ 		  argument (if numRegArgs = 2) in Arg1Reg (edi on x86).
- 		- if the number of arguments is less than or equal to numRegArgs then the receiver and arguments
- 		  are passed in registers.  numRegArgs is currently 1, but will become 2 once the code generator
- 		  generates machine code primitives which take 2 arguments (i.e. once the object representation
- 		  makes it feasible to implement at:put: in machine code numRegArgs will be raised to 2).  The receiver
- 		  is passed in ReceiverResultReg, the first argument in Arg0Reg (esi on x86) and the second argument
- 		  (if numRegArgs = 2) in Arg1Reg (edi on x86).
  
+ 		- if the number of arguments is greater than numRegArgs then the calling convention is as
+ 		  for SimpleStackBasedCogIt; ReceiverResultReg contains the receiver, and the receiver and
+ 		  arguments are all on the stack, receiver furthest from top-of-stack.  If the argument count
+ 		  is > 2 then argument count is passed in SendNumArgsReg (for the benefit of the run-time
+ 		  linking routines; it is ignored in linked sends).
- 		- if the number of arguments is greater than numRegArgs then the calling convention is as for
- 		  SimpleStackBasedCogIt; ReceiverResultReg contains the receiver, and the receiver and arguments
- 		  are all on the stack, receiver furthest from top-of-stack.  If the argument count is > 2 then argument
- 		  count is passed in SendNumArgsReg (for the benefit of the run-time linking routines; it is ignored in
- 		  linked sends).
  
+ 		On return the result is in ReceiverResultReg.  The callee removes arguments from the stack
+ 		(Pascal convention).
- 		On return the result is in ReceiverResultReg.  The callee removes arguments from the stack.
  
+ 		Note that if a machine code method contains a call to an interpreter primitive it will push any
+ 		register arguments (and if on a RISC, the return pc from the LinReg) on the stack before calling
+ 		the primitive so that to the primitive the stack looks the same as it does in the interpreter.
- 		Note that if a machine code method contains a call to an interpreter primitive it will push any register
- 		arguments on the stack before calling the primitive so that to the primitive the stack looks the same
- 		as it does in the interpreter.
  
+ 		Within all machine code primitives except genPrimitiveClosureValue and genPrimitivePerform all
+ 		arguments are taken from registers since no machine code primitive has more than numRegArgs
+ 		arguments.  genPrimitiveClosureValue pushes its register arguments immedately only for laziness
+ 		to be able to reuse SimpleStackBasedCogit's code.  genPrimitivePerform adjusts its arguments
+ 		as required by special-purpose code.
- 		Within all machine code primitives except primitiveClosureValue all arguments are taken form registers
- 	 	since no machine code primitiver has more than numRegArgs arguments.  primitiveClosureValue pushes
- 		its register arguments immedately only for laziness to be able to reuse SimpleStackBasedCogit's code.
  
+ 		Within machine code methods with interpreter primitives the register arguments are pushed
+ 		before calling the interpreter primitive.  In normal methods and if not already done so in primitive
+ 		code, the register arguments are pushed during frame build.  If a method is compiled frameless
+ 		it will access its arguments in registers."!
- 		Within machine code methods with interpreter primtiives the register arguments are pushed before calling
- 		the interpreter primitive.  In normal methods and if not already done so in [primitive code, the register
- 		arguments are pushed during frame build.  If a method is compiled frameless it will access its arguments
- 		 in registers."!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>evaluateTrampolineCallBlock:protectLinkRegIfNot: (in category 'trampoline support') -----
- evaluateTrampolineCallBlock: block protectLinkRegIfNot: inFrame
- 	<inline: true>
- 	inFrame 
- 		ifFalse: 
- 			[ backEnd saveAndRestoreLinkRegAround: [ block value ] ]
- 		ifTrue:
- 			[ block value ].!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
- genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
- 	| jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
- 	<var: #jumpFailClass type: #'AbstractInstruction *'>
- 	<var: #jumpFailClass2 type: #'AbstractInstruction *'>
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
- 	<var: #doOp type: #'AbstractInstruction *'>
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFailClass := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
- 	doOp := self Label.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
- 	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 						genAllocFloatValue: DPFPReg0
- 						into: SendNumArgsReg
- 						scratchReg: ClassReg
- 						scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: doOp.
- 	"We need to push the register args on two paths; this one and the interpreter primitive path.
- 	But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
- 	self assert: methodOrBlockNumArgs <= self numRegArgs.
- 	jumpFailClass jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
- 	backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
- 	jumpFailClass2 := self Jump: 0.
- 	jumpFailAlloc jmpTarget: self Label.
- 	self compileFallbackToInterpreterPrimitive: 0.
- 	jumpFailClass2 jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genDoubleComparison:invert: (in category 'primitive generators') -----
- genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
- 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #compare type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: 0.
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: Arg0Reg.
- 	self ConvertR: Arg0Reg Rd: DPFPReg1.
- 	self Jump: compare.
- 	jumpFail jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
- 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genLoadArgAtDepth:into: (in category 'primitive generators') -----
  genLoadArgAtDepth: n into: reg
+ 	"All machine code primitives apart from perform: have only
+ 	 register arguments, hence no arg load code is necessary."
+ 	<inline: true>
+ 	self assert: n < objectRepresentation numRegArgs!
- 	self shouldNotImplement!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimReturn (in category 'primitive generators') -----
+ genPrimReturn
+ 	"Generate a return that cuts back the stack to remove the receiver
+ 	 and arguments after an invocation of a primitive with nargs arguments.
+ 	 Since all primitives that succeed in the normal way (i.e. don't execute a
+ 	 method as do genPrimitiveClosureValue and genPrimitivePerform) take only
+ 	 register arguments, there is nothing to do."
+ 	<inline: true>
+ 	self assert: methodOrBlockNumArgs <= self numRegArgs.
+ 	^self RetN: 0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveAdd (in category 'primitive generators') -----
- genPrimitiveAdd
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
- 	self AddR: ReceiverResultReg R: ClassReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	self MoveR: ClassReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveAsCharacter (in category 'primitive generators') -----
- genPrimitiveAsCharacter
- 	| na r |
- 	na := coInterpreter argumentCountOf: methodObj.
- 	r := na <= 1
- 			ifTrue:
- 				[objectRepresentation
- 						genInnerPrimitiveAsCharacter: 0
- 						inReg: (na = 0 ifTrue: [ReceiverResultReg] ifFalse: [Arg0Reg])]
- 			ifFalse: [0].
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveAsFloat (in category 'primitive generators') -----
- genPrimitiveAsFloat
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: TempReg.
- 	self ConvertR: TempReg Rd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 						genAllocFloatValue: DPFPReg0
- 						into: SendNumArgsReg
- 						scratchReg: ClassReg
- 						scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveAt (in category 'primitive generators') -----
- genPrimitiveAt
- 	self assert: self numRegArgs >= 1.
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveAt: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveAtPut (in category 'primitive generators') -----
- genPrimitiveAtPut
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveAtPut: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveBitAnd (in category 'primitive generators') -----
- genPrimitiveBitAnd
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them."
- 	self AndR: Arg0Reg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveBitOr (in category 'primitive generators') -----
- genPrimitiveBitOr
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them."
- 	self OrR: Arg0Reg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveBitShift (in category 'primitive generators') -----
- genPrimitiveBitShift
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address
- 
- 	rTemp := rArg0
- 	rClass := tTemp
- 	rTemp := rTemp & 1
- 	jz nonInt
- 	rClass >>= 1
- 	cmp 0,rClass
- 	jge neg
- 	cmp 31,rClass // numSmallIntegerBits, jge for sign
- 	jge tooBig
- 	rTemp := rReceiver
- 	rTemp <<= rClass
- 	rTemp >>= rClass (arithmetic)
- 	cmp rTemp,rReceiver
- 	jnz ovfl
- 	rReceiver := rReceiver - 1
- 	rReceiver := rReceiver <<= rClass
- 	rReceiver := rReceiver + 1
- 	ret
- neg:
- 	rClass := 0 - rClass
- 	cmp 31,rClass
- 	jge inRange
- 	rClass := 31
- inRange
- 	rReceiver := rReceiver >>= rClass.
- 	rReceiver := rReceiver | 1.
- 	ret
- ovfl
- tooBig
- nonInt:
- 	fail"
- 	| jumpNotSI jumpOvfl jumpNegative jumpTooBig jumpInRange |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	<var: #jumpNegative type: #'AbstractInstruction *'>
- 	<var: #jumpTooBig type: #'AbstractInstruction *'>
- 	<var: #jumpInRange type: #'AbstractInstruction *'>
- 	self assert: self numRegArgs >= 1.
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
- 		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
- 	jumpNegative := self JumpNegative: 0.
- 	self CmpCq: objectRepresentation numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - 31"
- 	jumpTooBig := self JumpGreaterOrEqual: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	self LogicalShiftLeftR: ClassReg R: TempReg.
- 	self ArithmeticShiftRightR: ClassReg R: TempReg.
- 	self CmpR: TempReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - TempReg"
- 	jumpOvfl := self JumpNonZero: 0.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
- 	self LogicalShiftLeftR: ClassReg R: ReceiverResultReg.
- 	objectRepresentation genAddSmallIntegerTagsTo: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpNegative jmpTarget: (self NegateR: ClassReg).
- 	self CmpCq: objectRepresentation numSmallIntegerBits R: ClassReg. "N.B. FLAGS := ClassReg - 31"
- 	jumpInRange := self JumpLessOrEqual: 0.
- 	self MoveCq: objectRepresentation numSmallIntegerBits R: ClassReg.
- 	jumpInRange jmpTarget: (self ArithmeticShiftRightR: ClassReg R: ReceiverResultReg).
- 	objectRepresentation genClearAndSetSmallIntegerTagsIn: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpNotSI jmpTarget: (jumpTooBig jmpTarget: (jumpOvfl jmpTarget: self Label)).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveBitXor (in category 'primitive generators') -----
- genPrimitiveBitXor
- 	| jumpNotSI |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"Clear one or the other tag so that xoring will preserve them."
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
- 	self XorR: Arg0Reg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpNotSI jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveCharacterValue (in category 'primitive generators') -----
- genPrimitiveCharacterValue
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveCharacterValue: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveClass (in category 'primitive generators') -----
- genPrimitiveClass
- 	"Primitive class must be variadic for objectClass:"
- 	| reg |
- 	methodOrBlockNumArgs > 0
- 		ifTrue:
- 			[methodOrBlockNumArgs > 1 ifTrue:
- 				[^self compileFallbackToInterpreterPrimitive: 0].
- 			 reg := Arg0Reg]
- 		ifFalse:
- 			[reg := ReceiverResultReg].
- 	(objectRepresentation
- 			genGetClassObjectOf: reg
- 			into: ReceiverResultReg
- 			scratchReg: TempReg
- 			instRegIsReceiver: methodOrBlockNumArgs = 0) = BadRegisterSet ifTrue:
- 		[objectRepresentation
- 			genGetClassObjectOf: reg
- 			into: ClassReg
- 			scratchReg: TempReg
- 			instRegIsReceiver: methodOrBlockNumArgs = 0.
- 		 self MoveR: ClassReg R: ReceiverResultReg].
- 	self RetN: 0.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveDiv (in category 'primitive generators') -----
- genPrimitiveDiv
- 	| jumpNotSI jumpIsSI jumpZero jumpExact jumpSameSign convert |
- 	<var: #convert type: #'AbstractInstruction *'>
- 	<var: #jumpIsSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	<var: #jumpSameSign type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	self MoveR: Arg0Reg R: Arg1Reg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: ClassReg].
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we must check for overflow."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	"If arg and remainder signs are different we must round down."
- 	self XorR: ClassReg R: Arg1Reg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: Arg1Reg].
- 	jumpSameSign := self JumpGreaterOrEqual: 0.
- 	self SubCq: 1 R: TempReg.
- 	jumpSameSign jmpTarget: (convert := self Label).
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	"test for overflow; the only case is SmallInteger minVal // -1"
- 	jumpExact jmpTarget: self Label.
- 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	jumpIsSI jmpTarget: convert.
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveDivide (in category 'primitive generators') -----
- genPrimitiveDivide
- 	| jumpNotSI jumpZero jumpInexact jumpOverflow |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpInexact type: #'AbstractInstruction *'>
- 	<var: #jumpOverflow type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is non-zero fail."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpInexact := self JumpNonZero: 0.
- 	"test for overflow; the only case is SmallInteger minVal / -1"
- 	jumpOverflow := objectRepresentation genJumpNotSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpOverflow jmpTarget: (jumpInexact jmpTarget: (jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label))).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
- genPrimitiveFloatSquareRoot
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
- 	self SqrtRd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 						genAllocFloatValue: DPFPReg0
- 						into: SendNumArgsReg
- 						scratchReg: ClassReg
- 						scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveIdentical (in category 'primitive generators') -----
- genPrimitiveIdentical
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	^objectRepresentation
- 		genInnerPrimitiveIdentical: 0
- 		orNotIf: false!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
- genPrimitiveIdentityHash
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveIdentityHash: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveMod (in category 'primitive generators') -----
- genPrimitiveMod
- 	| jumpNotSI jumpZero jumpExact jumpSameSign |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	<var: #jumpSameSign type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ClassReg R: Arg1Reg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we're done."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	"If arg and remainder signs are different we must reflect around zero."
- 	self XorR: ClassReg R: Arg1Reg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: Arg1Reg].
- 	jumpSameSign := self JumpGreaterOrEqual: 0.
- 	self XorR: ClassReg R: Arg1Reg.
- 	self AddR: Arg1Reg R: ClassReg.
- 	jumpSameSign jmpTarget: (jumpExact jmpTarget: self Label).
- 	objectRepresentation genSetSmallIntegerTagsIn: ClassReg.
- 	self MoveR: ClassReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveMultiply (in category 'primitive generators') -----
- genPrimitiveMultiply
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	self MoveR: ReceiverResultReg R: Arg1Reg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg..
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg1Reg.
- 	self MulR: Arg1Reg R: ClassReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	objectRepresentation genSetSmallIntegerTagsIn: ClassReg.
- 	self MoveR: ClassReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveNew (in category 'primitive generators') -----
- genPrimitiveNew
- 	| r numArgs |
- 	NewspeakVM
- 		ifTrue:
- 			[r := 0.
- 			 numArgs := coInterpreter argumentCountOf: methodObj.
- 			 numArgs = 1 ifTrue:
- 				[r := objectRepresentation genInnerPrimitiveMirrorNew: 0].
- 			 numArgs = 0 ifTrue:
- 				[r := objectRepresentation genInnerPrimitiveNew: 0]]
- 		ifFalse:
- 			[r := objectRepresentation genInnerPrimitiveNew: 0].
- 	"Call the interpreter primitive either when the machine-code primitive
- 	 fails, or if the machine-code primitive is unimplemented."
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveNewMethod (in category 'primitive generators') -----
- genPrimitiveNewMethod
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveNewMethod: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveNewWithArg (in category 'primitive generators') -----
- genPrimitiveNewWithArg
- 	| r numArgs |
- 	NewspeakVM
- 		ifTrue:
- 			[r := 0.
- 			 numArgs := coInterpreter argumentCountOf: methodObj.
- 			 numArgs = 2 ifTrue:
- 				[r := objectRepresentation genInnerPrimitiveMirrorNewWithArg: 0].
- 			 numArgs = 1 ifTrue:
- 				[r := objectRepresentation genInnerPrimitiveNewWithArg: 0]]
- 		ifFalse:
- 			[r := objectRepresentation genInnerPrimitiveNewWithArg: 0].
- 	"Call the interpreter primitive either when the machine-code primitive
- 	 fails, or if the machine-code primitive is unimplemented."
- 	^self compileFallbackToInterpreterPrimitive: r!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveNotIdentical (in category 'primitive generators') -----
- genPrimitiveNotIdentical
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	^objectRepresentation
- 		genInnerPrimitiveIdentical: 0
- 		orNotIf: true!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveObjectAt (in category 'primitive generators') -----
- genPrimitiveObjectAt
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveObjectAt: 0)!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitivePerform (in category 'primitive generators') -----
  genPrimitivePerform
  	"Generate an in-line perform primitive.  The lookup code requires the selector to be in Arg0Reg.
  	 adjustArgumentsForPerform: adjusts the arguments once genLookupForPerformNumArgs:
  	 has generated the code for the lookup."
  	methodOrBlockNumArgs > self numRegArgs ifTrue:
+ 		[self MoveMw: (backEnd hasLinkRegister
+ 					ifTrue: [methodOrBlockNumArgs - 1]
+ 					ifFalse: [methodOrBlockNumArgs]) * objectMemory wordSize
+ 			r: SPReg
+ 			R: Arg0Reg].
+ 	^self genLookupForPerformNumArgs: methodOrBlockNumArgs!
- 		[self MoveMw: (backEnd hasLinkRegister ifTrue: [methodOrBlockNumArgs - 1] ifFalse: [methodOrBlockNumArgs]) * objectMemory wordSize r: SPReg R: Arg0Reg].
- 	self genLookupForPerformNumArgs: methodOrBlockNumArgs.
- 	^self compileInterpreterPrimitive: (coInterpreter
- 										functionPointerForCompiledMethod: methodObj
- 										primitiveIndex: primitiveIndex)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveQuo (in category 'primitive generators') -----
- genPrimitiveQuo
- 	| convert jumpNotSI jumpZero jumpIsSI jumpExact |
- 	<var: #convert type: #'AbstractInstruction *'>
- 	<var: #jumpIsSI type: #'AbstractInstruction *'>
- 	<var: #jumpZero type: #'AbstractInstruction *'>
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpExact type: #'AbstractInstruction *'>
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	"We must shift away the tags, not just subtract them, so that the
- 	 overflow case doesn't actually overflow the machine instruction."
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
- 	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
- 		[self CmpCq: 0 R: ClassReg].
- 	jumpZero := self JumpZero: 0.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
- 	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
- 	"If remainder is zero we must check for overflow."
- 	self CmpCq: 0 R: ClassReg.
- 	jumpExact := self JumpZero: 0.
- 	convert := self Label.
- 	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpExact jmpTarget: self Label.
- 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
- 	jumpIsSI jmpTarget: convert.
- 	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveSize (in category 'primitive generators') -----
- genPrimitiveSize
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveSize: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
- genPrimitiveSmallFloatSquareRoot
- 	<option: #Spur64BitMemoryManager>
- 	| jumpFailAlloc |
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	self SqrtRd: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 						genAllocFloatValue: DPFPReg0
- 						into: SendNumArgsReg
- 						scratchReg: ClassReg
- 						scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpFailAlloc jmpTarget: self Label.
- 	^self compileFallbackToInterpreterPrimitive: 0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveStringAt (in category 'primitive generators') -----
- genPrimitiveStringAt
- 	self assert: self numRegArgs >= 1.
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveStringAt: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveStringAtPut (in category 'primitive generators') -----
- genPrimitiveStringAtPut
- 	^self compileFallbackToInterpreterPrimitive:
- 		(objectRepresentation genInnerPrimitiveStringAtPut: 0)!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPrimitiveSubtract (in category 'primitive generators') -----
- genPrimitiveSubtract
- 	| jumpNotSI jumpOvfl |
- 	<var: #jumpNotSI type: #'AbstractInstruction *'>
- 	<var: #jumpOvfl type: #'AbstractInstruction *'>
- 	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	self MoveR: ReceiverResultReg R: TempReg.
- 	self SubR: Arg0Reg R: TempReg.
- 	jumpOvfl := self JumpOverflow: 0.
- 	objectRepresentation genAddSmallIntegerTagsTo: TempReg.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpOvfl jmpTarget: (jumpNotSI jmpTarget: self Label).
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSmallFloatArithmetic:preOpCheck: (in category 'primitive generators') -----
- genSmallFloatArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
- 	| jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
- 	<var: #jumpFailClass type: #'AbstractInstruction *'>
- 	<var: #jumpFailClass2 type: #'AbstractInstruction *'>
- 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
- 	<var: #doOp type: #'AbstractInstruction *'>
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	self MoveR: Arg0Reg R: ClassReg.
- 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFailClass := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
- 	doOp := self Label.
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
- 	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
- 	jumpFailAlloc := objectRepresentation
- 						genAllocFloatValue: DPFPReg0
- 						into: SendNumArgsReg
- 						scratchReg: ClassReg
- 						scratchReg: TempReg.
- 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: doOp.
- 	"We need to push the register args on two paths; this one and the interpreter primitive path.
- 	But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
- 	self assert: methodOrBlockNumArgs <= self numRegArgs.
- 	jumpFailClass jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
- 	preOpCheckOrNil ifNotNil:
- 		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
- 	backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
- 	jumpFailClass2 := self Jump: 0.
- 	jumpFailAlloc jmpTarget: self Label.
- 	self compileFallbackToInterpreterPrimitive: 0.
- 	jumpFailClass2 jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
- genSmallFloatComparison: jumpOpcodeGenerator invert: invertComparison
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
- 	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
- 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
- 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #compare type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
- 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: 0.
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: Arg0Reg.
- 	self ConvertR: Arg0Reg Rd: DPFPReg1.
- 	self Jump: compare.
- 	jumpFail jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSmallIntegerComparison: (in category 'primitive generators') -----
- genSmallIntegerComparison: jumpOpcode
- 	| jumpFail jumpTrue |
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	<var: #jumpTrue type: #'AbstractInstruction *'>
- 	jumpFail := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	self CmpR: Arg0Reg R: ReceiverResultReg. "N.B. FLAGS := RRReg - Arg0Reg"
- 	jumpTrue := self genConditionalBranch: jumpOpcode operand: 0.
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: 0.
- 	jumpFail jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSmallIntegerComparison:orDoubleComparison:invert: (in category 'primitive generators') -----
- genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator invert: invertComparison
- 	"Stack looks like
- 		return address"
- 	| jumpDouble jumpNonInt jumpFail jumpTrue jumpCond |
- 	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction *(*jumpFPOpcodeGenerator)(void *)'>
- 	<var: #jumpDouble type: #'AbstractInstruction *'>
- 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpCond type: #'AbstractInstruction *'>
- 	<var: #jumpTrue type: #'AbstractInstruction *'>
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	backEnd hasDoublePrecisionFloatingPointSupport ifFalse:
- 		[^self genSmallIntegerComparison: jumpOpcode].
- 	jumpDouble := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	self CmpR: Arg0Reg R: ReceiverResultReg. "N.B. FLAGS := RRReg - Arg0Reg"
- 	jumpTrue := self gen: jumpOpcode.
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: 0.
- 	
- 	"Argument may be a Float : let us check or fail"
- 	jumpDouble jmpTarget: self Label.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpImmediate: Arg0Reg].
- 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
- 	jumpFail := self JumpNonZero: 0.
- 
- 	"It was a Float, so convert the receiver to double and perform the operation"
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
- 	self ConvertR: ReceiverResultReg Rd: DPFPReg0.
- 	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
- 	invertComparison "May need to invert for NaNs"
- 		ifTrue: [self CmpRd: DPFPReg0 Rd: DPFPReg1]
- 		ifFalse: [self CmpRd: DPFPReg1 Rd: DPFPReg0].
- 	jumpCond := self perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
- 	self genMoveFalseR: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	self RetN: 0.
- 
- 	objectRepresentation smallIntegerIsOnlyImmediateType
- 		ifTrue: [jumpFail jmpTarget: self Label]
- 		ifFalse: [jumpNonInt jmpTarget: (jumpFail jmpTarget: self Label)].
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>isValidFramelessRegister: (in category 'testing') -----
- isValidFramelessRegister: reg
- 	"Answer if the receiver is valid in a frameless method."
- 	^reg = ReceiverResultReg or: [reg = Arg0Reg]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>primRetNOffsetFor: (in category 'primitive generators') -----
- primRetNOffsetFor: nargs
- 	self shouldNotImplement!

Item was changed:
  ----- Method: Symbol>>defined (in category '*VMMaker-interpreter simulator') -----
  defined
  	"To allow constructs such as self cppIf: #'SA_NOCLDSTOP' defined ifTrue: [...].
  	We could go look for a definition but likely there won't be one."
+ 	^(thisContext sender methodClass bindingOf: self)
+ 		ifNil: [false]
+ 		ifNotNil: [:binding| binding value ~~ #undefined]!
- 	^false!

Item was changed:
  ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files,
  	 or in the case of VMBIGENDIAN the various sqConfig.h files.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
  	self isInterpreterClass ifTrue:
  		[STACKVM := COGVM := COGMTVM := false].
  
  	initializationOptions ifNil: [self initializationOptions: Dictionary new].
  	omc := initializationOptions at: #ObjectMemory ifAbsent: nil.
  	(omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue:
  		[omc := initializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name].
  	initializationOptions
  		at: #SqueakV3ObjectMemory	"the good ole default"
  			ifAbsentPut: (omc
  					ifNil: [true]
  					ifNotNil: [(Smalltalk at: omc) includesBehavior: ObjectMemory]);
  		at: #SpurObjectMemory		"the new contender"
  			ifAbsentPut: (omc
  					ifNil: [false]
+ 					ifNotNil: [(Smalltalk at: omc) includesBehavior: SpurMemoryManager]);
+ 		at: #Spur32BitMemoryManager put: false;
+ 		at: #Spur64BitMemoryManager put: false.
- 					ifNotNil: [(Smalltalk at: omc) includesBehavior: SpurMemoryManager]).
  
  	"Use ifAbsentPut: so that they will get copied back to the
  	 VMMaker's options and dead code will likely be eliminated."
  	PharoVM := initializationOptions at: #PharoVM ifAbsentPut: [false].
  	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsentPut: [false].
  	SistaVM := initializationOptions at: #SistaVM ifAbsentPut: [false].
  	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
  	"N.B.  Not yet implemented."
  	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsentPut: [false].
  
  	"These for scripts etc... Usually they should get set by an Interpreter class's initializeMiscConstantsWith:"
  	(initializationOptions includesKey: #STACKVM) ifTrue:
  		[STACKVM := initializationOptions at: #STACKVM].
  	(initializationOptions includesKey: #COGVM) ifTrue:
  		[COGVM := initializationOptions at: #COGVM].
  	(initializationOptions includesKey: #COGMTVM) ifTrue:
  		[COGMTVM := initializationOptions at: #COGMTVM]!

Item was changed:
  ----- Method: VMClass class>>shouldIncludeMethodForSelector: (in category 'translation') -----
  shouldIncludeMethodForSelector: selector
+ 	"Answer whether a primitive method should be translated.  Emit a warning to the transcript if the method doesn't exist."
- 	"Answer whether a primitive method shoud be translated.  Emit a warning to the transcript if the method doesn't exist."
  	^(self whichClassIncludesSelector: selector)
  		ifNotNil:
  			[:c|
  			 (c >> selector pragmaAt: #option:)
  				ifNotNil:
  					[:pragma|
+ 					initializationOptions
+ 						at: pragma arguments first
+ 						ifAbsent: [(self bindingOf: pragma arguments first)
+ 									ifNil: [false]
+ 									ifNotNil: [:binding| binding value ~~ #undefined]]]
- 					 initializationOptions at: pragma arguments first ifAbsent: [false]]
  				ifNil: [true]]
  		ifNil:
  			[Transcript nextPutAll: 'Cannot find implementation of '; nextPutAll: selector; nextPutAll: ' in hierarchy of '; print: self; cr; flush.
  			 false]!



More information about the Vm-dev mailing list