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

commits at source.squeak.org commits at source.squeak.org
Sat Apr 11 03:43:17 UTC 2015


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

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

Name: VMMaker.oscog-eem.1181
Author: eem
Time: 10 April 2015, 8:41:28.267 pm
UUID: f6eaf06e-ed76-43ab-a517-891ecb31f637
Ancestors: VMMaker.oscog-eem.1180

Fix code generation bug surfaced by inline primitives.
On x86 movb N(%reg),%rl can only store into
al, bl, cl & dl, whereas movzbl can store into any
reg.  On ARM move byte also zero-extends.  So
change definition of MoveMbrR to always zero-extend,
use movzbl on x86 and remove all the MoveCq: 0 R:
used to zero the bits of the target of a MoveMb:r:R:.
And now that we have genGetNumSlotsOf:into:, use it.

Fix CogIA32CompilerTests for testCmpRdRd and
modify testMoveMbrR appropriately.

Fix a slip in genTrinaryInlinePrimitive:, meet the constraint
that the target must be in ReceiverResultReg, and do
a better job of register allocation there-in.

Do dead code elimination for the branch following
an inlined comparison (this is done in
genBinaryInlineComparison:opFalse:destReg:
copying the scheme in genSpecialSelectorEqualsEquals).

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

Item was changed:
  ----- Method: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^maxSize := N forms are to get around the compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^maxSize := 0].
  		[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  		[Fill16]					-> [^maxSize := 2].
  		[Fill32]					-> [^maxSize := 4].
  		[FillFromWord]			-> [^maxSize := 4].
  		[Nop]					-> [^maxSize := 1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^maxSize := 1].
  		[IDIVR]					-> [^maxSize := 2].
  		[IMULRR]				-> [^maxSize := 3].
  		[CPUID]					-> [^maxSize := 2].
  		[CMPXCHGAwR]			-> [^maxSize := 7].
  		[CMPXCHGMwrR]		-> [^maxSize := 8].
  		[LFENCE]				-> [^maxSize := 3].
  		[MFENCE]				-> [^maxSize := 3].
  		[SFENCE]				-> [^maxSize := 3].
  		[LOCK]					-> [^maxSize := 1].
  		[XCHGAwR]				-> [^maxSize := 6].
  		[XCHGMwrR]			-> [^maxSize := 7].
  		[XCHGRR]				-> [^maxSize := 2].
  		"Control"
  		[Call]					-> [^maxSize := 5].
  		[JumpR]					-> [^maxSize := 2].
  		[Jump]					-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpLong]				-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpZero]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNegative]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonNegative]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpOverflow]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoOverflow]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoCarry]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLess]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLessOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAbove]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPEqual]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPNotEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLess]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLessOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPOrdered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPUnordered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[RetN]					-> [^maxSize := (operands at: 0) = 0
  													ifTrue: [1]
  													ifFalse: [3]].
  		[Stop]					-> [^maxSize := 1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AndCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[CmpCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[OrCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[SubCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[XorCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AddRR]			-> [^maxSize := 2].
  		[AndRR]			-> [^maxSize := 2].
  		[CmpRR]		-> [^maxSize := 2].
  		[OrRR]			-> [^maxSize := 2].
  		[XorRR]			-> [^maxSize := 2].
  		[SubRR]			-> [^maxSize := 2].
  		[NegateR]		-> [^maxSize := 2].
  		[LoadEffectiveAddressMwrR]
  						-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftLeftRR]		-> [self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [self computeShiftRRSize].
  		[ArithmeticShiftRightRR]	-> [self computeShiftRRSize].
  		[AddRdRd]				-> [^maxSize := 4].
  		[CmpRdRd]				-> [^maxSize := 4].
  		[SubRdRd]				-> [^maxSize := 4].
  		[MulRdRd]				-> [^maxSize := 4].
  		[DivRdRd]				-> [^maxSize := 4].
  		[SqrtRd]					-> [^maxSize := 4].
  		"Data Movement"
  		[MoveCqR]		-> [^maxSize := (operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^maxSize := 5].
  		[MoveRR]		-> [^maxSize := 2].
  		[MoveRdRd]		-> [^maxSize := 4].
  		[MoveAwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRAw]		-> [^maxSize := (self concreteRegister: (operands at: 0)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRMwr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRdM64r]	-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMbrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
+ 											ifTrue: [4]
+ 											ifFalse: [7])
- 											ifTrue: [3]
- 											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRMbr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM16rR]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM64rRd]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^maxSize := 1].
  		[PushR]			-> [^maxSize := 1].
  		[PushCq]		-> [^maxSize := (self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^maxSize := 5].
  		[PrefetchAw]	-> [^maxSize := self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		[ConvertRRd]	-> [^maxSize := 4] }.
  	^0 "to keep C compiler quiet"!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveMbrR (in category 'generate machine code') -----
  concretizeMoveMbrR
  	"N.B. The Cogit compiler makes no assumption about the upper bits being set to zero.
  	 It will clear the register before hand if necessary."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
+ 				at: 0 put: 16r0f;
+ 				at: 1 put: 16rb6;
+ 				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
+ 				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^machineCodeSize := 4].
- 				at: 0 put: 16r8A;
- 				at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
- 				at: 2 put: (offset bitAnd: 16rFF).
- 			 ^machineCodeSize := 3].
  		machineCode
+ 			at: 0 put: 16r0f;
+ 			at: 1 put: 16rb6;
+ 			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
+ 			at: 3 put: (offset bitAnd: 16rFF);
+ 			at: 4 put: (offset >> 8 bitAnd: 16rFF);
+ 			at: 5 put: (offset >> 16 bitAnd: 16rFF);
+ 			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^machineCodeSize := 7].
- 			at: 0 put: 16r8A;
- 			at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
- 			at: 2 put: (offset bitAnd: 16rFF);
- 			at: 3 put: (offset >> 8 bitAnd: 16rFF);
- 			at: 4 put: (offset >> 16 bitAnd: 16rFF);
- 			at: 5 put: (offset >> 24 bitAnd: 16rFF).
- 		^machineCodeSize := 6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
+ 			at: 0 put: 16r0f;
+ 			at: 1 put: 16rb6;
+ 			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
+ 			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
+ 			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := 5].
- 			at: 0 put: 16r8A;
- 			at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
- 			at: 2 put: (self s: SIB1 i: 4 b: srcReg);
- 			at: 3 put: (offset bitAnd: 16rFF).
- 		 ^machineCodeSize := 4].
  	machineCode
