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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 23 04:17:49 UTC 2021


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

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

Name: VMMaker.oscog-eem.3109
Author: eem
Time: 22 November 2021, 8:17:34.602359 pm
UUID: 28141cc3-6a57-4a86-b9c2-383d8563851b
Ancestors: VMMaker.oscog-eem.3108

Cogit: add machine code versions of primtiiveSlotAt[Put] (used for instVarAt:[put:] in Spur) for Spur64.  This is mainly to reduce noise in Virtend crash log primitive traces, but is a lot faster.

Spur: Fix a bug in full GC with non-writable code zone.  The scavenge that comes immediately before the mark phase in a full GC needs to be done with GCModeNewSpace to ensure the Cogit's GC routines are invoked correctly.

In-image compilation: get it working again after recent changes.

Simulation: fix assigning the primitiveFunctionPointer from machine code.  The accessor needs to convert the illegal-address key into the relevant object.

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

Item was changed:
  ----- Method: CoInterpreter>>primitiveFunctionPointer: (in category 'cog jit support') -----
+ primitiveFunctionPointer: oopOrSimulatedTrampolineKey
+ 	"Used by the cogit to allow machine code primitives to set primitiveFunctionPointer"
- primitiveFunctionPointer: oop
- 	"Apparently not sent but is used in the simulator."
  	<doNotGenerate>
