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

commits at source.squeak.org commits at source.squeak.org
Mon Jul 7 20:58:05 UTC 2014


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

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

Name: VMMaker.oscog-eem.808
Author: eem
Time: 7 July 2014, 1:55:27.921 pm
UUID: 84bdf081-a2e8-4c84-b249-b140228e6636
Ancestors: VMMaker.oscog-eem.807

Cogit:
Change implementation of the implicit receiver trampoline
to cache the class tag, not the class object (thanks Ryan).
Has a significant impact on Newspeak Spur performance.
Refactor getInlineCacheClassTagFrom:into: into
getInlineCacheClassTagFrom:into: and add inlineCacheTagForClass:
to support this.

Change the V3 inline cache check to not shift the compact
class index (thanks Tim).  Saves a byte and an instruction
from the entry sequence.

Add the opcode for MoveRAb (but no support as yet).

Interpreter:
Finally rename ClassInteger to ClassSmallInteger.

Plugins:
Make primSizeField[Put] simulate.

Simulator:
Add some missing NewsqueakV4 instructions.

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

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
+ 	self assert: ((cogit cogMethodDoesntLookKosher: cogMethod) = 0
+ 				 or: [(cogit cogMethodDoesntLookKosher: cogMethod) = 23
+ 					 and: [(cogit cCoerceSimple: cogMethod methodObject to: #'CogMethod *') cmType = CMFree]]).
- 	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader]
  			ifFalse:
  				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
  				 self cppIf: NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod.
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod.
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was added:
+ ----- Method: CogObjectRepresentation>>genGetInlineCacheClassTagFrom:into:forEntry: (in category 'compile abstract instructions') -----
+ genGetInlineCacheClassTagFrom: sourceReg into: destReg forEntry: forEntry
+ 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline cache tag
+ 	 for a given object is the value loaded in inline caches to distinguish objects of different
+ 	 classes. If forEntry is true answer the entry label at which control is to enter (cmEntryOffset).
+ 	 If forEntry is false, control enters at the start."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>inlineCacheTagForClass: (in category 'in-line cacheing') -----
+ inlineCacheTagForClass: classOop
+ 	"Answer the relevant inline cache tag for a class.
+ 	 c.f. inlineCacheTagForInstance:"
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentation>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
  inlineCacheTagForInstance: oop
+ 	"Answer the relevant inline cache tag for an instance.
+ 	 c.f. getInlineCacheClassTagFrom:into: & inlineCacheTagForClass:"
- 	"c.f. getInlineCacheClassTagFrom:into:"
  	^self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genGetClassTagOf:into:scratchReg: (in category 'compile abstract instructions') -----
  genGetClassTagOf: instReg into: destReg scratchReg: scratchReg
+ 	^self genGetInlineCacheClassTagFrom: instReg into: destReg forEntry: true!
- 	^self getInlineCacheClassTagFrom: instReg into: destReg!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genGetInlineCacheClassTagFrom:into:forEntry: (in category 'compile abstract instructions') -----
+ genGetInlineCacheClassTagFrom: sourceReg into: destReg forEntry: forEntry
+ 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline
+ 	 cache tag for a given object is the value loaded in inline caches to distinguish
+ 	 objects of different classes.  In Spur this is either the tags for immediates, (with
+ 	 1 & 3 collapsed to 1 for SmallIntegers, and 2 collapsed to 0 for Characters), or
+ 	 the receiver's classIndex.
+ 	 If forEntry is true answer the entry label at which control is to enter (cmEntryOffset).
+ 	 If forEntry is false, control enters at the start.
+ 	If forEntry is false, generate something like this:
+ 		Limm:
+ 			andl $0x1, rDest
+ 			j Lcmp
+ 		Lentry:
+ 			movl rSource, rDest
+ 			andl $0x3, rDest
+ 			jnz Limm
+ 			movl 0(%edx), rDest
+ 			andl $0x3fffff, rDest
+ 		Lcmp:
+ 	 If forEntry is true, generate something like the following.
+ 	 At least on a 2.2GHz Intel Core i7 the following is slightly faster than the above,
+ 	 136m sends/sec vs 130m sends/sec for nfib in tinyBenchmarks
+ 		Lentry:
+ 			movl rSource, rDest
+ 			andl $0x3, rDest
+ 			jz LnotImm
+ 			andl $1, rDest
+ 			j Lcmp
+ 		LnotImm:
+ 			movl 0(%edx), rDest
+ 			andl $0x3fffff, rDest
+ 		Lcmp:
+ 	 But we expect most SmallInteger arithmetic to be performed in-line and so prefer the
+ 	 version that is faster for non-immediates (because it branches for immediates only)."
+ 	| immLabel jumpNotImm entryLabel jumpCompare |
+ 	<var: #immLabel type: #'AbstractInstruction *'>
+ 	<var: #jumpNotImm type: #'AbstractInstruction *'>
+ 	<var: #entryLabel type: #'AbstractInstruction *'>
+ 	<var: #jumpCompare type: #'AbstractInstruction *'>
+ 	forEntry
+ 		ifFalse:
+ 			[entryLabel := cogit Label.
+ 			 cogit MoveR: sourceReg R: destReg.
+ 			 cogit AndCq: objectMemory tagMask R: destReg.
+ 			 jumpNotImm := cogit JumpZero: 0.
+ 			 cogit AndCq: 1 R: destReg.
+ 			 jumpCompare := cogit Jump: 0.
+ 			 "Get least significant half of header word in destReg"
+ 			 self flag: #endianness.
+ 			 jumpNotImm jmpTarget:
+ 				(cogit MoveMw: 0 r: sourceReg R: destReg).
+ 			 jumpCompare jmpTarget:
+ 				(cogit AndCq: objectMemory classIndexMask R: destReg)]
+ 		ifTrue:
+ 			[cogit AlignmentNops: BytesPerWord.
+ 			 immLabel := cogit Label.
+ 			 cogit AndCq: 1 R: destReg.
+ 			 jumpCompare := cogit Jump: 0.
+ 			 cogit AlignmentNops: BytesPerWord.
+ 			 entryLabel := cogit Label.
+ 			 cogit MoveR: sourceReg R: destReg.
+ 			 cogit AndCq: objectMemory tagMask R: destReg.
+ 			 cogit JumpNonZero: immLabel.
+ 			 self flag: #endianness.
+ 			 "Get least significant half of header word in destReg"
+ 			 cogit MoveMw: 0 r: sourceReg R: destReg.
+ 			 cogit AndCq: objectMemory classIndexMask R: destReg.
+ 			 jumpCompare jmpTarget: cogit Label].
+ 	^entryLabel!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>getInlineCacheClassTagFrom:into: (in category 'compile abstract instructions') -----
- getInlineCacheClassTagFrom: sourceReg into: destReg
- 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline
- 	 cache tag for a given object is the value loaded in inline caches to distinguish
- 	 objects of different classes.  In Spur this is either the tags for immediates, (with
- 	 1 & 3 collapsed to 1 for SmallIntegers, and 2 collapsed to 0 for Characters), or
- 	 the receiver's classIndex.  Generate something like this:
- 		Limm:
- 			andl $0x1, rDest
- 			j Lcmp
- 		Lentry:
- 			movl rSource, rDest
- 			andl $0x3, rDest
- 			jnz Limm
- 			movl 0(%edx), rDest
- 			andl $0x3fffff, rDest
- 		Lcmp:
- 	 At least on a 2.2GHz Intel Core i7 the following is slightly faster than the above,
- 	 136m sends/sec vs 130m sends/sec for nfib in tinyBenchmarks
- 		Lentry:
- 			movl rSource, rDest
- 			andl $0x3, rDest
- 			jz LnotImm
- 			andl $1, rDest
- 			j Lcmp
- 		LnotImm:
- 			movl 0(%edx), rDest
- 			andl $0x3fffff, rDest
- 		Lcmp:
- 	 But we expect most SmallInteger arithmetic to be performed in-line and so prefer the
- 	 version that is faster for non-immediates (because it branches for immediates only)."
- 	| immLabel jumpNotImm entryLabel jumpCompare |
- 	<var: #immLabel type: #'AbstractInstruction *'>
- 	<var: #jumpNotImm type: #'AbstractInstruction *'>
- 	<var: #entryLabel type: #'AbstractInstruction *'>
- 	<var: #jumpCompare type: #'AbstractInstruction *'>
- 	false
- 		ifTrue:
- 			[cogit AlignmentNops: BytesPerWord.
- 			 entryLabel := cogit Label.
- 			 cogit MoveR: sourceReg R: destReg.
- 			 cogit AndCq: objectMemory tagMask R: destReg.
- 			 jumpNotImm := cogit JumpZero: 0.
- 			 cogit AndCq: 1 R: destReg.
- 			 jumpCompare := cogit Jump: 0.
- 			 "Get least significant half of header word in destReg"
- 			 self flag: #endianness.
- 			 jumpNotImm jmpTarget:
- 				(cogit MoveMw: 0 r: sourceReg R: destReg).
- 			 jumpCompare jmpTarget:
- 				(cogit AndCq: objectMemory classIndexMask R: destReg)]
- 		ifFalse:
- 			[cogit AlignmentNops: BytesPerWord.
- 			 immLabel := cogit Label.
- 			 cogit AndCq: 1 R: destReg.
- 			 jumpCompare := cogit Jump: 0.
- 			 cogit AlignmentNops: BytesPerWord.
- 			 entryLabel := cogit Label.
- 			 cogit MoveR: sourceReg R: destReg.
- 			 cogit AndCq: objectMemory tagMask R: destReg.
- 			 cogit JumpNonZero: immLabel.
- 			 self flag: #endianness.
- 			 "Get least significant half of header word in destReg"
- 			 cogit MoveMw: 0 r: sourceReg R: destReg.
- 			 cogit AndCq: objectMemory classIndexMask R: destReg.
- 			 jumpCompare jmpTarget: cogit Label].
- 	^entryLabel!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>inlineCacheTagForClass: (in category 'in-line cacheing') -----
+ inlineCacheTagForClass: classOop
+ 	"Answer the relevant inline cache tag for a class.
+ 	 c.f. inlineCacheTagForInstance:"
+ 	| hash |
+ 	hash := objectMemory ensureBehaviorHash: classOop.
+ 	^hash <= objectMemory tagMask
+ 		ifTrue: [hash bitAnd: 1]
+ 		ifFalse: [hash]!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
  inlineCacheTagForInstance: oop
+ 	"Answer the relevant inline cache tag for an instance.
+ 	 c.f. getInlineCacheClassTagFrom:into: & inlineCacheTagForClass:"
- 	"c.f. getInlineCacheClassTagFrom:into:"
  	^(objectMemory isImmediate: oop)
+ 		ifTrue: [oop bitAnd: 1] "SmallInteger => 1, Character => 0"
- 		ifTrue: [oop bitAnd: 1]
  		ifFalse: [objectMemory classIndexOf: oop]!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>inlineCacheTagForClass: (in category 'in-line cacheing') -----
+ inlineCacheTagForClass: classOop
+ 	"Answer the relevant inline cache tag for a class.
+ 	 c.f. inlineCacheTagForInstance:"
+ 	^objectMemory ensureBehaviorHash: classOop!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
  inlineCacheTagForInstance: oop
+ 	"Answer the relevant inline cache tag for an instance.
+ 	 c.f. getInlineCacheClassTagFrom:into: & inlineCacheTagForClass:"
- 	"c.f. getInlineCacheClassTagFrom:into:"
  	^(objectMemory isImmediate: oop)
  		ifTrue: [oop bitAnd: objectMemory tagMask]
  		ifFalse: [objectMemory classIndexOf: oop]!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>getInlineCacheClassTagFrom:into: (in category 'compile abstract instructions') -----
- getInlineCacheClassTagFrom: sourceReg into: destReg
- 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline cache tag
- 	 for a given object is the value loaded in inline caches to distinguish objects of different
- 	 classes.  In Spur this is either the tags for immediates, or the receiver's classIndex."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
- inlineCacheTagForInstance: oop
- 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>checkValidInlineCacheTag: (in category 'garbage collection') -----
  checkValidInlineCacheTag: cacheTag
  	^((cacheTag bitAnd: 1 << ShiftForWord - 1) = 0
  		and: [cacheTag
+ 				between: 1 << objectMemory compactClassFieldLSB
+ 				and: (objectMemory compactClassIndexOfHeader: -1) << objectMemory compactClassFieldLSB])
- 				between: 1 << ShiftForWord
- 				and: (objectMemory compactClassIndexOfHeader: -1) << ShiftForWord])
  	   or: [self checkValidObjectReference: cacheTag]!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>classForInlineCacheTag: (in category 'in-line cacheing') -----
  classForInlineCacheTag: inlineCacheTag
  	(objectMemory isIntegerObject: inlineCacheTag) ifTrue:
  		[^objectMemory classSmallInteger].
  	(self couldBeObject: inlineCacheTag) ifTrue:
  		[^inlineCacheTag].
+ 	^objectMemory compactClassAt: inlineCacheTag >> objectMemory compactClassFieldLSB!
- 	^objectMemory compactClassAt: inlineCacheTag >> ShiftForWord!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genGetInlineCacheClassTagFrom:into:forEntry: (in category 'compile abstract instructions') -----
+ genGetInlineCacheClassTagFrom: sourceReg into: destReg forEntry: forEntry
+ 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline cache tag
+ 	 for a given object is the value loaded in inline caches to distinguish objects of different
+ 	 classes.  In Spur this is either the tags for immediates, or the receiver's classIndex.
+ 	 The inline cache tag for a given object is the value loaded in inline caches to distinguish
+ 	 objects of different classes.  In SqueakV3 the tag is the integer tag bit for SmallIntegers (1),
+ 	 the compact class index shifted by log: 2 word size for objects with compact classes
+ 	 (1 * 4 to: 31 * 4 by: 4), or the class.  These ranges cannot overlap because the heap
+ 	 (and hence the lowest class object) is beyond the machine code zone.
+ 	 If forEntry is true answer the entry label at which control is to enter (cmEntryOffset).
+ 	 If forEntry is false, control enters at the start."
+ 	| entryLabel jumpIsInt jumpCompact |
+ 	<var: #entryLabel type: #'AbstractInstruction *'>
+ 	<var: #jumpIsInt type: #'AbstractInstruction *'>
+ 	<var: #jumpCompact type: #'AbstractInstruction *'>
+ 	cogit AlignmentNops: (BytesPerWord max: 8).
+ 	entryLabel := cogit Label.
+ 	cogit MoveR: sourceReg R: destReg.
+ 	cogit AndCq: 1 R: destReg.
+ 	jumpIsInt := cogit JumpNonZero: 0.
+ 	"Get header word in destReg"
+ 	cogit MoveMw: 0 r: sourceReg R: destReg.
+ 	"Extract the compact class field, and if non-zero use it as the tag.."
+ 	self assert: self compactClassFieldMask << objectMemory compactClassFieldLSB < objectMemory nilObject.
+ 	cogit AndCq: self compactClassFieldMask << objectMemory compactClassFieldLSB R: destReg.
+ 	jumpCompact := cogit JumpNonZero: 0.
+ 	cogit MoveMw: objectMemory classFieldOffset r: sourceReg R: destReg.
+ 	"The use of signedIntFromLong is a hack to get round short addressing mode computations.
+ 	 Much easier if offsets are signed and the arithmetic machinery we have makes it difficult to
+ 	 mix signed and unsigned offsets."
+ 	cogit AndCq: AllButTypeMask signedIntFromLong R: destReg.
+ 	jumpCompact jmpTarget: (jumpIsInt jmpTarget: cogit Label).
+ 	^entryLabel!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>getInlineCacheClassTagFrom:into: (in category 'compile abstract instructions') -----
- getInlineCacheClassTagFrom: sourceReg into: destReg
- 	"Extract the inline cache tag for the object in sourceReg into destReg. The inline
- 	 cache tag for a given object is the value loaded in inline caches to distinguish objects
- 	 of different classes.  In SqueakV3 the tag is the integer tag bit for SmallIntegers (1),
- 	 the compact class index shifted by log: 2 word size for objects with compact classes
- 	 (1 * 4 to: 31 * 4 by: 4), or the class.  These ranges cannot overlap because the heap
- 	 (and hence the lowest class object) is beyond the machine code zone."
- 	| entryLabel jumpIsInt jumpCompact |
- 	<var: #entryLabel type: #'AbstractInstruction *'>
- 	<var: #jumpIsInt type: #'AbstractInstruction *'>
- 	<var: #jumpCompact type: #'AbstractInstruction *'>
- 	cogit AlignmentNops: (BytesPerWord max: 8).
- 	entryLabel := cogit Label.
- 	cogit MoveR: sourceReg R: destReg.
- 	cogit AndCq: 1 R: destReg.
- 	jumpIsInt := cogit JumpNonZero: 0.
- 	"Get header word in destReg"
- 	cogit MoveMw: 0 r: sourceReg R: destReg.
- 	"Form the byte index of the compact class field"
- 	cogit LogicalShiftRightCq: (objectMemory compactClassFieldLSB - ShiftForWord) R: destReg.
- 	cogit AndCq: self compactClassFieldMask << ShiftForWord R: destReg.
- 	jumpCompact := cogit JumpNonZero: 0.
- 	cogit MoveMw: objectMemory classFieldOffset r: sourceReg R: destReg.
- 	"The use of signedIntFromLong is a hack to get round short addressing mode computations.
- 	 Much easier if offsets are signed and the arithmetic machinery we have makes it difficult to
- 	 mix signed and unsigned offsets."
- 	cogit AndCq: AllButTypeMask signedIntFromLong R: destReg.
- 	jumpCompact jmpTarget: (jumpIsInt jmpTarget: cogit Label).
- 	^entryLabel!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>inlineCacheTagForClass: (in category 'in-line cacheing') -----
+ inlineCacheTagForClass: classOop
+ 	"Answer the relevant inline cache tag for a class.
+ 	 c.f. inlineCacheTagForInstance:"
+ 	| cci |
+ 	classOop = objectMemory classSmallInteger ifTrue:
+ 		[^objectMemory integerObjectOf: 0]. "the SmallInteger tag"
+ 	(cci :=  objectMemory noShiftCompactClassIndexOfHeader: (objectMemory formatOfClass: classOop)) > 0 ifTrue:
+ 		[^cci].
+ 	^classOop!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
  inlineCacheTagForInstance: oop
+ 	"Answer the relevant inline cache tag for an instance.
+ 	 c.f. getInlineCacheClassTagFrom:into: & inlineCacheTagForClass:"
- 	"c.f. getInlineCacheClassTagFrom:into:"
  	| cci |
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^objectMemory integerObjectOf: 0]. "the SmallInteger tag"
+ 	(cci :=  objectMemory noShiftCompactClassIndexOf: oop) > 0 ifTrue:
+ 		[^cci].
- 	(cci :=  objectMemory compactClassIndexOf: oop) > 0 ifTrue:
- 		[^cci << ShiftForWord].
  	^(objectMemory classHeader: oop) bitAnd: AllButTypeMask!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

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.		(self initialize)
- 	 a 32-bit architecture or 64-bits on a 64-bit architecture.  
  	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 with an absolute address
  		Ab		- memory byte with 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
  		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 |
  	FPReg := -1.
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3.
  	TempReg := -4.
  	ClassReg := -5.
  	SendNumArgsReg := -6.
  	Arg0Reg := -7.
  	Arg1Reg := GPRegMin := -8.
  
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  	
  	LinkReg := -17.
  	PCReg := -18.
  
  	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."
  
  						"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 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
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd 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 added:
+ ----- Method: Cogit>>ceImplicitReceiverFor:receiver: (in category 'in-line cacheing') -----
+ ceImplicitReceiverFor: selector receiver: receiver
+ 	"Cached implicit receiver implementation.  Caller looks like
+ 		mov selector, ClassReg
+ 				call ceImplicitReceiver
+ 				br continue
+ 		Lclass	.word
+ 		Lmixin:	.word
+ 		continue:
+ 	 The trampoline has already fetched the class and probed the cache and found
+ 	 that the cache missed.  Compute the implicit receiver for the receiver's class
+ 	 and reload the class tag.  If either the class tag or the mixin are young then the
+ 	 method needs to be added to the youngReferrers list to ensure correct GC."
+ 
+ 	| rcvrClass retpc classpc mixinpc mixin cogMethod |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	retpc := coInterpreter stackTop.
+ 	classpc := retpc + backEnd jumpShortByteSize.
+ 	mixinpc := retpc + backEnd jumpShortByteSize + BytesPerOop.
+ 	mixin := coInterpreter
+ 				implicitReceiverFor: receiver
+ 				mixin: coInterpreter mMethodClass
+ 				implementing: selector.
+ 	rcvrClass := objectMemory fetchClassOf: receiver.
+ 	cogMethod := coInterpreter mframeHomeMethodExport.
+ 	cogMethod cmRefersToYoung ifFalse:
+ 		[((objectRepresentation inlineCacheTagsMayBeObjects
+ 		   and: [objectMemory isYoung: rcvrClass])
+ 		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
+ 			[methodZone roomOnYoungReferrersList ifFalse:
+ 				[coInterpreter callForCogCompiledCodeCompaction.
+ 				 ^mixin].
+ 			 cogMethod cmRefersToYoung: true.
+ 			 methodZone addToYoungReferrers: cogMethod]].
+ 	backEnd
+ 		unalignedLongAt: classpc
+ 			put: (objectRepresentation inlineCacheTagForClass: rcvrClass);
+ 		unalignedLongAt: mixinpc
+ 			put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
+ 	^mixin!

Item was removed:
- ----- Method: Cogit>>ceImplicitReceiverFor:receiver:class: (in category 'in-line cacheing') -----
- ceImplicitReceiverFor: selector receiver: receiver class: rcvrClass
- 	"Cached implicit receiver implementation.  Caller looks like
- 		mov selector, ClassReg
- 				call ceImplicitReceiver
- 				br continue
- 		Lclass	.word
- 		Lmixin:	.word
- 		continue:
- 	 The trampoline has already fetched the class and probed the cache and found
- 	 that the cache missed.  Compute the implicit receiver for the receiver's class
- 	 and reload the class.  If either the class or the mixin are young the method needs
- 	 to be added to the youngReferrers list to ensure correct GC."
- 
- 	| retpc classpc mixinpc mixin cogMethod |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	retpc := coInterpreter stackTop.
- 	classpc := retpc + backEnd jumpShortByteSize.
- 	mixinpc := retpc + backEnd jumpShortByteSize + BytesPerOop.
- 	self assert: rcvrClass ~= (backEnd unalignedLongAt: classpc).
- 	mixin := coInterpreter
- 				implicitReceiverFor: receiver
- 				mixin: coInterpreter mMethodClass
- 				implementing: selector.
- 	cogMethod := coInterpreter mframeHomeMethodExport.
- 	cogMethod cmRefersToYoung ifFalse:
- 		[((objectMemory isYoung: rcvrClass)
- 		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
- 			[methodZone roomOnYoungReferrersList ifFalse:
- 				[coInterpreter callForCogCompiledCodeCompaction.
- 				 ^mixin].
- 			 cogMethod cmRefersToYoung: true.
- 			 methodZone addToYoungReferrers: cogMethod]].
- 	backEnd unalignedLongAt: classpc put: rcvrClass.
- 	backEnd unalignedLongAt: mixinpc put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
- 	^mixin!

Item was changed:
  ----- Method: Cogit>>compileCPICEntry (in category 'in-line cacheing') -----
  compileCPICEntry
  	<returnTypeC: #'AbstractInstruction *'>
  	"Compile the cache tag computation and the first comparison.  Answer the address of that comparison."
  	self cppIf: NewspeakVM ifTrue:
  		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
  		 dynSuperEntry := self Nop].
+ 	entry := objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: TempReg forEntry: true.
- 	entry := objectRepresentation getInlineCacheClassTagFrom: ReceiverResultReg into: TempReg.
  	self CmpR: ClassReg R: TempReg.
  	^self JumpNonZero: 0!

Item was changed:
  ----- Method: Cogit>>compileEntry (in category 'compile abstract instructions') -----
  compileEntry
  	"The entry code to a method checks that the class of the current receiver matches
  	 that in the inline cache.  Other non-obvious elements are that its alignment must be
  	 different from the alignment of the noCheckEntry so that the method map machinery
  	 can distinguish normal and super sends (super sends bind to the noCheckEntry).
  	 In Newspeak we also need to distinguish dynSuperSends from normal and super
  	 and so bind a the preceeding nop (on x86 there happens to be one anyway)."
  
  	self cppIf: NewspeakVM ifTrue:
  		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
  		 dynSuperEntry := self Nop].