+ 		at: 0 put: 16r0f;
+ 		at: 1 put: 16rb6;
+ 		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
+ 		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
+ 		at: 4 put: (offset bitAnd: 16rFF);
+ 		at: 5 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: 6 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 8!
- 		at: 0 put: 16r8A;
- 		at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
- 		at: 2 put: (self s: SIB1 i: 4 b: srcReg);
- 		at: 3 put: (offset bitAnd: 16rFF);
- 		at: 4 put: (offset >> 8 bitAnd: 16rFF);
- 		at: 5 put: (offset >> 16 bitAnd: 16rFF);
- 		at: 6 put: (offset >> 24 bitAnd: 16rFF).
- 	^machineCodeSize := 7!

Item was added:
+ ----- Method: CogIA32CompilerForTests>>hasSSE2Instructions (in category 'testing') -----
+ hasSSE2Instructions
+ 	"Answer if we support SSE2"
+ 	^true!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveMbrR (in category 'tests') -----
  testMoveMbrR
  	"self new testMoveMbrR"
  	CogIA32CompilerForTests registersWithNamesDo:
  		[:sreg :srname|
  		CogIA32CompilerForTests registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveMbrR operand: offset operand: sreg operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movzbl 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!
- 			[:dreg :drname| | brname |
- 			dreg < 4 ifTrue:
- 				[brname := #('%al' '%cl' '%dl' '%bl') at: dreg + 1.
- 				((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 					[:offset| | inst len |
- 					inst := self gen: MoveMbrR operand: offset operand: sreg operand: dreg.
- 					len := inst concretizeAt: 0.
- 					self processor
- 						disassembleInstructionAt: 0
- 						In: inst machineCode object
- 						into: [:str :sz| | plainJane herIntended |
- 							plainJane := self strip: str.
- 							herIntended := 'movb 0x', (offset hex allButFirst: 3), '(', srname, '), ', brname.
- 							self assert: (plainJane match: herIntended).
- 							self assert: len = sz]]]]]!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genGetSizeOf:into:formatReg:scratchReg:abortJumpsInto: (in category 'primitive generators') -----
  genGetSizeOf: sourceReg into: destReg formatReg: formatReg scratchReg: scratchReg abortJumpsInto: aBinaryBlock
  	"Get the size of the non-immediate object in sourceReg into destReg using formatReg
  	 and scratchReg as temps.  None of these registers can overlap.  Supply the jumps
  	 taken if the object in sourceReg is not indexable, or if the object in sourceReg is a
  	 context.. Hack: If the object has a pointer format other than 2 leave the number of
  	 fixed fields in formatReg.  Used by primitiveSize, primitiveAt, and primitiveAtPut"
  	<returnTypeC: #'AbstractInstruction *'>
+ 	| jumpNotIndexable
- 	| jumpNotIndexable jumpSmallSize
  	  jumpBytesDone jumpShortsDone jumpArrayDone jump32BitLongsDone
  	  jumpIsBytes jumpHasFixedFields jumpIsShorts jumpIsContext  |
  	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
- 	<var: #jumpSmallSize type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpArrayDone type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jump32BitLongsDone type: #'AbstractInstruction *'>
  
  	"formatReg := self formatOf: sourceReg"
  	self genGetFormatOf: sourceReg
  		into: formatReg
  		leastSignificantHalfOfBaseHeaderIntoScratch: scratchReg.
  
+ 	self genGetNumSlotsOf: sourceReg into: destReg.
- 	"get numSlots into destReg."
- 	cogit MoveCq: 0 R: destReg. "N.B. MoveMb:r:R: does not zero other bits"
- 	cogit MoveMb: 7 r: sourceReg R: destReg. "MSB of header"
- 	cogit CmpCq: objectMemory numSlotsMask R: destReg.
- 	jumpSmallSize := cogit JumpLess: 0.
- 	cogit MoveMw: -8 r: sourceReg R: destReg. "LSW of overflow size header"
  
  	"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.
- 	jumpSmallSize jmpTarget:
- 					(cogit CmpCq: objectMemory firstByteFormat R: formatReg).
  	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpArrayDone := cogit JumpZero: 0.
  	jumpNotIndexable := cogit JumpLess: 0.
  					cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpHasFixedFields := cogit JumpLessOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jump32BitLongsDone := cogit JumpGreaterOrEqual: 0.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexable jmpTarget: cogit Label.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: destReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  		cogit SubR: formatReg R: destReg.
  	jumpBytesDone := cogit Jump: 0.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: destReg).
  		cogit AndCq: 1 R: formatReg.
  		cogit SubR: formatReg R: destReg.
  	jumpShortsDone := cogit Jump: 0.
  
  	"formatReg contains fmt, now up for grabs.
  	 destReg contains numSlots, precious.
  	 sourceReg must be preserved"
  	jumpHasFixedFields jmpTarget:
  		(cogit AndCq: objectMemory classIndexMask R: scratchReg).
  	cogit MoveR: scratchReg R: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: scratchReg.
  	jumpIsContext := cogit JumpZero: 0.
  	cogit PushR: destReg.
  	self genGetClassObjectOfClassIndex: formatReg into: destReg scratchReg: scratchReg.
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: destReg destReg: formatReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit
  		PopR: destReg;
  		AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg;
  		SubR: formatReg R: destReg.
  
  	jumpArrayDone jmpTarget:
  	(jump32BitLongsDone jmpTarget:
  	(jumpShortsDone jmpTarget:
  	(jumpBytesDone jmpTarget:
  		cogit Label))).
  	aBinaryBlock value: jumpNotIndexable value: jumpIsContext!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveAt: (in category 'primitive generators') -----
  genInnerPrimitiveAt: retNoffset
  	"Implement the guts of primitiveAt"
+ 	| formatReg jumpNotIndexable jumpImmediate jumpBadIndex
- 	| formatReg jumpNotIndexable jumpSmallSize jumpImmediate jumpBadIndex
  	  jumpBytesDone jumpShortsDone jumpWordsDone jumpFixedFieldsDone
  	  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: #jumpSmallSize type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpBytesDone type: #'AbstractInstruction *'>
  	<var: #jumpShortsDone type: #'AbstractInstruction *'>
  	<var: #jumpWordsDone type: #'AbstractInstruction *'>
  	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jumpFixedFieldsDone type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpFixedFieldsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
  	cogit MoveR: Arg0Reg R: TempReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallIntegerInScratchReg: 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.
- 	"get numSlots into ClassReg."
- 	cogit MoveCq: 0 R: ClassReg. "N.B. MoveMb:r:R: does not zero other bits"
- 	cogit MoveMb: 7 r: ReceiverResultReg R: ClassReg. "MSB of header"
- 	cogit CmpCq: objectMemory numSlotsMask R: ClassReg.
- 	jumpSmallSize := cogit JumpBelow: 0.
- 	cogit MoveMw: -8 r: ReceiverResultReg R: ClassReg. "LSW of overflow size header"
  
  	"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.
- 	jumpSmallSize jmpTarget:
- 					(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 MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	jumpBytesDone := cogit Jump: 0.
  
  	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.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	jumpShortsDone := cogit Jump: 0.
  
  	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.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	jumpWordsDone := cogit Jump: 0.
  
  	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.
  	jumpFixedFieldsDone := cogit Jump: 0.
  
  	jumpIsArray jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.	
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  
  	jumpFixedFieldsDone jmpTarget:
  	(jumpWordsDone jmpTarget:
  	(jumpShortsDone jmpTarget:
  	(jumpBytesDone jmpTarget:
  		(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 changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveAtPut: (in category 'primitive generators') -----
  genInnerPrimitiveAtPut: retNoffset
  	"Implement the guts of primitiveAtPut"
  	| formatReg jumpImmediate jumpBadIndex
+ 	  jumpNotIndexablePointers jumpNotIndexableBits
- 	  jumpSmallSize jumpNotIndexablePointers jumpNotIndexableBits
  	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpHasFixedFields
  	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
  	  jumpWordsOutOfBounds jumpBytesOutOfBounds jumpBytesOutOfRange
  	  jumpNonSmallIntegerValue jumpShortsUnsupported jumpNotPointers
  	  |
  	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpSmallSize 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 MoveR: ReceiverResultReg R: TempReg.
  	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
  	cogit MoveR: Arg0Reg R: TempReg.
  	jumpBadIndex := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
- 	"get numSlots into ClassReg."
- 	cogit MoveCq: 0 R: ClassReg. "N.B. MoveMb:r:R: does not zero other bits"
- 	cogit MoveMb: 7 r: ReceiverResultReg R: ClassReg. "MSB of header"
- 	cogit CmpCq: objectMemory numSlotsMask R: ClassReg.
- 	jumpSmallSize := cogit JumpBelow: 0.
- 	cogit MoveMw: -8 r: ReceiverResultReg R: ClassReg. "LSW of overflow size header"
  
  	"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.
- 	jumpSmallSize jmpTarget:
- 					(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.
  
  	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.
  	cogit MoveR: Arg1Reg R: TempReg.
  	jumpNonSmallIntegerValue := self genJumpNotSmallIntegerInScratchReg: 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 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: 
  	(jumpNotIndexableBits jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsUnsupported jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexablePointers jmpTarget:
  	(jumpNonSmallIntegerValue jmpTarget:
  	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label)))))))))).
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveStringAt: (in category 'primitive generators') -----
  genInnerPrimitiveStringAt: retNoffset
  	"Implement the guts of primitiveStringAt; dispatch on size"