+ 	| value |
+ 	value := cogit simulatedTrampolines
+ 				at: oopOrSimulatedTrampolineKey
+ 				ifPresent: [:messageSendOrBlock|
+ 							messageSendOrBlock isMessageSend
+ 								ifTrue: [messageSendOrBlock selector]
+ 								ifFalse: [messageSendOrBlock]]
+ 				ifAbsent: [oopOrSimulatedTrampolineKey].
+ 	primitiveFunctionPointer := value!
- 	primitiveFunctionPointer := oop!

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

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

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveSlotAt (in category 'primitive generators') -----
+ genPrimitiveSlotAt
+ 	"Generate the code for primitive 173, instVarAt:. Defer to StackInterpreterPrimitives>>primitiveSlotAt for Contexts."
+ 	| formatReg nSlotsOrElementsReg convertToIntAndReturn
+ 	  jumpImmediate jumpBadIndex
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpIsMethod jumpIsContext
+ 	  jumpPointersOutOfBounds
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpLongsOutOfBounds
+ 	  jumpFailAlloc jumpNonPointers jumpToReturnLargeInteger |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 
+ 	nSlotsOrElementsReg := ClassReg.
+ 
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self genGetFormatOf: ReceiverResultReg
+ 		into: (formatReg := SendNumArgsReg)
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: nSlotsOrElementsReg.
+ 
+ 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
+ 		  0 = 0 sized objects (UndefinedObject True False et al)
+ 		  1 = non-indexable objects with inst vars (Point et al)
+ 		  2 = indexable objects with no inst vars (Array et al)
+ 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		  4 = weak indexable objects with inst vars (WeakArray et al)
+ 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		  6 unused, reserved for exotic pointer objects?
+ 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 		  8 unused, reserved for exotic non-pointer objects?
+ 		  9 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: formatReg.
+ 	jumpNonPointers := cogit JumpAboveOrEqual: 0.
+ 
+ 	cogit AndCq: objectMemory classIndexMask R: TempReg.
+ 	cogit CmpCq: ClassMethodContextCompactIndex R: TempReg.
+ 	jumpIsContext := cogit JumpZero: 0. "Fail to StackInterpreterPrimitives>>primitiveSlotAt for Context"
+ 
+ 	cogit CmpR: Arg1Reg R: nSlotsOrElementsReg.
+ 	jumpPointersOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	"index is (formatReg Arg1Reg (0-rel index) * wordSize + baseHeaderSize"
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpNonPointers jmpTarget:
+ 					(cogit CmpCq: objectMemory firstByteFormat R: formatReg).
+ 	jumpIsBytes := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpIsWords := cogit JumpAboveOrEqual: 0.
+ 
+ 	"fall through to objectMemory sixtyFourBitIndexableFormat"
+ 	cogit CmpR: Arg1Reg R: nSlotsOrElementsReg.
+ 	jumpLongsOutOfBounds := cogit JumpBelowOrEqual: 0.	
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ClassReg.
+ 	cogit MoveR: ClassReg R: TempReg.
+ 	cogit LogicalShiftRightCq: self numSmallIntegerBits - 1 R: TempReg. "If in range this is now 0"
+ 	(cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ 		[cogit CmpCq: 0 R: TempReg]. "N.B. FLAGS := ClassReg - 0"
+ 	jumpToReturnLargeInteger := cogit JumpNonZero: 0.
+ 	self genConvertIntegerInReg: ClassReg toSmallIntegerInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	jumpToReturnLargeInteger jmpTarget: cogit Label.
+ 	jumpFailAlloc := self genAlloc64BitPositiveIntegerValue: ClassReg into: SendNumArgsReg scratchReg: Extra0Reg scratchReg: TempReg.
+ 	cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: nSlotsOrElementsReg).
+ 		cogit AndCq: 7 R: formatReg R: TempReg.
+ 		cogit SubR: TempReg R: nSlotsOrElementsReg;
+ 		CmpR: Arg1Reg R: nSlotsOrElementsReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsMethod := cogit JumpAboveOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
+ 	cogit backEnd byteReadsZeroExtend
+ 		ifTrue:
+ 			[cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg]
+ 		ifFalse:
+ 			[cogit "formatReg already contains a value <= 16r1f, so no need to zero it"
+ 				MoveXbr: Arg1Reg R: ReceiverResultReg R: formatReg;
+ 				MoveR: formatReg R: ReceiverResultReg].
+ 	convertToIntAndReturn := cogit Label.
+ 	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: nSlotsOrElementsReg).
+ 		cogit AndCq: 3 R: formatReg.
+ 		cogit SubR: formatReg R: nSlotsOrElementsReg;
+ 		CmpR: Arg1Reg R: nSlotsOrElementsReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddR: Arg1Reg R: ReceiverResultReg.
+ 	cogit AddR: Arg1Reg R: ReceiverResultReg.
+ 	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit Jump: convertToIntAndReturn.
+ 
+ 	jumpIsWords jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: nSlotsOrElementsReg).
+ 		cogit AndCq: 1 R: formatReg.
+ 		cogit SubR: formatReg R: nSlotsOrElementsReg;
+ 		CmpR: Arg1Reg R: nSlotsOrElementsReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >>  (objectMemory shiftForWord - 1) R: Arg1Reg.
+ 	cogit MoveX32r: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit Jump: convertToIntAndReturn.
+ 
+ 	jumpFailAlloc jmpTarget:
+ 	(jumpLongsOutOfBounds jmpTarget:
+ 	(jumpPointersOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpIsMethod jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpIsContext jmpTarget:
+ 	(jumpBadIndex jmpTarget:
+ 	(jumpImmediate jmpTarget: cogit Label))))))))).
+ 
+ 	^0 "Can't be complete because of contexts."!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveSlotAtPut (in category 'primitive generators') -----
+ genPrimitiveSlotAtPut
+ 	"Generate the code for primitive 174, instVarAt:put:. Defer to StackInterpreterPrimitives>>primitiveSlotAtPut for Contexts."
+ 	| formatReg nSlotsOrBytesReg
+ 	  jumpImmediate jumpBadIndex jumpImmutable jumpNotIndexableBits
+ 	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpIsShorts jumpIsWords
+ 	  jumpPointersOutOfBounds jumpWordsOutOfBounds jumpShortsOutOfBounds jumpBytesOutOfBounds
+ 	  jumpShortsOutOfRange jumpWordsOutOfRange jumpBytesOutOfRange
+ 	  jumpNonSmallIntegerValue jumpNotPointers
+ 	  rejoin jump64BitsOutOfBounds jumpNot64BitIndexable jump64BitArgIsImmediate jumpNot8ByteInteger
+ 	  |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	nSlotsOrBytesReg := Extra0Reg.
+ 
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
+ 	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue:
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
+ 		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
+ 		ifFalse: 
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: nSlotsOrBytesReg.
+ 
+ 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
+ 		  0 = 0 sized objects (UndefinedObject True False et al)
+ 		  1 = non-indexable objects with inst vars (Point et al)
+ 		  2 = indexable objects with no inst vars (Array et al)
+ 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		  4 = weak indexable objects with inst vars (WeakArray et al)
+ 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		  6 unused, reserved for exotic pointer objects?
+ 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 		  8 unused, reserved for exotic non-pointer objects?
+ 		  9 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
+ 	jumpNotPointers := cogit JumpAbove: 0.
+ 	self genGetClassIndexOfNonImm: ReceiverResultReg into: ClassReg.
+ 	cogit CmpCq: ClassMethodContextCompactIndex R: ClassReg.
+ 	jumpIsContext := cogit JumpZero: 0. "Fail to StackInterpreterPrimitives>>primitiveSlotAtPut for Context"
+ 
+ 	"optimistic store check; assume index in range (almost always is)."
+ 	self genStoreCheckReceiverReg: ReceiverResultReg
+ 		valueReg: Arg1Reg
+ 		scratchReg: TempReg
+ 		inFrame: false.
+ 
+ 	cogit CmpR: Arg0Reg R: nSlotsOrBytesReg.
+ 	jumpPointersOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpNotPointers jmpTarget: cogit Label.
+ 	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
+ 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpIsWords := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: formatReg.
+ 	jumpNotIndexableBits := cogit JumpNonZero: 0.
+ 	"fall through to 64-bit words"
+ 	cogit MoveR: Arg1Reg R: SendNumArgsReg.
+ 	self genConvertSmallIntegerToIntegerInReg: SendNumArgsReg.
+ 	rejoin :=
+ 	cogit CmpR: Arg0Reg R: nSlotsOrBytesReg.
+ 	jump64BitsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: SendNumArgsReg Xwr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	"Handle LargePositiveInteger (unsigned) or LargePositiveInteger and LargeNegativeInteger (signed)
+ 	 for sixtyFourBitIndexableFormat"
+ 	jumpNonSmallIntegerValue jmpTarget:
+ 		(cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: formatReg).
+ 	jumpNot64BitIndexable := cogit JumpNonZero: 0.
+ 	jump64BitArgIsImmediate := self genJumpImmediate: Arg1Reg.
+ 	"Now check if the header is that of an 8 byte LargePositiveInteger"
+ 	cogit MoveMw: 0 r: Arg1Reg R: SendNumArgsReg.
+ 	cogit AndCq: (objectMemory
+ 						headerForSlots: objectMemory numSlotsMask
+ 						format: objectMemory formatMask
+ 						classIndex: objectMemory classIndexMask)
+ 		R: SendNumArgsReg.
+ 	cogit CmpCq: (objectMemory
+ 						headerForSlots: 1
+ 						format: objectMemory firstByteFormat
+ 						classIndex: ClassLargePositiveIntegerCompactIndex)
+ 		R: SendNumArgsReg.
+ 	jumpNot8ByteInteger := cogit JumpNonZero: 0.
+ 	cogit MoveMw: objectMemory baseHeaderSize r: Arg1Reg R: SendNumArgsReg.
+ 	cogit Jump: rejoin.
+ 
+ 	jumpIsWords jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 16rFFFFFFFF) R: Arg1Reg).
+ 	jumpWordsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: nSlotsOrBytesReg.
+ 	cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: nSlotsOrBytesReg.
+ 	cogit CmpR: Arg0Reg R: nSlotsOrBytesReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize >> (objectMemory shiftForWord - 1) R: Arg0Reg.
+ 	cogit MoveR: TempReg X32r: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
+ 	jumpShortsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: nSlotsOrBytesReg.
+ 	cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: nSlotsOrBytesReg.
+ 	cogit CmpR: Arg0Reg R: nSlotsOrBytesReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 255) R: Arg1Reg).
+ 	jumpBytesOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: nSlotsOrBytesReg.
+ 	cogit AndCq: objectMemory wordSize - 1 R: formatReg R: TempReg.
+ 	cogit SubR: TempReg R: nSlotsOrBytesReg.
+ 	cogit CmpR: Arg0Reg R: nSlotsOrBytesReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
+ 	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	
+ 	jumpNot8ByteInteger jmpTarget:
+ 	(jump64BitArgIsImmediate jmpTarget:
+ 	(jumpNot64BitIndexable jmpTarget:
+ 	(jumpIsContext jmpTarget:
+ 	(jumpNotIndexableBits jmpTarget:
+ 	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpShortsOutOfRange jmpTarget:
+ 	(jumpWordsOutOfRange jmpTarget:
+ 	(jumpIsCompiledMethod jmpTarget:
+ 	(jumpPointersOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jump64BitsOutOfBounds jmpTarget: cogit Label))))))))))))).
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable jmpTarget: jumpIsContext getJmpTarget].
+ 
+ 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
+ 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
+ 
+ 	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
+ 
+ 	^0 "Can't be complete because of contexts."!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>initialCStackAddress (in category 'accessing') -----
+ initialCStackAddress
+ 	^self rumpCStackAddress!

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

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

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

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: [575]
  										ifFalse: [575].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