+ 	entry := objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: TempReg forEntry: true.
- 	entry := objectRepresentation getInlineCacheClassTagFrom: ReceiverResultReg into: TempReg.
  	self CmpR: ClassReg R: TempReg.
  	self JumpNonZero: sendMiss.
  	noCheckEntry := self Label.
  	self recordSendTrace ifTrue:
  		[self CallRT: ceTraceLinkedSendTrampoline]!

Item was changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
  	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
  	ceExplicitReceiverTrampoline := self genTrampolineFor: #ceExplicitReceiverAt:
  										called: 'ceExplicitReceiverTrampoline'
  										arg: SendNumArgsReg
  										result: ReceiverResultReg.
  	"Cached push implicit receiver implementation.  Caller looks like
  				mov selector, ClassReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
+ 	 If class tag matches class of receiver then mixin contains either 0 or the implicit receiver.
- 	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver, otherwise the mixin.
+ 	 Generate the class fetch and cache probe inline for speed.
+ 	 Smashes Arg1Reg, RegClass and caller-saved regs."
- 	 Generate the class fetch and cache probe inline for speed. Smashes Arg0Reg and caller-saved regs."
  	opcodeIndex := 0.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	objectRepresentation
+ 		genGetInlineCacheClassTagFrom: ReceiverResultReg
- 		genGetClassObjectOf: ReceiverResultReg
  		into: ClassReg