+ 	| formatReg jumpNotIndexable jumpBadIndex done
- 	| formatReg jumpNotIndexable jumpSmallSize 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: #jumpSmallSize 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: TempReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
  
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
- 	"get numSlots into ClassReg."
- 	cogit MoveCq: 0 R: ClassReg. "N.B. MoveMb:r:R: does not zero other bits"
- 	cogit MoveMb: 7 r: ReceiverResultReg R: ClassReg. "MSB of header"
- 	cogit CmpCq: objectMemory numSlotsMask R: ClassReg.
- 	jumpSmallSize := cogit JumpLess: 0.
- 	cogit MoveMw: -8 r: ReceiverResultReg R: ClassReg. "LSW of overflow size header"
  
  	"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.
- 	jumpSmallSize jmpTarget:
- 					(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.
  	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 changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveStringAtPut: (in category 'primitive generators') -----
  genInnerPrimitiveStringAtPut: retNoffset
  	"Implement the guts of primitiveStringAtPut"
+ 	| formatReg jumpImmediate jumpBadIndex jumpBadArg
- 	| formatReg jumpSmallSize jumpImmediate jumpBadIndex jumpBadArg
  	  jumpWordsDone jumpBytesOutOfRange
  	  jumpIsBytes jumpNotString jumpIsCompiledMethod
  	  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: #jumpSmallSize type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpWordsDone type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
  	cogit MoveR: Arg0Reg R: TempReg.
  	jumpBadIndex := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	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 genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
- 	"get numSlots into ClassReg."
- 	cogit MoveCq: 0 R: ClassReg. "N.B. MoveMb:r:R: does not zero other bits"
- 	cogit MoveMb: 7 r: ReceiverResultReg R: ClassReg. "MSB of header"
- 	cogit CmpCq: objectMemory numSlotsMask R: ClassReg.
- 	jumpSmallSize := cogit JumpBelow: 0.
- 	cogit MoveMw: -8 r: ReceiverResultReg R: ClassReg. "LSW of overflow size header"
  
  	"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.
- 	jumpSmallSize jmpTarget:
- 					(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)))))).
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetRawSlotSizeOfNonImm:into: (in category 'compile abstract instructions') -----
  genGetRawSlotSizeOfNonImm: sourceReg into: destReg
