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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 11 20:51:31 UTC 2016


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

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

Name: VMMaker.oscog-eem.1915
Author: eem
Time: 11 August 2016, 1:49:36.374918 pm
UUID: fca185a9-541b-461c-9dd2-3c4dca0127d1
Ancestors: VMMaker.oscog-eem.1914

Spur:
Implement machine-code shallowCopy for Spur, excepting 0 slot objects, contexts, methods and objects with overflow size.

Fix the commentary for Xbr, X16r & X32r addressing modes.

Make sure that markAndTrace: is never inlined.

N.B. The 64-bit Cogit appears to be broken (an MNU early on, followed by a 0 arg to value: later in trying to report the MNU).  No time to fix it now.  When did it break I wonder?

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

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

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveShallowCopy (in category 'primitive generators') -----
+ genPrimitiveShallowCopy
+ 	"Implement primitiveShallowCopy/primitiveClone for convenient cases:
+ 	- the receiver is not a context
+ 	- the receiver is not a compiled method
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	| formatReg resultReg slotsReg ptrReg
+ 	  jumpImmediate jumpIsMethod jumpVariable jumpTooBig jumpEmpty jumpNoSpace
+ 	  continuance copyLoop |
+ 	<var: #continue type: #'AbstractInstruction *'>
+ 	<var: #copyLoop type: #'AbstractInstruction *'>
+ 	<var: #jumpTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpVariable type: #'AbstractInstruction *'>
+ 	<var: #jumpNoSpace type: #'AbstractInstruction *'>
+ 	<var: #jumpIsMethod type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	true ifTrue: [^UnimplementedPrimitive].
+ 	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
+ 	resultReg := Arg0Reg.
+ 	slotsReg := Arg1Reg.
+ 	"get freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self genGetFormatOf: ReceiverResultReg
+ 		into: (ptrReg := formatReg := SendNumArgsReg)
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 
+ 	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsMethod := cogit JumpAboveOrEqual: 0.
+ 	cogit CmpCq: objectMemory indexablePointersFormat R: formatReg.
+ 	jumpVariable := cogit JumpZero: 0.
+ 	continuance := cogit Label.
+ 
+ 	self genGetRawSlotSizeOfNonImm: ReceiverResultReg into: slotsReg.
+ 	cogit CmpCq: objectMemory numSlotsMask R: slotsReg.
+ 	jumpTooBig := cogit JumpZero: 0.
+ 
+ 	cogit CmpCq: 0 R: slotsReg.
+ 	jumpEmpty := cogit JumpZero: 0.
+ 
+ 	"round up to allocationUnit"
+ 	cogit
+ 		MoveR: slotsReg R: TempReg;
+ 		AndCq: 1 R: TempReg;
+ 		AddR: TempReg R: slotsReg;
+ 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: slotsReg;
+ 		LogicalShiftLeftCq: objectMemory shiftForWord R: slotsReg;
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 		AddR: resultReg R: slotsReg;
+ 		CmpCq: objectMemory getScavengeThreshold R: slotsReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	cogit
+ 		MoveR: resultReg R: ptrReg;
+ 	"write back new freeStart; get result. slotsReg holds new freeStart, the limit of the object"
+ 		MoveR: slotsReg Aw: objectMemory freeStartAddress;
+ 	"set up loop bounds"
+ 		SubCq: objectMemory wordSize * 2 R: slotsReg;
+ 	"copy header, masking off irrelevant bits"
+ 		MoveMw: 0 r: ReceiverResultReg R: TempReg;
+ 		AndCq: objectMemory formatMask << objectMemory formatShift + objectMemory classIndexMask R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: resultReg;
+ 		MoveMw: objectMemory wordSize r: ReceiverResultReg R: TempReg;
+ 		AndCq: objectMemory numSlotsMask << objectMemory numSlotsHalfShift R: TempReg;
+ 		MoveR: TempReg Mw: objectMemory wordSize r: resultReg.
+ 	"copy two fields at a time..."
+ 	copyLoop := cogit Label.
+ 	cogit
+ 		AddCq: objectMemory wordSize * 2 R: ReceiverResultReg;
+ 		AddCq: objectMemory wordSize * 2 R: ptrReg;
+ 		MoveMw: 0 r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: ptrReg;
+ 		MoveMw: objectMemory wordSize r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Mw: objectMemory wordSize r: ptrReg;
+ 		CmpR: ptrReg R: slotsReg;
+ 		JumpAbove: copyLoop;
+ 		MoveR: resultReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 
+ 	"If the receiver is variable pointers, fail if its a context, otherwise continue"
+ 	jumpVariable jmpTarget: cogit Label.
+ 	self genGetClassIndexOfNonImm: ReceiverResultReg into: ClassReg.
+ 	cogit
+ 		CmpCq: ClassMethodContextCompactIndex R: ClassReg;
+ 		JumpNonZero: continuance.
+ 
+ 	jumpImmediate jmpTarget:
+ 	(jumpNoSpace jmpTarget:
+ 	(jumpIsMethod jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpEmpty jmpTarget: cogit Label)))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveShallowCopy (in category 'primitive generators') -----
+ genPrimitiveShallowCopy
+ 	"Implement primitiveShallowCopy/primitiveClone for convenient cases:
+ 	- the receiver is not a context
+ 	- the receiver is not a compiled method
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	| formatReg resultReg slotsReg ptrReg
+ 	  jumpImmediate jumpIsMethod jumpVariable jumpTooBig jumpEmpty jumpNoSpace
+ 	  continuance copyLoop |
+ 	<var: #continue type: #'AbstractInstruction *'>
+ 	<var: #copyLoop type: #'AbstractInstruction *'>
+ 	<var: #jumpTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpVariable type: #'AbstractInstruction *'>
+ 	<var: #jumpNoSpace type: #'AbstractInstruction *'>
+ 	<var: #jumpIsMethod type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 
+ 	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
+ 	resultReg := Arg0Reg.
+ 	slotsReg := Arg1Reg.
+ 	"get freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self genGetFormatOf: ReceiverResultReg
+ 		into: (ptrReg := formatReg := SendNumArgsReg)
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 
+ 	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsMethod := cogit JumpAboveOrEqual: 0.
+ 	cogit CmpCq: objectMemory indexablePointersFormat R: formatReg.
+ 	jumpVariable := cogit JumpZero: 0.
+ 	continuance := cogit Label.
+ 
+ 	self genGetRawSlotSizeOfNonImm: ReceiverResultReg into: slotsReg.
+ 	cogit CmpCq: objectMemory numSlotsMask R: slotsReg.
+ 	jumpTooBig := cogit JumpZero: 0.
+ 
+ 	cogit CmpCq: 0 R: slotsReg.
+ 	jumpEmpty := cogit JumpZero: 0.
+ 
+ 	"compute byte size for slots"
+ 	cogit
+ 		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: slotsReg;
+ 		LogicalShiftLeftCq: objectMemory shiftForWord R: slotsReg;
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 		AddR: resultReg R: slotsReg;
+ 		CmpCq: objectMemory getScavengeThreshold R: slotsReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	cogit
+ 		MoveR: resultReg R: ptrReg;
+ 	"write back new freeStart; get result. slotsReg holds new freeStart, the limit of the object"
+ 		MoveR: slotsReg Aw: objectMemory freeStartAddress;
+ 	"set up loop bounds"
+ 		SubCq: objectMemory wordSize * 2 R: slotsReg;
+ 	"copy header, masking off irrelevant bits"
+ 		MoveMw: 0 r: ReceiverResultReg R: TempReg;
+ 		AndCq: (objectMemory
+ 					headerForSlots: objectMemory numSlotsMask
+ 					format: objectMemory formatMask
+ 					classIndex: objectMemory classIndexMask) R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: resultReg.
+ 	copyLoop := cogit Label.
+ 	cogit
+ 		AddCq: objectMemory wordSize R: ReceiverResultReg;
+ 		AddCq: objectMemory wordSize R: ptrReg;
+ 		MoveMw: 0 r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: ptrReg;
+ 		CmpR: ptrReg R: slotsReg;
+ 		JumpAbove: copyLoop;
+ 		MoveR: resultReg R: ReceiverResultReg;
+ 		genPrimReturn.
+ 
+ 	"If the receiver is variable pointers, fail if its a context, otherwise continue"
+ 	jumpVariable jmpTarget: cogit Label.
+ 	self genGetClassIndexOfNonImm: ReceiverResultReg into: ClassReg.
+ 	cogit
+ 		CmpCq: ClassMethodContextCompactIndex R: ClassReg;
+ 		JumpNonZero: continuance.
+ 
+ 	jumpImmediate jmpTarget:
+ 	(jumpNoSpace jmpTarget:
+ 	(jumpIsMethod jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpEmpty 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.
  	 The assembler is in Cogit protocol abstract instructions and uses `at&t' syntax, assigning to the register on the
  	 right. 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)
  		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
+ 		Xbr		- memory byte whose address is r * byte size away from an address in a register
+ 		X16r	- memory 16-bit halfword whose address is r * (2 bytes size) away from an address in a register
+ 		X32r	- memory 32-bit halfword whose address is r * (4 bytes size) away from an address in a register
- 		Xbr		- memory word whose address is r * byte size away from an address in a register
- 		X16r	- memory word whose address is r * (2 bytes size) away from an address in a register
- 		X32r	- memory word whose address is r * (4 bytes size) away from an address in a register
  		Xwr		- memory word whose address is r * word size away from an address in a register
  		Xowr	- memory word whose address is o + (r * word size) 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.  On processors such as MIPS this distinction is invalid; there are no
  	condition codes.  So the backend is allowed to collapse operation, branch pairs to internal instruciton definitions
  	(see sender and implementors of noteFollowingConditionalBranch:). 
  
  	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.
  
  	Not all instructions make sense on all architectures.  MoveRRd and MoveRdR aqre meaningful only on 64-bit machines.
  
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
  	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
  	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
  	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
  	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
  	they are used to call code in the C runtime, which may be distant from the code zone.  CallFull/JumpFull are allowed
  	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump).
  
  	Byte reads.  If the concrete compiler class answers true to byteReadsZeroExtend then byte reads must zero-extend
  	the byte read into the destination register.  If not, the other bits of the register should be left undisturbed and the
  	Cogit will add an instruction to zero the register as required.  Under no circumstances should byte reads sign-extend.
  
  	16-bit (and on 64-bits, 32-bit) reads.  These /are/ expected to always zero-extend."
  
  	| opcodeNames refs |
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						Fill32			"output four byte's worth of bytes with operand 0"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contigiuous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						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
  						MoveRRd MoveRdR 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
  						RotateLeftCqR RotateRightCqR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR
  						CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR
  
  						AndCqRR "Three address ops for RISCs; feel free to add and extend"
  
  						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 := JumpFull.
  	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: SimpleStackBasedCogit class>>initializePrimitiveTableForNewsqueak (in category 'class initialization') -----
  initializePrimitiveTableForNewsqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForNewsqueak"
  	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
  										ifTrue: [555]
  										ifFalse: [222].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
  		(2 genPrimitiveSubtract			1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1)
  		(10 genPrimitiveDivide			1)
  		(11 genPrimitiveMod			1)
  		(12 genPrimitiveDiv				1)
  		(13 genPrimitiveQuo			1)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift			1)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 genPrimitiveFloatAt)"
  		"(39 genPrimitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0)
  		(41 genPrimitiveFloatAdd				1)
  		(42 genPrimitiveFloatSubtract			1)
  		(43 genPrimitiveFloatLessThan			1)
  		(44 genPrimitiveFloatGreaterThan		1)
  		(45 genPrimitiveFloatLessOrEqual		1)
  		(46 genPrimitiveFloatGreaterOrEqual	1)
  		(47 genPrimitiveFloatEqual				1)
  		(48 genPrimitiveFloatNotEqual			1)
  		(49 genPrimitiveFloatMultiply			1)
  		(50 genPrimitiveFloatDivide				1)
  		"(51 genPrimitiveTruncated)"
  		"(52 genPrimitiveFractionalPart)"
  		"(53 genPrimitiveExponent)"
  		"(54 genPrimitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0)
  		"(56 genPrimitiveSine)"
  		"(57 genPrimitiveArctan)"
  		"(58 genPrimitiveLogN)"
  		"(59 genPrimitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew)				"For VMMirror support 1 argument instantiateFixedClass: as well as baiscNew"
  		(71 genPrimitiveNewWithArg)		"For VMMirror support 2 argument instantiateVariableClass:withSize: as well as baiscNew:"
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)			"For objectClass: and VMMirror support 1 argument classOf: as well as class"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
+ 		(148 genPrimitiveShallowCopy 0)			"a.k.a. clone"
+ 
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>value SmallFloat64>>asInteger"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
  		(541 genPrimitiveSmallFloatAdd				1)
  		(542 genPrimitiveSmallFloatSubtract			1)
  		(543 genPrimitiveSmallFloatLessThan			1)
  		(544 genPrimitiveSmallFloatGreaterThan		1)
  		(545 genPrimitiveSmallFloatLessOrEqual		1)
  		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
  		(547 genPrimitiveSmallFloatEqual				1)
  		(548 genPrimitiveSmallFloatNotEqual			1)
  		(549 genPrimitiveSmallFloatMultiply				1)
  		(550 genPrimitiveSmallFloatDivide				1)
  		"(551 genPrimitiveSmallFloatTruncated			0)"
  		"(552 genPrimitiveSmallFloatFractionalPart		0)"
  		"(553 genPrimitiveSmallFloatExponent			0)"
  		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
  		(555 genPrimitiveSmallFloatSquareRoot			0)
  		"(556 genPrimitiveSmallFloatSine				0)"
  		"(557 genPrimitiveSmallFloatArctan				0)"
  		"(558 genPrimitiveSmallFloatLogN				0)"
  		"(559 genPrimitiveSmallFloatExp				0)"
  	)!

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

Item was changed:
  ----- Method: SpurMemoryManager>>markAndTrace: (in category 'gc - global') -----
  markAndTrace: objOop
  	"Mark the argument, and all objects reachable from it, and any remaining objects
  	 on the mark stack. Follow forwarding pointers in the scan."
  	<api>
+ 	<inline: #never>
  	"if markAndTrace: is to follow and eliminate forwarding pointers
  	 in its scan it cannot be handed an r-value which is forwarded.
  	 The assert for this is in markAndShouldScan:"
  	(self markAndShouldScan: objOop) ifFalse:
  		[^self].
  
  	"Now scan the object, and any remaining objects on the mark stack."
  	self markLoopFrom: objOop!



More information about the Vm-dev mailing list