+ 		forEntry: false.
- 		scratchReg: TempReg
- 		instRegIsReceiver: true. "don't follow forwarding pointer here"
  	self MoveMw: 0 r: SPReg R: TempReg.
  	self MoveMw: backEnd jumpShortByteSize r: TempReg R: Arg1Reg.
  	self CmpR: ClassReg R: Arg1Reg.
  	jumpMiss := self JumpNonZero: 0.
  	self MoveMw: backEnd jumpShortByteSize + BytesPerOop r: TempReg R: ClassReg.
  	self CmpCq: 0 R: ClassReg.
  	jumpItsTheReceiverStupid := self JumpZero: 0.
  	self MoveR: ClassReg R: ReceiverResultReg.
  	jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  	jumpMiss jmpTarget: self Label.
  	ceImplicitReceiverTrampoline := self
+ 										genTrampolineFor: #ceImplicitReceiverFor:receiver:
- 										genTrampolineFor: #ceImplicitReceiverFor:receiver:class:
  										called: 'ceImplicitReceiverTrampoline'
+ 										numArgs: 2
- 										numArgs: 3
  										arg: SendNumArgsReg
  										arg: ReceiverResultReg
- 										arg: ClassReg
  										arg: nil
+ 										arg: nil
  										saveRegs: false
  										pushLinkReg: true
  										resultReg: ReceiverResultReg
  										appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>markLiterals:pc:method: (in category 'garbage collection') -----
  markLiterals: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.
  	 Additionally in Newspeak, void push implicits that have unmarked classes."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteral: literal].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[objectRepresentation markAndTraceLiteral: cacheTag].  "cacheTag is selector"
  			  self cppIf: NewspeakVM ifTrue:
  				[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  					[| classpc mixinpc class mixin |
  					 classpc := mcpc asInteger + backEnd jumpShortByteSize.
  					 mixinpc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
  					 class := backEnd unalignedLongAt: classpc.
  					 class ~= 0
  						ifTrue:
+ 							[(objectRepresentation cacheTagIsMarked: class)
- 							[self assert: (objectMemory addressCouldBeObj: class).
- 							 (objectRepresentation cacheTagIsMarked: class)
  								ifTrue:
  									[(mixin := backEnd unalignedLongAt: mixinpc) ~= 0 ifTrue:
  										[objectRepresentation markAndTraceLiteral: mixin]]
  								ifFalse:
  									[backEnd
  										unalignedLongAt: classpc put: 0;
  										unalignedLongAt: mixinpc put: 0.
  									 codeModified := true]]
  						ifFalse:
  							[self assert: (backEnd unalignedLongAt: mixinpc) = 0]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteral: literal].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint into:
  						[:targetMethod :sendTable| | unlinkedRoutine |
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  							 backEnd
  								rewriteInlineCacheAt: mcpc asInteger
  								tag: targetMethod selector
  								target: unlinkedRoutine.
  							 codeModified := true.
  							 objectRepresentation markAndTraceLiteral: targetMethod selector]]]
  				ifFalse:
  					[objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
  					 self cppIf: NewspeakVM ifTrue:
  						[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  							[| classpc mixinpc class mixin |
  							 objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
  							 classpc := mcpc asInteger + backEnd jumpShortByteSize.
  							 mixinpc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
  							 class := backEnd unalignedLongAt: classpc.
  							 class ~= 0
  								ifTrue:
+ 									[(objectRepresentation cacheTagIsMarked: class)
- 									[self assert: (objectMemory addressCouldBeObj: class).
- 									 (objectRepresentation cacheTagIsMarked: class)
  										ifTrue:
  											[(mixin := backEnd unalignedLongAt: mixinpc) ~= 0 ifTrue:
  												[objectRepresentation markAndTraceLiteral: mixin]]
  										ifFalse:
  											[backEnd
  												unalignedLongAt: classpc put: 0;
  												unalignedLongAt: mixinpc put: 0.
  											 codeModified := true]]
  								ifFalse:
  									[self assert: (backEnd unalignedLongAt: mixinpc) = 0]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markYoungObjects:pc:method: (in category 'garbage collection') -----
  markYoungObjects: annotation pc: mcpc method: cogMethod
  	"Mark and trace young literals."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag].
  				 self cppIf: NewspeakVM ifTrue:
  					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  						[| class mixin |
  						 (class := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize) ~= 0 ifTrue:
+ 							[objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
+ 								[objectRepresentation markAndTraceLiteralIfYoung: class].
- 							[objectRepresentation markAndTraceLiteralIfYoung: class.
  							 mixin := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
  							 objectRepresentation markAndTraceLiteralIfYoung: mixin]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
  					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			 (self cppIf: NewspeakVM
  					ifTrue: [entryPoint = ceImplicitReceiverTrampoline]
  					ifFalse: [false])
+ 				ifTrue: "Examine an implicit receiver cache."
- 				ifTrue:
  					[| pc oop mappedOop |
  					 pc := mcpc asInteger + backEnd jumpShortByteSize.
  					 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
+ 						["First look at the classTag entry.  This is an inline cache tag and so might not be an object."
+ 						 (objectRepresentation inlineCacheTagsMayBeObjects
+ 						  and: [objectRepresentation couldBeObject: oop]) ifTrue:
+ 							[mappedOop := objectRepresentation remapOop: oop.
+ 							 mappedOop ~= oop ifTrue:
+ 								[backEnd unalignedLongAt: pc put: mappedOop].
+ 							 (hasYoungPtr ~= 0
+ 							  and: [objectMemory isYoung: mappedOop]) ifTrue:
+ 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
+ 						 "Second look at the mixin entry. this must be 0 or an objct."
- 						[mappedOop := objectRepresentation remapOop: oop.
- 						 mappedOop ~= oop ifTrue:
- 							[backEnd unalignedLongAt: pc put: mappedOop].
- 						 (hasYoungPtr ~= 0
- 						  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true].
  						 pc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
  						 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
  							[mappedOop := objectRepresentation remapOop: oop.
  							 mappedOop ~= oop ifTrue:
  								[backEnd unalignedLongAt: pc put: mappedOop].
+ 							 (hasYoungPtr ~= 0
+ 							  and: [objectMemory isYoung: mappedOop]) ifTrue:
+ 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
- 						 (hasYoungPtr ~= 0
- 						  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
  				ifFalse:
  					[hasYoungPtr ~= 0 ifTrue:
  						["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  						  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  						  the method must remain in youngReferrers if the targetMethod's selector is young."
  						 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  							[self targetMethodAndSendTableFor: entryPoint into:
  								[:targetMethod :ignored|
  								 (objectMemory isYoung: targetMethod selector) ifTrue:
  									[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSizeField (in category 'primitives-accessing') -----
  primSizeField
  	"Answer the signed 32-bit integer comprising the size field (the first 32-bit field)."
  	"<Alien> primSizeField ^<Integer>
  		<primitive: 'primSizeField' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	rcvr := interpreterProxy stackValue: 0.
+ 	value := (self longAt: rcvr + BaseHeaderSize) signedIntFromLong.
- 	value := self longAt: rcvr + BaseHeaderSize.
  	valueOop := interpreterProxy signed32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSizeFieldPut (in category 'primitives-accessing') -----
  primSizeFieldPut
  	"Store a signed integer into the size field (the first 32 bit field; little endian)."
  	"<Alien> sizeFieldPut: value <Integer> ^<Integer>
  		<primitive: 'primSizeFieldPut' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	rcvr := interpreterProxy stackValue: 1.
  	value := interpreterProxy signed32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 	self longAt: rcvr + BaseHeaderSize put: value signedIntToLong.
- 	self longAt: rcvr + BaseHeaderSize put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was added:
+ ----- Method: NewCoObjectMemory>>noShiftCompactClassIndexOf: (in category 'cog jit support') -----
+ noShiftCompactClassIndexOf: oop
+ 	<api>
+ 	^(self baseHeader: oop) bitAnd: 16r1F << self compactClassFieldLSB!

Item was removed:
- ----- Method: NewObjectMemory>>compactClassFieldLSB (in category 'cog jit support') -----
- compactClassFieldLSB
- 	<api>
- 	<cmacro: '() 12'>
- 	^12!

Item was changed:
  ----- Method: NewsqueakIA32ABIPlugin>>primSizeField (in category 'primitives-accessing') -----
  primSizeField
  	"Answer the signed 32-bit integer comprising the size field (the first 32-bit field)."
  	"<Alien> primSizeField ^<Integer>
  		<primitive: 'primSizeField' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	rcvr := interpreterProxy stackValue: 0.
+ 	value := (self longAt: rcvr + BaseHeaderSize) signedIntFromLong.
- 	value := self longAt: rcvr + BaseHeaderSize.
  	valueOop := interpreterProxy signed32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: NewsqueakIA32ABIPlugin>>primSizeFieldPut (in category 'primitives-accessing') -----
  primSizeFieldPut
  	"Store a signed integer into the size field (the first 32 bit field; little endian)."
  	"<Alien> sizeFieldPut: value <Integer> ^<Integer>
  		<primitive: 'primSizeFieldPut' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	rcvr := interpreterProxy stackValue: 1.
  	value := interpreterProxy signed32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(interpreterProxy isOopImmutable: rcvr) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
+ 	self longAt: rcvr + BaseHeaderSize put: value signedIntToLong.
- 	self longAt: rcvr + BaseHeaderSize put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: ObjectMemory class>>initializeSpecialObjectIndices (in category 'initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
+ 	ClassSmallInteger := 5.
- 	ClassInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	ClassBlockContext := 11.
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := 24.
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
  	SelectorCounterTripped := 58
  !

Item was changed:
  ----- Method: ObjectMemory>>classSmallInteger (in category 'plugin support') -----
  classSmallInteger
  	<api>
+ 	^self splObj: ClassSmallInteger!
- 	^self splObj: ClassInteger!

Item was added:
+ ----- Method: ObjectMemory>>compactClassFieldLSB (in category 'cog jit support') -----
+ compactClassFieldLSB
+ 	<api>
+ 	<cmacro: '() 12'>
+ 	^12!

Item was changed:
  ----- Method: ObjectMemory>>compactClassIndexOf: (in category 'header access') -----
  compactClassIndexOf: oop
  	<api>
  	<inline: true>
+ 	^((self baseHeader: oop) >> self compactClassFieldLSB) bitAnd: 16r1F!
- 	^((self baseHeader: oop) >> 12) bitAnd: 16r1F!

Item was changed:
  ----- Method: ObjectMemory>>compactClassIndexOfHeader: (in category 'header access') -----
  compactClassIndexOfHeader: header
  	<api>
  	<inline: true>
+ 	^(header >> self compactClassFieldLSB) bitAnd: 16r1F!
- 	^(header >> 12) bitAnd: 16r1F!

Item was changed:
  ----- Method: ObjectMemory>>fetchClassOf: (in category 'interpreter access') -----
  fetchClassOf: oop 
  	| ccIndex |
  	<inline: true>
  	<asmLabel: false>
  	^(self isIntegerObject: oop)
+ 		ifTrue: [self splObj: ClassSmallInteger]
- 		ifTrue: [self splObj: ClassInteger]
  		ifFalse:
  			[(ccIndex := (self compactClassIndexOf: oop)) = 0
  				ifTrue: [(self classHeader: oop) bitAnd: AllButTypeMask]
  				ifFalse: [self compactClassAt: ccIndex]]!

Item was added:
+ ----- Method: ObjectMemory>>noShiftCompactClassIndexOfHeader: (in category 'header access') -----
+ noShiftCompactClassIndexOfHeader: header
+ 	<api>
+ 	<inline: true>
+ 	^header bitAnd: 16r1F << self compactClassFieldLSB!

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpecialObjectIndices (in category 'class initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
+ 	ClassSmallInteger := 5.
- 	ClassInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	"ClassBlockContext := 11. unused by the VM"
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := nil.	"Must be unused by the VM"
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
  	SelectorCounterTripped := 58!

Item was changed:
  ----- Method: SpurMemoryManager>>classSmallInteger (in category 'accessing') -----
  classSmallInteger
+ 	^self splObj: ClassSmallInteger!
- 	^self splObj: ClassInteger!

Item was changed:
  ----- Method: SpurMemoryManager>>ensureBehaviorHash: (in category 'class table') -----
  ensureBehaviorHash: aBehavior
  	| newHash err |
+ 	<api>
  	<inline: true>
  	self assert: (coInterpreter addressCouldBeClassObj: aBehavior).
  	(newHash := self rawHashBitsOf: aBehavior) = 0 ifTrue:
  		[(err := self enterIntoClassTable: aBehavior) ~= 0 ifTrue:
  			[^err negated].
  		 newHash := self rawHashBitsOf: aBehavior.
  		 self assert: (self classAtIndex: newHash) = aBehavior].
  	^newHash!

Item was removed:
- ----- Method: StackDepthFinder>>alternateInterpretNextInstructionFor: (in category 'decoding') -----
- alternateInterpretNextInstructionFor: client
- 	joins at: pc put: stackp.
- 	^super alternateInterpretNextInstructionFor: client!

Item was added:
+ ----- Method: StackDepthFinder>>pushExplicitOuter: (in category 'instruction decoding') -----
+ pushExplicitOuter: level
+ 	"Push receiver for explcit outer, on Top Of Stack bytecode."
+ 	self push!

Item was added:
+ ----- Method: StackDepthFinder>>sendToAbsentDynamicSuperclass:numArgs: (in category 'instruction decoding') -----
+ sendToAbsentDynamicSuperclass: selector numArgs: numArgs
+ 	"Dynamic Superclass Send Message With Selector, selector, to absent implicit receiver bytecode."
+ 	self drop: numArgs - 1 "e.g. if no args pushes a result"!

Item was added:
+ ----- Method: StackDepthFinder>>sendToAbsentImplicitReceiver:numArgs: (in category 'instruction decoding') -----
+ sendToAbsentImplicitReceiver: selector numArgs: numArgs
+ 	"Send Message With Selector, selector, to absent implicit receiver bytecode."
+ 	self drop: numArgs - 1 "e.g. if no args pushes a result"!

Item was added:
+ ----- Method: VMMaker class>>generateAllNewspeakConfigurationsUnderVersionControl (in category 'configurations') -----
+ generateAllNewspeakConfigurationsUnderVersionControl
+ 	self generateNewspeakCogVM;
+ 		generateNewspeakSpurCogVM!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassInteger ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMObjectIndices commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define object layout and well-known objects shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self classPool declare: #Foo from: StackInterpreter classPool
  
  (ObjectMemory classPool keys select: [:k| (k beginsWith: 'Class') and: [(k endsWith: 'Index') not]]) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list