+ 	"The raw numSlots field is the most significant byte of the 64-bit header word.
+ 	 MoveMbrR zero-extends."
- 	"The raw numSlots field is the most significant byte of the 64-bit header word."
  	cogit MoveMb: 7 r: sourceReg R: destReg.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreCheckReceiverReg:valueReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreCheckReceiverReg: destReg valueReg: valueReg scratchReg: scratchReg
  	"Generate the code for a store check of valueReg into destReg."
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"Is value stored an integer?  If so we're done"
  	cogit MoveR: valueReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: valueReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
  	 Need to remember this only if the remembered bit is not already set.
  	 Test the remembered bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rememberedBitByteOffset := jmpSourceOld isBigEndian
  									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
  									ifFalse:[objectMemory rememberedBitShift // 8].
  	mask := 1 << (objectMemory rememberedBitShift \\ 8).
- 	"N.B. MoveMb:r:R: does not zero other bits"
  	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Remembered bit is not set.  Call store check to insert dest into remembered table."
  	self assert: destReg == ReceiverResultReg.
  	cogit
  		CallRT: ceStoreCheckTrampoline
+ 		registersToBeSavedMask: (((cogit registerMaskFor: valueReg)
+ 										bitOr: cogit callerSavedRegMask)
+ 										bitClear: (cogit registerMaskFor: ReceiverResultReg)).
- 		registersToBeSavedMask: ((cogit registerMaskFor: valueReg)
- 										bitOr: cogit callerSavedRegMask).
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRemembered jmpTarget:
  		cogit Label))).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genStoreSourceReg:slotIndex:destReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRoot mask rootBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRoot type: #'AbstractInstruction *'>
  	"do the store"
  	cogit MoveR: sourceReg Mw: index * objectMemory wordSize + objectMemory baseHeaderSize r: destReg.
  	"now the check.  Is value stored an integer?  If so we're done"
  	cogit MoveR: sourceReg R: scratchReg.
  	cogit AndCq: 1 R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveAw: objectMemory youngStartAddress R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpAboveOrEqual: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := sourceReg - scratchReg"
  	jmpSourceOld := cogit JumpBelow: 0.
  	"value is young and target is old.
  	 Need to make this a root if the root bit is not already set.
  	 Test the root bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rootBitByteOffset := jmpSourceOld isBigEndian
  							ifTrue: [objectMemory wordSize - RootBitDigitLength]
  							ifFalse:[RootBitDigitLength - 1].
  	mask := RootBitDigitLength > 1
  				ifTrue: [RootBit >> (RootBitDigitLength - 1 * 8)]
  				ifFalse: [RootBit].