+ 		(2 genPrimitiveSubtract		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)
- 		(17 genPrimitiveBitShift			1)
  		(18 genPrimitiveMakePoint		1)	"this is here mainly to remove noise from printPrimTraceLog()"
  		"(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)
- 		(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"
- 		(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)"
  
  		"(90 primitiveMousePoint)"
  		"(91 primitiveTestDisplayDepth)"			"Blue Book: primitiveCursorLocPut"
  		"(92 primitiveSetDisplayMode)"				"Blue Book: primitiveCursorLink"
  		"(93 primitiveInputSemaphore)"
  		"(94 primitiveGetNextEvent)"				"Blue Book: primitiveSampleInterval"
  		"(95 primitiveInputWord)"
  		"(96 primitiveFail)"	"primitiveCopyBits"
  		"(97 primitiveSnapshot)"
  		"(98 primitiveStoreImageSegment)"
  		"(99 primitiveLoadImageSegment)"
  		"(100 primitivePerformInSuperclass)"		"Blue Book: primitiveSignalAtTick"
  		"(101 primitiveBeCursor)"
  		"(102 primitiveBeDisplay)"
  		"(103 primitiveScanCharacters)"
  		"(104 primitiveFail)"	"primitiveDrawLoop"
  		(105 genPrimitiveStringReplace)
  		"(106 primitiveScreenSize)"
  		"(107 primitiveMouseButtons)"
  		"(108 primitiveKbdNext)"
  		"(109 primitiveKbdPeek)"
  
  
  		"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"
  
  		(158 genPrimitiveStringCompareWith 1)
  		(159 genPrimitiveHashMultiply 0)
  
  		(165 genPrimitiveIntegerAt			1)	"Signed version of genPrimitiveAt"
  		(166 genPrimitiveIntegerAtPut		2)	"Signed version of genPrimitiveAtPut"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>asInteger/hash/identityHash, SmallFloat64>>identityHash"
  			
+ 		(173 genPrimitiveSlotAt 1)				"Good for micro-benchmark performance, and for reducing noise in Croquet primitive trace logs"
+ 		(174 genPrimitiveSlotAtPut 2)			"ditto"
- 		"(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)"
  		(575 genPrimitiveHighBit			0)
  	)!

Item was changed:
  ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
  globalGarbageCollect
  	<inline: true> "inline into fullGC"
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  
  	"Mark objects /before/ scavenging, to empty the rememberedTable of unmarked roots."
  	self markObjects: true.
  	gcMarkEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	
  	scavenger forgetUnmarkedRememberedObjects.
+ 
+ 	coInterpreter setGCMode: GCModeNewSpace.
  	self doScavenge: MarkOnTenure.
+ 	coInterpreter setGCMode: GCModeFull.
  
  	"Mid-way the leak check must be more lenient.  Unmarked classes will have been
  	 expunged from the table, but unmarked instances will not yet have been reclaimed."
  	self runLeakCheckerFor: GCModeFull
  		excludeUnmarkedObjs: true
  		classIndicesShouldBeValid: true.
  
  	compactionStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  	segmentManager prepareForGlobalSweep. "for notePinned:"
  	compactor compact.
  	self attemptToShrink.
  	self setHeapSizeAtPreviousGC.
  
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  	self assert: self allObjectsUnmarked.
  	self runLeakCheckerFor: GCModeFull!



More information about the Vm-dev mailing list