- 	"N.B. MoveMb:r:R: does not zero other bits"
  	cogit MoveMb: rootBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRoot := cogit JumpNonZero: 0.
  	"Root bit is not set.  Call store check to insert dest into root table."
  	self assert: destReg == ReceiverResultReg.
  	cogit
  		CallRT: ceStoreCheckTrampoline
+ 		registersToBeSavedMask: (((cogit registerMaskFor: sourceReg)
+ 										bitOr: cogit callerSavedRegMask)
+ 										bitClear: (cogit registerMaskFor: ReceiverResultReg)).
- 		registersToBeSavedMask: ((cogit registerMaskFor: sourceReg)
- 										bitOr: cogit callerSavedRegMask).
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRoot jmpTarget:
  		cogit Label))).
  	^0!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
+ 		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
- 		Mbr		- memory byte whose address is at a constant offset from an address in a register
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some."
  
  	| opcodeNames refs |
  	self flag: 'GPRegMin and GPRegMax are poorly thought-out and should instead defer to the backEnd for allocateable registers.'.
  	"A small fixed set of abstract registers are defined and used in code generation
  	 for Smalltalk code, and executes on stack pages in the stack zone.
  	 These are mapped to processor-specific registers by concreteRegister:"
  	FPReg := -1.	"A frame pointer is used for Smalltalk frames."
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3. "The receiver at point of send, and return value from a send"
  	TempReg := -4.
  	ClassReg := -5.							"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg := -6.				"Sends > 2 args set the arg count in this reg"
  	Arg0Reg := -7.							"In the StackToregisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg := GPRegMin := -8.
  
  	"Floating-point registers"
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  
  	"RISC-specific"
  	LinkReg := -17.
  	RISCTempReg := -18.
  	PCReg := -19.
  	VarBaseReg := -20. "If useful, points to base of interpreter variables."
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long jumps are contigiuous within them.  See FirstJump et al below"
  						JumpLong
  						JumpLongZero		"a.k.a. JumpLongEqual"
  						JumpLongNonZero	"a.k.a. JumpLongNotEqual"
  						Jump
  						JumpZero			"a.k.a. JumpEqual"
  						JumpNonZero		"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR MulRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
  						AndCqRR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd TstCqR SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpLong.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was changed:
  ----- Method: Cogit>>MoveMb:r:R: (in category 'abstract instructions') -----
  MoveMb: offset r: baseReg R: destReg
+ 	"N.B.  This instruction is guaranteed to zero-extend the byte into destReg."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	^self gen: MoveMbrR operand: offset operand: baseReg operand: destReg!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genFastPrimTraceUsing:and: (in category 'primitive generators') -----
  genFastPrimTraceUsing: r1 and: r2
  	"Suport for compileInterpreterPrimitive.  Generate inline code so as to record the primitive
  	 trace as fast as possible."
  	self MoveCq: 0 R: TempReg.
- 	self MoveCq: 0 R: r2. "N.B. MoveMb:r:R: does not zero other bits"
  	"Too lazy to add MoveAbR and MoveRAb, so misuse MoveMbrR and MoveRMbr"
  	self MoveMb: coInterpreter primTraceLogIndexAddress r: TempReg R: r2.
  	self MoveR: r2 R: r1.
  	self AddCq: 1 R: r1.
  	self MoveR: r1 Mb: coInterpreter primTraceLogIndexAddress r: TempReg.
  	methodLabel addDependent:
  		(self annotateAbsolutePCRef:
  			(self MoveCw: methodLabel asInteger R: r1)).
  	self MoveMw: (self offset: CogMethod of: #selector) r: r1 R: TempReg.
  	self MoveCw: coInterpreter primTraceLogAddress asInteger R: r1.
  	self MoveR: TempReg Xwr: r2 R: r1!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') -----
  genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg
  	"Inlined comparison. opTrue = jump for true and opFalse = jump for false"
  	| nextPC branchDescriptor nExts |	
  	nextPC := bytecodePC + 3.
  	nExts := 0.	
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  	 	 nextPC := nextPC + branchDescriptor numBytes].
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])
  		ifTrue: "This is the path where the inlined comparison is followed immediately by a branch"
  			[| targetBytecodePC postBranchPC |
  			targetBytecodePC := nextPC
  					+ branchDescriptor numBytes
  					+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  			postBranchPC := nextPC + branchDescriptor numBytes.
+ 			(self fixupAt: nextPC - initialPC) targetInstruction = 0
+ 				ifTrue: "The next instruction is dead.  we can skip it."
+ 					[deadCode := true.
+ 				 	 self ensureFixupAt: targetBytecodePC - initialPC.
+ 					 self ensureFixupAt: postBranchPC - initialPC]
+ 				ifFalse:
+ 					[self ssPushConstant: objectMemory trueObject]. "dummy value"
- 			self ssPushConstant: objectMemory trueObject. "dummy object"
  			self gen: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse])
  				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  			self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)]
  		ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch"
  			[| condJump jump |
  			condJump := self gen: opTrue operand: 0.
  	 		self 
  				annotate: (self MoveCw: objectMemory falseObject R: destReg) 
  				objRef: objectMemory falseObject.
  	 		jump := self Jump: 0.
  			condJump jmpTarget: (self 
  				annotate: (self MoveCw: objectMemory trueObject R: destReg) 
  				objRef: objectMemory trueObject).
  			jump jmpTarget: self Label].
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genTrinaryInlinePrimitive: (in category 'inline primitive generators') -----
  genTrinaryInlinePrimitive: prim
  	"Unary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#trinaryInlinePrimitive:"
  
  	| ra1 ra2 rr adjust |
  	(ra2 := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssAllocateRequiredReg: (ra2 := Arg1Reg)].
  	(ra1 := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: ra2))) ifNil:
  		[self ssAllocateRequiredReg: (ra1 := Arg0Reg)].
+ 	prim = 0
+ 		ifTrue:
+ 			[rr := ReceiverResultReg.
+ 			 ((self ssValue: 2) type = SSRegister
+ 			  and: [(self ssValue: 2) register = ReceiverResultReg]) ifFalse:
+ 				[self ssAllocateRequiredReg: rr]]
+ 		ifFalse:
+ 			[(rr := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: ra1 and: ra2))) ifNil:
+ 				[self ssAllocateRequiredReg: (rr := ReceiverResultReg)].
+ 			 optStatus isReceiverResultRegLive: false].
- 	(rr := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: ra1 and: ra2))) ifNil:
- 		[self ssAllocateRequiredReg: (rr := ReceiverResultReg)].
- 	(rr = ReceiverResultReg or: [ra1 = ReceiverResultReg or: [ra2 = ReceiverResultReg]]) ifTrue:
- 		[optStatus isReceiverResultRegLive: false].
  	self assert: (rr ~= ra1 and: [rr ~= ra2 and: [ra1 ~= ra2]]).
  	self ssTop popToReg: ra2.
  	self ssPop: 1.
  	self ssTop popToReg: ra1.
  	self ssPop: 1.
  	self ssTop popToReg: rr.
  	self ssPop: 1.
  	objectRepresentation genConvertSmallIntegerToIntegerInReg: ra1.
  	"Now: ra is the variable object, rr is long, TempReg holds the value to store."
  	prim caseOf: {
  		"0 - 1 pointerAt:put: and byteAt:Put:"
  		[0] ->	[ adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				adjust ~= 0 ifTrue: [ self AddCq: adjust R: ra1. ]. 
  				self MoveR: ra2 Xwr: ra1 R: rr.
+ 				objectRepresentation genStoreCheckReceiverReg: rr valueReg: ra2 scratchReg: TempReg].
- 				objectRepresentation genStoreCheckReceiverReg: rr valueReg: ra1 scratchReg: TempReg].
  		[1] ->	[ objectRepresentation genConvertSmallIntegerToIntegerInReg: ra2.
  				adjust := objectMemory baseHeaderSize - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				self AddCq: adjust R: ra1.
  				self MoveR: ra2 Xbr: ra1 R: rr.
  				objectRepresentation genConvertIntegerToSmallIntegerInReg: ra2. ]
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: ra2.
  	^0!



More information about the Vm-dev mailing list