[Vm-dev] VM Maker: VMMaker.oscog.seperateMarking-WoC.3207.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jun 29 14:54:46 UTC 2022


Tom Braun uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog.seperateMarking-WoC.3207.mcz

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

Name: VMMaker.oscog.seperateMarking-WoC.3207
Author: WoC
Time: 29 June 2022, 4:54:19.037798 pm
UUID: 38b41253-526f-4015-8815-21870b2d6b3a
Ancestors: VMMaker.oscog-eem.3203, VMMaker.oscog.seperateMarking-eem.3206

Created abstract superclass for marking 

Added <cmacro: GIV(...)> where needed to keep the same semantic in generated code

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

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Utilities'!
+ SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!

Item was changed:
  SmartSyntaxInterpreterPlugin subclass: #BitBltSimulation
  	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight sourceWidth sourceHeight sourceDepth sourcePitch sourceBits sourcePPW sourceMSB destWidth destHeight destDepth destPitch destBits destPPW destMSB bitCount skew mask1 mask2 preload nWords destMask hDir vDir sourceIndex sourceDelta destIndex destDelta sx sy dx dy bbW bbH halftoneHeight noSource noHalftone halftoneBase sourceAlpha srcBitShift dstBitShift bitBltOop affectedL affectedR affectedT affectedB opTable maskTable ditherMatrix4x4 ditherThresholds16 ditherValues16 hasSurfaceLock warpSrcShift warpSrcMask warpAlignShift warpAlignMask warpBitShiftTable querySurfaceFn lockSurfaceFn unlockSurfaceFn isWarping cmFlags cmMask cmShiftTable cmMaskTable cmLookupTable cmBitsPerColor dither8Lookup componentAlphaModeColor componentAlphaModeAlpha ungammaLookupTable gammaLookupTable numGCsOnInvocation bitBltIsReceiver endOfDestination endOfSource'
  	classVariableNames: 'AllOnes AlphaIndex BBClipHeightIndex BBClipWidthIndex BBClipXIndex BBClipYIndex BBColorMapIndex BBDestFormIndex BBDestXIndex BBDestYIndex BBHalftoneFormIndex BBHeightIndex BBLastIndex BBRuleIndex BBSourceFormIndex BBSourceXIndex BBSourceYIndex BBWarpBase BBWidthIndex BBXTableIndex BEBitBltIndex BinaryPoint BlueIndex ColorMapFixedPart ColorMapIndexedPart ColorMapNewStyle ColorMapPresent CrossedX EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex OpTable OpTableSize RedIndex'
  	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins'!
- 	category: 'VMMaker-Interpreter'!
  
  !BitBltSimulation commentStamp: 'nice 10/31/2020 23:39' prior: 0!
  This class implements BitBlt, much as specified in the Blue Book spec.
  
  Performance has been enhanced through the use of pointer variables such as sourceIndex and destIndex, and by separating several special cases of the inner loop.
  
  Operation has been extended to color, with support for 1, 2, 4, 8, 16, and 32-bit pixel sizes.  Conversion between different pixel sizes is facilitated by accepting an optional color map.
  
  In addition to the original 16 combination rules, this BitBlt supports
  	16	fail (for old paint mode)
  	17	fail (for old mask mode)
  	18	sourceWord + destinationWord
  	19	sourceWord - destinationWord
  	20	rgbAdd: sourceWord with: destinationWord
  	21	rgbSub: sourceWord with: destinationWord
  	22	OLDrgbDiff: sourceWord with: destinationWord
  	23	OLDtallyIntoMap: destinationWord -- old vers doesn't clip to bit boundary
  	24	alphaBlend: sourceWord with: destinationWord
  	25	pixPaint: sourceWord with: destinationWord
  	26	pixMask: sourceWord with: destinationWord
  	27	rgbMax: sourceWord with: destinationWord
  	28	rgbMin: sourceWord with: destinationWord
  	29	rgbMin: sourceWord bitInvert32 with: destinationWord
  	30	alphaBlendConst: sourceWord with: destinationWord -- alpha passed as an arg
  	31	alphaPaintConst: sourceWord with: destinationWord -- alpha passed as an arg
  	32	rgbDiff: sourceWord with: destinationWord
  	33	tallyIntoMap: destinationWord
  	34	alphaBlendScaled: sourceWord with: destinationWord
  	35 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
  	36 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
  	37 rgbMul: sourceWord with: destinationWord
  	38 pixSwap: sourceWord with: destinationWord
  	39 pixClear: sourceWord with: destinationWord
  	40 fixAlpha: sourceWord with: destinationWord
  	41 rgbComponentAlpha: sourceWord with: destinationWord
  	42 alphaScale: ignoredSourceWord with: destinationWord
  	43 alphaUnscale: ignoredSourceWord with: destinationWord
  	44	alphaBlendUnscaled: sourceWord with: destinationWord
  
  This implementation has also been fitted with an experimental "warp drive" that allows abritrary scaling and rotation (and even limited affine deformations) with all BitBlt storage modes supported.
  
  To add a new rule to BitBlt...
  	1.  add the new rule method or methods in the category 'combination rules' of BBSim
  	2.  describe it in the class comment  of BBSim and in the class comment for BitBlt
  	3.  add refs to initializeRuleTable in proper positions
  	4.  add refs to initBBOpTable, following the pattern
  !

Item was changed:
  ----- Method: CCodeGenerator>>sortMethods: (in category 'utilities') -----
  sortMethods: aTMethodCollection
  	"We need to define this since different Squeak versions answer different results
  	 for asSortedCollection and if sort order changes, generated code changes too.
  	 When generating VM code, use class name as major sort index as this groups
  	 some methods by functionality (e.g. SpurGenerationScavenger) and that makes
  	 the VMProfiler more useful."
  	^aTMethodCollection asSortedCollection:
  		(self isGeneratingPluginCode
  			ifTrue:
  				[[:a :b| a selector caseSensitiveLessOrEqual: b selector]]
  			ifFalse:
  				[[:a :b|
+ 				  a definingClass sourceSortingKey = b definingClass sourceSortingKey
- 				  a definingClass = b definingClass
  					ifTrue: [a selector caseSensitiveLessOrEqual: b selector]
+ 					ifFalse: [a definingClass sourceSortingKey caseSensitiveLessOrEqual: b definingClass sourceSortingKey]]])!
- 					ifFalse: [a definingClass name caseSensitiveLessOrEqual: b definingClass name]]])!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----
+ primitiveNewPinnedInOldSpace
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
+ 			(objectMemory instantiateClass: self stackTop)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
+ 											ifTrue: [PrimErrNoMemory]
+ 											ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			["Allocate a new fixed-size instance. Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. May cause a GC."
+ 			| spaceOkay |
+ 			"The following may cause GC!! Use var for result to permit inlining."
+ 			spaceOkay := objectMemory
+ 								sufficientSpaceToInstantiate: self stackTop
+ 								indexableSize: 0.
+ 			spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory
+ 									instantiateClass: self stackTop
+ 									indexableSize: 0)]
+ 				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----
+ primitiveNewWithArgUninitialized
+ 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
+ 	| size spaceOkay instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
+ 			 spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
+ 				ifFalse:
+ 					[self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
  ObjectMemory subclass: #NewObjectMemory
  	instanceVariableNames: 'coInterpreter freeStart reserveStart scavengeThreshold needGCFlag edenBytes checkForLeaks statGCEndUsecs heapMap'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-V3MemoryManager'!
- 	category: 'VMMaker-Interpreter'!
  
  !NewObjectMemory commentStamp: '<historical>' prior: 0!
  I am a refinement of ObjectMemory that eliminates the need for pushRemappableOop:/popRemappableOop in the interpreter proper.  Certain primitives that do major allocation may still want to provoke a garbage collection and hence may still need to remap private pointers.  But the interpreter subclass of this class does not have to provided it reserves sufficient space for it to make progress to the next scavenge point (send or backward branch).!

Item was changed:
  VMClass subclass: #ObjectMemory
  	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount rootTableOverflowed extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount forceTenureFlag gcStartUsecs oldSpaceStart'
  	classVariableNames: 'AllButHashBits AllButImmutabilityBit AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit Done ExtraRootSize GCTopMarker HashBits HeaderTypeClass HeaderTypeExtraBytes HeaderTypeFree HeaderTypeGC LongSizeNumBits NilContext RemapBufferSize RootTableRedZone RootTableSize StartField StartObj Upward WeakRootTableSize WordMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3ObjectRepresentationConstants'
+ 	category: 'VMMaker-V3MemoryManager'!
- 	category: 'VMMaker-Interpreter'!
  
  !ObjectMemory commentStamp: '<historical>' prior: 0!
  This class describes a 32-bit direct-pointer object memory for Smalltalk.  The model is very simple in principle:  a pointer is either a SmallInteger or a 32-bit direct object pointer.
  
  SmallIntegers are tagged with a low-order bit equal to 1, and an immediate 31-bit 2s-complement signed value in the rest of the word.
  
  All object pointers point to a header, which may be followed by a number of data fields.  This object memory achieves considerable compactness by using a variable header size (the one complexity of the design).  The format of the 0th header word is as follows:
  
  	3 bits	reserved for gc (mark, root, unused)
  	12 bits	object hash (for HashSets)
  	5 bits	compact class index
  	4 bits	object format
  	6 bits	object size in 32-bit words
  	2 bits	header type (0: 3-word, 1: 2-word, 2: forbidden, 3: 1-word)
  
  If a class is in the compact class table, then this is the only header information needed.  If it is not, then it will have another header word at offset -4 bytes with its class in the high 30 bits, and the header type repeated in its low 2 bits.  It the objects size is greater than 255 bytes, then it will have yet another header word at offset -8 bytes with its full word size in the high 30 bits and its header type repeated in the low two bits.
  
  The object format field provides the remaining information as given in the formatOf: method (including isPointers, isVariable, isBytes, and the low 2 size bits of byte-sized objects).
  
  This implementation includes incremental (2-generation) and full garbage collection, each with compaction and rectification of direct pointers.  It also supports a bulk-become (exchange object identity) feature that allows many objects to be becomed at once, as when all instances of a class must be grown or shrunk.
  
  There is now a simple 64-bit version of the object memory.  It is the simplest possible change that could work.  It merely sign-extends all integer oops, and extends all object headers and oops by adding 32 zeroes in the high bits.  The format of the base header word is changed in one minor, not especially elegant, way.  Consider the old 32-bit header:
  	ggghhhhhhhhhhhhcccccffffsssssstt
  The 64-bit header is almost identical, except that the size field (now being in units of 8 bytes, has a zero in its low-order bit.  At the same time, the byte-size residue bits for byte objects, which are in the low order bits of formats 8-11 and 12-15, are now in need of another bit of residue.  So, the change is as follows:
  	ggghhhhhhhhhhhhcccccffffsssssrtt
  where bit r supplies the 4's bit of the byte size residue for byte objects.  Oh, yes, this is also needed now for 'variableWord' objects, since their size in 32-bit words requires a low-order bit.
  
  See the comment in formatOf: for the change allowing for 64-bit wide bitmaps, now dubbed 'variableLong'.!

Item was added:
+ SpurMarker subclass: #SpurAllAtOnceMarker
+ 	instanceVariableNames: 'marking'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'SpurObjStackConstants VMBasicConstants'
+ 	category: 'VMMaker-SpurMemoryManager'!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>implicitReturnTypeFor: (in category 'translation') -----
+ implicitReturnTypeFor: aSelector
+ 	"Answer the return type for methods that don't have an explicit return."
+ 	^#void!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>simulatorClass (in category 'simulation') -----
+ simulatorClass
+ 	^ SpurAllAtOnceMarkerSimulator!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>sourceSortingKey (in category 'translation') -----
+ sourceSortingKey
+ 	"To keep methods in the same order while refactoring..."
+ 	^SpurMemoryManager name!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>initialize (in category 'instance initialization') -----
+ initialize
+ 
+ 	marking := false!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAccessibleObjectsAndFireEphemerons (in category 'marking') -----
+ markAccessibleObjectsAndFireEphemerons
+ 	self assert: marking.
+ 	self assert: manager validClassTableRootPages.
+ 	self assert: manager segmentManager allBridgesMarked.
+ 	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
+ 		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
+ 
+ 	"This must come first to enable stack page reclamation.  It clears
+ 	  the trace flags on stack pages and so must precede any marking.
+ 	  Otherwise it will clear the trace flags of reached pages."
+ 	coInterpreter initStackPageGC.
+ 	self markAndTraceHiddenRoots.
+ 	self markAndTraceExtraRoots.
+ 	self assert: manager validClassTableRootPages.
+ 	coInterpreter markAndTraceInterpreterOops: true.
+ 	self assert: manager validObjStacks.
+ 	self markWeaklingsAndMarkAndFireEphemerons.
+ 	self assert: manager validObjStacks!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAllUnscannedEphemerons (in category 'weakness and ephemerality') -----
+ markAllUnscannedEphemerons
+ 	"After firing the unscanned ephemerons we must scan-mark them.
+ 	 The wrinkle is that doing so may add more ephemerons to the set.
+ 	 So we remove the first element, by overwriting it with the last element,
+ 	 and decrementing the top, and then markAndTrace its contents."
+ 	self assert: (manager noUnscannedEphemerons) not.
+ 	self assert: manager allUnscannedEphemeronsAreActive.
+ 	[manager unscannedEphemerons top > manager unscannedEphemerons start] whileTrue:
+ 		[| ephemeron key lastptr |
+ 		 ephemeron := manager longAt: manager unscannedEphemerons start.
+ 		 lastptr := manager unscannedEphemerons top - manager bytesPerOop.
+ 		 lastptr > manager unscannedEphemerons start ifTrue:
+ 			[manager longAt: manager unscannedEphemerons start put: (manager longAt: lastptr)].
+ 		 manager unscannedEphemerons top: lastptr.
+ 		 key := manager followedKeyOfMaybeFiredEphemeron: ephemeron.
+ 		 manager setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
+ 		 self
+ 			markAndTrace: key;
+ 			markAndTrace: ephemeron]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndShouldScan: (in category 'marking') -----
+ markAndShouldScan: objOop
+ 	"Helper for markAndTrace:.
+ 	 Mark the argument, and answer if its fields should be scanned now.
+ 	 Immediate objects don't need to be marked.
+ 	 Already marked objects have already been processed.
+ 	 Pure bits objects don't need scanning, although their class does.
+ 	 Weak objects should be pushed on the weakling stack.
+ 	 Anything else need scanning."
+ 	| format |
+ 	<inline: true>
+ 	(manager isImmediate: objOop) ifTrue:
+ 		[^false].
+ 	"if markAndTrace: is to follow and eliminate forwarding pointers
+ 	 in its scan it cannot be handed an r-value which is forwarded."
+ 	self assert: (manager isForwarded: objOop) not.
+ 	(manager isMarked: objOop) ifTrue:
+ 		[^false].
+ 	manager setIsMarkedOf: objOop to: true.
+ 	format := manager formatOf: objOop.
+ 	(manager isPureBitsFormat: format) ifTrue: "avoid pushing non-pointer objects on the markStack."
+ 		["Avoid tracing classes of non-objects on the heap, e.g. IRC caches, Sista counters."
+ 		 (manager classIndexOf: objOop) > manager lastClassIndexPun ifTrue:
+ 			[self markAndTraceClassOf: objOop].
+ 		 ^false].
+ 	(manager isWeakFormat: format) ifTrue: "push weaklings on the weakling stack to scan later"
+ 		[manager push: objOop onObjStack: manager weaklingStack.
+ 		 ^false].
+ 	((manager isEphemeronFormat: format)
+ 	 and: [manager activeAndDeferredScan: objOop]) ifTrue:
+ 		[^false].
+ 	^true!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTrace: (in category 'marking') -----
+ 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!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceClassOf: (in category 'marking') -----
+ markAndTraceClassOf: objOop
+ 	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
+ 	 And for one-way become, which can create duplicate entries in the class table, make sure
+ 	 objOop's classIndex refers to the classObj's actual classIndex.
+ 	 Note that this is recursive, but the metaclass chain should terminate quickly."
+ 	<inline: false>
+ 	| classIndex classObj realClassIndex |
+ 	classIndex := manager classIndexOf: objOop.
+ 	classObj := manager classOrNilAtIndex: classIndex.
+ 	self assert: (coInterpreter objCouldBeClassObj: classObj).
+ 	realClassIndex := manager rawHashBitsOf: classObj.
+ 	(classIndex ~= realClassIndex
+ 	 and: [classIndex > manager lastClassIndexPun]) ifTrue:
+ 		[manager setClassIndexOf: objOop to: realClassIndex].
+ 	(manager isMarked: classObj) ifFalse:
+ 		[manager setIsMarkedOf: classObj to: true.
+ 		 self markAndTraceClassOf: classObj.
+ 		 manager push: classObj onObjStack: manager markStack]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceExtraRoots (in category 'marking') -----
+ markAndTraceExtraRoots
+ 	| oop |
+ 	self assert: manager remapBufferCount = 0.
+ 
+ 	1 to: manager extraRootCount do:
+ 		[:i|
+ 		oop := (manager extraRoots at: i) at: 0.
+ 		((manager isImmediate: oop) or: [manager isFreeObject: oop]) ifFalse:
+ 			[self markAndTrace: oop]]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceHiddenRoots (in category 'marking') -----
+ markAndTraceHiddenRoots
+ 	"The hidden roots hold both the class table pages and the obj stacks,
+ 	 and hence need special treatment.  The obj stacks must be marked
+ 	 specially; their pages must be marked, but only the contents of the
+ 	 mournQueue should be marked.
+ 
+ 	 If a class table page is weak we can mark and trace the hiddenRoots,
+ 	 which will not trace through class table pages because they are weak.
+ 	 But if class table pages are strong, we must mark the pages and *not*
+ 	 trace them so that only classes reachable from the true roots will be
+ 	 marked, and unreachable classes will be left unmarked."
+ 
+ 	self markAndTraceObjStack: manager markStack andContents: false.
+ 	self markAndTraceObjStack: manager weaklingStack andContents: false.
+ 	self markAndTraceObjStack: manager mournQueue andContents: true.
+ 
+ 	manager setIsMarkedOf: manager rememberedSetObj to: true.
+ 	manager setIsMarkedOf: manager freeListsObj to: true.
+ 
+ 	(manager isWeakNonImm: manager classTableFirstPage) ifTrue:
+ 		[^self markAndTrace: manager hiddenRootsObj].
+ 
+ 	manager setIsMarkedOf: manager hiddenRootsObj to: true.
+ 	self markAndTrace: manager classTableFirstPage.
+ 	1 to: manager numClassTablePages - 1 do:
+ 		[:i| manager setIsMarkedOf: (manager fetchPointer: i ofObject: manager hiddenRootsObj)
+ 				to: true]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceObjStack:andContents: (in category 'marking') -----
+ markAndTraceObjStack: stackOrNil andContents: markAndTraceContents
+ 	"An obj stack is a stack of objects stored in a hidden root slot, such
+ 	 as the markStack or the ephemeronQueue.  It is a linked list of
+ 	 segments, with the hot end at the head of the list.  It is a word object.
+ 	 The stack pointer is in ObjStackTopx and 0 means empty."
+ 	<inline: false>
+ 	| index field |
+ 	stackOrNil = manager nilObj ifTrue:
+ 		[^self].
+ 	manager setIsMarkedOf: stackOrNil to: true.
+ 	self assert: (manager numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
+ 	field := manager fetchPointer: ObjStackNextx ofObject: stackOrNil.
+ 	field ~= 0 ifTrue:
+ 		[self markAndTraceObjStack: field andContents: markAndTraceContents].
+ 	field := stackOrNil.
+ 	[field := manager fetchPointer: ObjStackFreex ofObject: field.
+ 	 field ~= 0] whileTrue:
+ 		[manager setIsMarkedOf: field to: true].
+ 	markAndTraceContents ifFalse:
+ 		[^self].
+ 	"There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
+ 	  if there were 6 slots in an oop stack, full would be 2, and the last 0-rel index is 5."
+ 	index := (manager fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
+ 	[index >= ObjStackFixedSlots] whileTrue:
+ 		[field := manager followObjField: index ofObject: stackOrNil.
+ 		 (manager isImmediate: field) ifFalse:
+ 			[self markAndTrace: field].
+ 		 index := index - 1]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceWeaklingsFrom: (in category 'weakness and ephemerality') -----
+ markAndTraceWeaklingsFrom: startIndex
+ 	"Mark weaklings on the weaklingStack, ignoring startIndex
+ 	 number of elements on the bottom of the stack.  Answer
+ 	 the size of the stack *before* the enumeration began."
+ 	^manager objStack: manager weaklingStack from: startIndex do:
+ 		[:weakling|
+ 		 self deny: (manager isForwarded: weakling).
+ 		 self markAndTraceClassOf: weakling.
+ 		"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
+ 		 0 to: (manager numStrongSlotsOfWeakling: weakling) - 1 do:
+ 			[:i| | field |
+ 			field := manager followOopField: i ofObject: weakling.
+ 			((manager isImmediate: field) or: [manager isMarked: field]) ifFalse:
+ 				[self markAndTrace: field]]]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markInactiveEphemerons (in category 'weakness and ephemerality') -----
+ markInactiveEphemerons
+ 	"Go through the unscanned ephemerons, marking the inactive ones, and
+ 	 removing them from the unscanned ephemerons. Answer if any inactive
+ 	 ones were found. We cannot fire the ephemerons until all are found to
+ 	 be active since scan-marking an inactive ephemeron later in the set may
+ 	 render a previously-observed active ephemeron as inactive."
+ 	| foundInactive ptr |
+ 	foundInactive := false.
+ 	ptr := manager unscannedEphemerons start.
+ 	[ptr < manager unscannedEphemerons top] whileTrue:
+ 		[| ephemeron key |
+ 		 key := manager followedKeyOfEphemeron: (ephemeron := manager longAt: ptr).
+ 		 ((manager isImmediate: key) or: [manager isMarked: key])
+ 			ifTrue:
+ 				[foundInactive := true.
+ 				 "Now remove the inactive ephemeron from the set, and scan-mark it.
+ 				  Scan-marking it may add more ephemerons to the set."
+ 				 manager unscannedEphemerons top: manager unscannedEphemerons top - manager bytesPerOop.
+ 				 manager unscannedEphemerons top > ptr ifTrue:
+ 					[manager longAt: ptr put: (manager longAt: manager unscannedEphemerons top)].
+ 				 self markAndTrace: ephemeron]
+ 			ifFalse:
+ 				[ptr := ptr + manager bytesPerOop]].
+ 	^foundInactive!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markLoopFrom: (in category 'marking') -----
+ markLoopFrom: objOop
+ 	"Scan objOop and all objects on the mark stack, until the mark stack is empty.
+ 	 N.B. When the incremental GC is written this will probably be refactored as
+ 	 markLoopFrom: objOop while: aBlock"
+ 	<inline: true>
+ 	| objToScan field index numStrongSlots scanLargeObject |
+ 
+ 	"Now scan the object, and any remaining objects on the mark stack."
+ 	objToScan := objOop.
+ 	"To avoid overflowing the mark stack when we encounter large objects, we
+ 	 push the obj, then its numStrongSlots, and then index the object from the stack."
+ 	[(manager isImmediate: objToScan)
+ 		ifTrue: [scanLargeObject := true]
+ 		ifFalse:
+ 			[numStrongSlots := manager numStrongSlotsOfInephemeral: objToScan.
+ 			 scanLargeObject := numStrongSlots > self traceImmediatelySlotLimit].
+ 	 scanLargeObject
+ 		ifTrue: "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
+ 			[(manager isImmediate: objToScan)
+ 				ifTrue:
+ 					[index := manager integerValueOf: objToScan.
+ 					 objToScan := manager topOfObjStack: manager markStack]
+ 				ifFalse:
+ 					[index := numStrongSlots.
+ 					 self markAndTraceClassOf: objToScan].
+ 			 [index > 0] whileTrue:
+ 				[index := index - 1.
+ 				 field := manager fetchPointer: index ofObject: objToScan.
+ 				 (manager isNonImmediate: field) ifTrue:
+ 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
+ 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
+ 					 (self markAndShouldScan: field) ifTrue:
+ 						[index > 0 ifTrue:
+ 							[(manager topOfObjStack: manager markStack) ~= objToScan ifTrue: 
+ 								[manager push: objToScan onObjStack: manager markStack].
+ 							 manager push: (manager integerObjectOf: index) onObjStack: manager markStack].
+ 						 objToScan := field.
+ 						 index := -1]]].
+ 			 index >= 0 ifTrue: "if loop terminated without finding an unmarked referent, switch to top of stack."
+ 				[objToScan := manager popObjStack: manager markStack.
+ 				 objToScan = objOop ifTrue:
+ 					[objToScan := manager popObjStack: manager markStack]]]
+ 		ifFalse: "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
+ 			[index := numStrongSlots.
+ 			 self markAndTraceClassOf: objToScan.
+ 			 [index > 0] whileTrue:
+ 				[index := index - 1.
+ 				 field := manager fetchPointer: index ofObject: objToScan.
+ 				 (manager isNonImmediate: field) ifTrue:
+ 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
+ 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
+ 					 (self markAndShouldScan: field) ifTrue:
+ 						[manager push: field onObjStack: manager markStack.
+ 						 ((manager rawNumSlotsOf: field) > self traceImmediatelySlotLimit
+ 						  and: [(numStrongSlots := manager numStrongSlotsOfInephemeral: field) > self traceImmediatelySlotLimit]) ifTrue:
+ 							[manager push: (manager integerObjectOf: numStrongSlots) onObjStack: manager markStack]]]].
+ 			 objToScan := manager popObjStack: manager markStack].
+ 	 objToScan notNil] whileTrue!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markObjects: (in category 'marking') -----
+ markObjects: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
+ 	<inline: #never> "for profiling"
+ 	"Mark all accessible objects.  objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
+ 	 is true if all objects are unmarked and/or if unmarked classes shoud be removed from the class table."
+ 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
+ 	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'marking...'; flush].
+ 	manager runLeakCheckerFor: GCModeFull.
+ 
+ 	manager shutDownGlobalIncrementalGC: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
+ 	manager initializeUnscannedEphemerons.
+ 	manager initializeMarkStack.
+ 	manager initializeWeaklingStack.
+ 	marking := true.
+ 	self markAccessibleObjectsAndFireEphemerons.
+ 	manager expungeDuplicateAndUnmarkedClasses: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
+ 	manager nilUnmarkedWeaklingSlots.
+ 	marking := false!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markWeaklingsAndMarkAndFireEphemerons (in category 'weakness and ephemerality') -----
+ markWeaklingsAndMarkAndFireEphemerons
+ 	"After the initial scan-mark is complete ephemerons can be processed.
+ 	 Weaklings have accumulated on the weaklingStack, but more may be
+ 	 uncovered during ephemeron processing.  So trace the strong slots
+ 	 of the weaklings, and as ephemerons are processed ensure any newly
+ 	 reached weaklings are also traced."
+ 	| numTracedWeaklings |
+ 	<inline: false>
+ 	numTracedWeaklings := 0.
+ 	[coInterpreter markAndTraceUntracedReachableStackPages.
+ 	 coInterpreter markAndTraceMachineCodeOfMarkedMethods.
+ 	 "Make sure all reached weaklings have their strong slots traced before firing ephemerons..."
+ 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
+ 	  (manager sizeOfObjStack: manager weaklingStack) > numTracedWeaklings] whileTrue.
+ 	 manager noUnscannedEphemerons ifTrue:
+ 		[coInterpreter
+ 			markAndTraceUntracedReachableStackPages;
+ 	 		markAndTraceMachineCodeOfMarkedMethods;
+ 			freeUntracedStackPages;
+ 			freeUnmarkedMachineCode.
+ 		 ^self].
+ 	 self markInactiveEphemerons ifFalse:
+ 		[manager fireAllUnscannedEphemerons].
+ 	 self markAllUnscannedEphemerons]
+ 		repeat!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>marking (in category 'marking') -----
+ marking 
+ 	<cmacro: '() GIV(marking)'>
+ 	
+ 	^ marking!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>traceImmediatelySlotLimit (in category 'marking') -----
+ traceImmediatelySlotLimit
+ 	"Arbitrary level at which to defer tracing large objects until later.
+ 	 The average slot size of Smalltalk objects is typically near 8.
+ 	 We do require traceImmediatelySlotLimit to be < numSlotsMask."
+ 	^64!

Item was added:
+ SpurAllAtOnceMarker subclass: #SpurAllAtOnceMarkerSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was added:
+ SpurMarker subclass: #SpurIncrementalMarker
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!

Item was changed:
  CogClass subclass: #SpurMarker
+ 	instanceVariableNames: 'manager coInterpreter'
- 	instanceVariableNames: 'manager marking coInterpreter'
  	classVariableNames: ''
+ 	poolDictionaries: ''
- 	poolDictionaries: 'SpurObjStackConstants VMBasicConstants'
  	category: 'VMMaker-SpurMemoryManager'!

Item was removed:
- ----- Method: SpurMarker class>>simulatorClass (in category 'as yet unclassified') -----
- simulatorClass
- 	^SpurMarkerSimulator!

Item was changed:
  ----- Method: SpurMarker>>coInterpreter: (in category 'accessing') -----
  coInterpreter: aVMSimulator
  	<doNotGenerate>
+ 	
  	coInterpreter := aVMSimulator!

Item was removed:
- ----- Method: SpurMarker>>doMarkAndTrace: (in category 'as yet unclassified') -----
- doMarkAndTrace: objOop
- 	"Mark the argument, and all objects reachable from it, and any remaining objects
- 	 on the mark stack. Follow forwarding pointers in the scan."
- 	
- 	<inline: true>
- 	"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!

Item was removed:
- ----- Method: SpurMarker>>initialize (in category 'as yet unclassified') -----
- initialize
- 
- 	marking := false!

Item was changed:
  ----- Method: SpurMarker>>manager: (in category 'accessing') -----
  manager: aSpurNBitMMXEndianSimulator
  	<doNotGenerate>
  	manager := aSpurNBitMMXEndianSimulator.
  
  	aSpurNBitMMXEndianSimulator coInterpreter ifNotNil:
  		[:coint | coInterpreter := coint].!

Item was removed:
- ----- Method: SpurMarker>>markAccessibleObjectsAndFireEphemerons (in category 'as yet unclassified') -----
- markAccessibleObjectsAndFireEphemerons
- 	self assert: marking.
- 	self assert: manager validClassTableRootPages.
- 	self assert: manager segmentManager allBridgesMarked.
- 	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
- 		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
- 
- 	"This must come first to enable stack page reclamation.  It clears
- 	  the trace flags on stack pages and so must precede any marking.
- 	  Otherwise it will clear the trace flags of reached pages."
- 	coInterpreter initStackPageGC.
- 	self markAndTraceHiddenRoots.
- 	self markAndTraceExtraRoots.
- 	self assert: manager validClassTableRootPages.
- 	coInterpreter markAndTraceInterpreterOops: true.
- 	self assert: manager validObjStacks.
- 	self markWeaklingsAndMarkAndFireEphemerons.
- 	self assert: manager validObjStacks!

Item was removed:
- ----- Method: SpurMarker>>markAllUnscannedEphemerons (in category 'weakness and ephemerality') -----
- markAllUnscannedEphemerons
- 	"After firing the unscanned ephemerons we must scan-mark them.
- 	 The wrinkle is that doing so may add more ephemerons to the set.
- 	 So we remove the first element, by overwriting it with the last element,
- 	 and decrementing the top, and then markAndTrace its contents."
- 	self assert: (manager noUnscannedEphemerons) not.
- 	self assert: manager allUnscannedEphemeronsAreActive.
- 	[manager unscannedEphemerons top > manager unscannedEphemerons start] whileTrue:
- 		[| ephemeron key lastptr |
- 		 ephemeron := manager longAt: manager unscannedEphemerons start.
- 		 lastptr := manager unscannedEphemerons top - manager bytesPerOop.
- 		 lastptr > manager unscannedEphemerons start ifTrue:
- 			[manager longAt: manager unscannedEphemerons start put: (manager longAt: lastptr)].
- 		 manager unscannedEphemerons top: lastptr.
- 		 key := manager followedKeyOfMaybeFiredEphemeron: ephemeron.
- 		 manager setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
- 		 self
- 			doMarkAndTrace: key;
- 			doMarkAndTrace: ephemeron]!

Item was removed:
- ----- Method: SpurMarker>>markAndShouldScan: (in category 'as yet unclassified') -----
- markAndShouldScan: objOop
- 	"Helper for markAndTrace:.
- 	 Mark the argument, and answer if its fields should be scanned now.
- 	 Immediate objects don't need to be marked.
- 	 Already marked objects have already been processed.
- 	 Pure bits objects don't need scanning, although their class does.
- 	 Weak objects should be pushed on the weakling stack.
- 	 Anything else need scanning."
- 	| format |
- 	<inline: true>
- 	(manager isImmediate: objOop) ifTrue:
- 		[^false].
- 	"if markAndTrace: is to follow and eliminate forwarding pointers
- 	 in its scan it cannot be handed an r-value which is forwarded."
- 	self assert: (manager isForwarded: objOop) not.
- 	(manager isMarked: objOop) ifTrue:
- 		[^false].
- 	manager setIsMarkedOf: objOop to: true.
- 	format := manager formatOf: objOop.
- 	(manager isPureBitsFormat: format) ifTrue: "avoid pushing non-pointer objects on the markStack."
- 		["Avoid tracing classes of non-objects on the heap, e.g. IRC caches, Sista counters."
- 		 (manager classIndexOf: objOop) > manager lastClassIndexPun ifTrue:
- 			[self markAndTraceClassOf: objOop].
- 		 ^false].
- 	format = manager weakArrayFormat ifTrue: "push weaklings on the weakling stack to scan later"
- 		[manager push: objOop onObjStack: manager weaklingStack.
- 		 ^false].
- 	(format = manager ephemeronFormat
- 	 and: [manager activeAndDeferredScan: objOop]) ifTrue:
- 		[^false].
- 	^true!

Item was added:
+ ----- Method: SpurMarker>>markAndTrace: (in category 'marking') -----
+ markAndTrace: objOop
+ 
+ 	^ self subclassResponsibility!

Item was removed:
- ----- Method: SpurMarker>>markAndTraceClassOf: (in category 'as yet unclassified') -----
- markAndTraceClassOf: objOop
- 	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
- 	 And for one-way become, which can create duplicate entries in the class table, make sure
- 	 objOop's classIndex refers to the classObj's actual classIndex.
- 	 Note that this is recursive, but the metaclass chain should terminate quickly."
- 	<inline: false>
- 	| classIndex classObj realClassIndex |
- 	classIndex := manager classIndexOf: objOop.
- 	classObj := manager classOrNilAtIndex: classIndex.
- 	self assert: (coInterpreter objCouldBeClassObj: classObj).
- 	realClassIndex := manager rawHashBitsOf: classObj.
- 	(classIndex ~= realClassIndex
- 	 and: [classIndex > manager lastClassIndexPun]) ifTrue:
- 		[manager setClassIndexOf: objOop to: realClassIndex].
- 	(manager isMarked: classObj) ifFalse:
- 		[manager setIsMarkedOf: classObj to: true.
- 		 self markAndTraceClassOf: classObj.
- 		 manager push: classObj onObjStack: manager markStack]!

Item was removed:
- ----- Method: SpurMarker>>markAndTraceExtraRoots (in category 'as yet unclassified') -----
- markAndTraceExtraRoots
- 	| oop |
- 	self assert: manager remapBufferCount = 0.
- 
- 	1 to: manager extraRootCount do:
- 		[:i|
- 		oop := (manager extraRoots at: i) at: 0.
- 		((manager isImmediate: oop) or: [manager isFreeObject: oop]) ifFalse:
- 			[self doMarkAndTrace: oop]]!

Item was removed:
- ----- Method: SpurMarker>>markAndTraceHiddenRoots (in category 'as yet unclassified') -----
- markAndTraceHiddenRoots
- 	"The hidden roots hold both the class table pages and the obj stacks,
- 	 and hence need special treatment.  The obj stacks must be marked
- 	 specially; their pages must be marked, but only the contents of the
- 	 mournQueue should be marked.
- 
- 	 If a class table page is weak we can mark and trace the hiddenRoots,
- 	 which will not trace through class table pages because they are weak.
- 	 But if class table pages are strong, we must mark the pages and *not*
- 	 trace them so that only classes reachable from the true roots will be
- 	 marked, and unreachable classes will be left unmarked."
- 
- 	self markAndTraceObjStack: manager markStack andContents: false.
- 	self markAndTraceObjStack: manager weaklingStack andContents: false.
- 	self markAndTraceObjStack: manager mournQueue andContents: true.
- 
- 	manager setIsMarkedOf: manager rememberedSetObj to: true.
- 	manager setIsMarkedOf: manager freeListsObj to: true.
- 
- 	(manager isWeakNonImm: manager classTableFirstPage) ifTrue:
- 		[^self doMarkAndTrace: manager hiddenRootsObj].
- 
- 	manager setIsMarkedOf: manager hiddenRootsObj to: true.
- 	self doMarkAndTrace: manager classTableFirstPage.
- 	1 to: manager numClassTablePages - 1 do:
- 		[:i| manager setIsMarkedOf: (manager fetchPointer: i ofObject: manager hiddenRootsObj)
- 				to: true]!

Item was removed:
- ----- Method: SpurMarker>>markAndTraceObjStack:andContents: (in category 'as yet unclassified') -----
- markAndTraceObjStack: stackOrNil andContents: markAndTraceContents
- 	"An obj stack is a stack of objects stored in a hidden root slot, such
- 	 as the markStack or the ephemeronQueue.  It is a linked list of
- 	 segments, with the hot end at the head of the list.  It is a word object.
- 	 The stack pointer is in ObjStackTopx and 0 means empty."
- 	<inline: false>
- 	| index field |
- 	stackOrNil = manager nilObj ifTrue:
- 		[^self].
- 	manager setIsMarkedOf: stackOrNil to: true.
- 	self assert: (manager numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
- 	field := manager fetchPointer: ObjStackNextx ofObject: stackOrNil.
- 	field ~= 0 ifTrue:
- 		[self markAndTraceObjStack: field andContents: markAndTraceContents].
- 	field := stackOrNil.
- 	[field := manager fetchPointer: ObjStackFreex ofObject: field.
- 	 field ~= 0] whileTrue:
- 		[manager setIsMarkedOf: field to: true].
- 	markAndTraceContents ifFalse:
- 		[^self].
- 	"There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
- 	  if there were 6 slots in an oop stack, full would be 2, and the last 0-rel index is 5."
- 	index := (manager fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
- 	[index >= ObjStackFixedSlots] whileTrue:
- 		[field := manager followObjField: index ofObject: stackOrNil.
- 		 (manager isImmediate: field) ifFalse:
- 			[self doMarkAndTrace: field].
- 		 index := index - 1]!

Item was removed:
- ----- Method: SpurMarker>>markAndTraceWeaklingsFrom: (in category 'weakness and ephemerality') -----
- markAndTraceWeaklingsFrom: startIndex
- 	"Mark weaklings on the weaklingStack, ignoring startIndex
- 	 number of elements on the bottom of the stack.  Answer
- 	 the size of the stack *before* the enumeration began."
- 	^manager objStack: manager weaklingStack from: startIndex do:
- 		[:weakling|
- 		 self deny: (manager isForwarded: weakling).
- 		 self markAndTraceClassOf: weakling.
- 		"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
- 		 0 to: (manager numStrongSlotsOfWeakling: weakling) - 1 do:
- 			[:i| | field |
- 			field := manager followOopField: i ofObject: weakling.
- 			((manager isImmediate: field) or: [manager isMarked: field]) ifFalse:
- 				[self doMarkAndTrace: field]]]!

Item was removed:
- ----- Method: SpurMarker>>markInactiveEphemerons (in category 'weakness and ephemerality') -----
- markInactiveEphemerons
- 	"Go through the unscanned ephemerons, marking the inactive ones, and
- 	 removing them from the unscanned ephemerons. Answer if any inactive
- 	 ones were found. We cannot fire the ephemerons until all are found to
- 	 be active since scan-marking an inactive ephemeron later in the set may
- 	 render a previously-observed active ephemeron as inactive."
- 	| foundInactive ptr |
- 	foundInactive := false.
- 	ptr := manager unscannedEphemerons start.
- 	[ptr < manager unscannedEphemerons top] whileTrue:
- 		[| ephemeron key |
- 		 key := manager followedKeyOfEphemeron: (ephemeron := manager longAt: ptr).
- 		 ((manager isImmediate: key) or: [manager isMarked: key])
- 			ifTrue:
- 				[foundInactive := true.
- 				 "Now remove the inactive ephemeron from the set, and scan-mark it.
- 				  Scan-marking it may add more ephemerons to the set."
- 				 manager unscannedEphemerons top: manager unscannedEphemerons top - manager bytesPerOop.
- 				 manager unscannedEphemerons top > ptr ifTrue:
- 					[manager longAt: ptr put: (manager longAt: manager unscannedEphemerons top)].
- 				 self doMarkAndTrace: ephemeron]
- 			ifFalse:
- 				[ptr := ptr + manager bytesPerOop]].
- 	^foundInactive!

Item was removed:
- ----- Method: SpurMarker>>markLoopFrom: (in category 'as yet unclassified') -----
- markLoopFrom: objOop
- 	"Scan objOop and all objects on the mark stack, until the mark stack is empty.
- 	 N.B. When the incremental GC is written this will probably be refactored as
- 	 markLoopFrom: objOop while: aBlock"
- 	<inline: true>
- 	| objToScan field index numStrongSlots scanLargeObject |
- 
- 	"Now scan the object, and any remaining objects on the mark stack."
- 	objToScan := objOop.
- 	"To avoid overflowing the mark stack when we encounter large objects, we
- 	 push the obj, then its numStrongSlots, and then index the object from the stack."
- 	[(manager isImmediate: objToScan)
- 		ifTrue: [scanLargeObject := true]
- 		ifFalse:
- 			[numStrongSlots := manager numStrongSlotsOfInephemeral: objToScan.
- 			 scanLargeObject := numStrongSlots > self traceImmediatelySlotLimit].
- 	 scanLargeObject
- 		ifTrue: "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
- 			[(manager isImmediate: objToScan)
- 				ifTrue:
- 					[index := manager integerValueOf: objToScan.
- 					 objToScan := manager topOfObjStack: manager markStack]
- 				ifFalse:
- 					[index := numStrongSlots.
- 					 self markAndTraceClassOf: objToScan].
- 			 [index > 0] whileTrue:
- 				[index := index - 1.
- 				 field := manager fetchPointer: index ofObject: objToScan.
- 				 (manager isNonImmediate: field) ifTrue:
- 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
- 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
- 					 (self markAndShouldScan: field) ifTrue:
- 						[index > 0 ifTrue:
- 							[(manager topOfObjStack: manager markStack) ~= objToScan ifTrue: 
- 								[manager push: objToScan onObjStack: manager markStack].
- 							 manager push: (manager integerObjectOf: index) onObjStack: manager markStack].
- 						 objToScan := field.
- 						 index := -1]]].
- 			 index >= 0 ifTrue: "if loop terminated without finding an unmarked referent, switch to top of stack."
- 				[objToScan := manager popObjStack: manager markStack.
- 				 objToScan = objOop ifTrue:
- 					[objToScan := manager popObjStack: manager markStack]]]
- 		ifFalse: "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
- 			[index := numStrongSlots.
- 			 self markAndTraceClassOf: objToScan.
- 			 [index > 0] whileTrue:
- 				[index := index - 1.
- 				 field := manager fetchPointer: index ofObject: objToScan.
- 				 (manager isNonImmediate: field) ifTrue:
- 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
- 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
- 					 (self markAndShouldScan: field) ifTrue:
- 						[manager push: field onObjStack: manager markStack.
- 						 ((manager rawNumSlotsOf: field) > self traceImmediatelySlotLimit
- 						  and: [(numStrongSlots := manager numStrongSlotsOfInephemeral: field) > self traceImmediatelySlotLimit]) ifTrue:
- 							[manager push: (manager integerObjectOf: numStrongSlots) onObjStack: manager markStack]]]].
- 			 objToScan := manager popObjStack: manager markStack].
- 	 objToScan notNil] whileTrue!

Item was removed:
- ----- Method: SpurMarker>>markObjects: (in category 'as yet unclassified') -----
- markObjects: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
- 	<inline: #never> "for profiling"
- 	"Mark all accessible objects.  objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
- 	 is true if all objects are unmarked and/or if unmarked classes shoud be removed from the class table."
- 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
- 	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'marking...'; flush].
- 	manager runLeakCheckerFor: GCModeFull.
- 
- 	manager shutDownGlobalIncrementalGC: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
- 	manager initializeUnscannedEphemerons.
- 	manager initializeMarkStack.
- 	manager initializeWeaklingStack.
- 	marking := true.
- 	self markAccessibleObjectsAndFireEphemerons.
- 	manager expungeDuplicateAndUnmarkedClasses: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
- 	manager nilUnmarkedWeaklingSlots.
- 	marking := false!

Item was removed:
- ----- Method: SpurMarker>>markWeaklingsAndMarkAndFireEphemerons (in category 'weakness and ephemerality') -----
- markWeaklingsAndMarkAndFireEphemerons
- 	"After the initial scan-mark is complete ephemerons can be processed.
- 	 Weaklings have accumulated on the weaklingStack, but more may be
- 	 uncovered during ephemeron processing.  So trace the strong slots
- 	 of the weaklings, and as ephemerons are processed ensure any newly
- 	 reached weaklings are also traced."
- 	| numTracedWeaklings |
- 	<inline: false>
- 	numTracedWeaklings := 0.
- 	[coInterpreter markAndTraceUntracedReachableStackPages.
- 	 coInterpreter markAndTraceMachineCodeOfMarkedMethods.
- 	 "Make sure all reached weaklings have their strong slots traced before firing ephemerons..."
- 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
- 	  (manager sizeOfObjStack: manager weaklingStack) > numTracedWeaklings] whileTrue.
- 	 manager noUnscannedEphemerons ifTrue:
- 		[coInterpreter
- 			markAndTraceUntracedReachableStackPages;
- 	 		markAndTraceMachineCodeOfMarkedMethods;
- 			freeUntracedStackPages;
- 			freeUnmarkedMachineCode.
- 		 ^self].
- 	 self markInactiveEphemerons ifFalse:
- 		[manager fireAllUnscannedEphemerons].
- 	 self markAllUnscannedEphemerons]
- 		repeat!

Item was removed:
- ----- Method: SpurMarker>>marking (in category 'as yet unclassified') -----
- marking 
- 
- 	^ marking!

Item was removed:
- ----- Method: SpurMarker>>traceImmediatelySlotLimit (in category 'as yet unclassified') -----
- traceImmediatelySlotLimit
- 	"Arbitrary level at which to defer tracing large objects until later.
- 	 The average slot size of Smalltalk objects is typically near 8.
- 	 We do require traceImmediatelySlotLimit to be < numSlotsMask."
- 	^64!

Item was removed:
- SpurMarker subclass: #SpurMarkerSimulator
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses (in category 'translation') -----
  ancilliaryClasses
  	"Answer any extra classes to be included in the translation."
+ 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. SpurAllAtOnceMarker }, 
- 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. SpurMarker }, 
  		self compactorClass classesForTranslation,
  		SpurNewSpaceSpace withAllSubclasses
  		
  	!

Item was changed:
  ----- Method: SpurMemoryManager class>>markerClass (in category 'accessing class hierarchy') -----
  markerClass
  	"Answer the marking algorithm to use."
+ 	^Smalltalk classNamed: (InitializationOptions at: #markerClass ifAbsent: [#SpurAllAtOnceMarker])!
- 	^Smalltalk classNamed: (InitializationOptions at: #markerClass ifAbsent: [#SpurMarker])!

Item was changed:
  ----- Method: SpurMemoryManager>>classTableFirstPage (in category 'accessing') -----
  classTableFirstPage
+ 	<cmacro: '() GIV(classTableFirstPage)'>
+ 	
- 	<cmacro>
  	^classTableFirstPage!

Item was added:
+ ----- Method: SpurMemoryManager>>extraRootCount (in category 'accessing') -----
+ extraRootCount
+ 
+ 	^ extraRootCount!

Item was added:
+ ----- Method: SpurMemoryManager>>extraRoots (in category 'accessing') -----
+ extraRoots
+ 	<cmacro: '() GIV(extraRoots)'>
+ 	^ extraRoots!

Item was added:
+ ----- Method: SpurMemoryManager>>hiddenRootsObj (in category 'accessing') -----
+ hiddenRootsObj
+ 
+ 	^ hiddenRootsObj!

Item was added:
+ ----- Method: SpurMemoryManager>>lowSpaceThreshold (in category 'accessing') -----
+ lowSpaceThreshold
+ 
+ 	^ lowSpaceThreshold!

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. This behaviour is now
+ 	 extracted to the SpurMarker hierarchy, so bridge to it."
+ 	<doNotGenerate>
- 	 on the mark stack. Follow forwarding pointers in the scan."
- 	<api>
- 	<inline: #never>
  
+ 	^marker markAndTrace: objOop!
- 	marker doMarkAndTrace: objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>nilObj (in category 'accessing') -----
+ nilObj
+ 
+ 	^ nilObj!

Item was changed:
  ----- Method: SpurMemoryManager>>nilUnmarkedWeaklingSlots (in category 'weakness and ephemerality') -----
  nilUnmarkedWeaklingSlots
  	"Nil the unmarked slots in the weaklings on the
  	 weakling stack, finalizing those that lost references.
  	 Finally, empty the weaklingStack."
  	<inline: #never> "for profiling"
  	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'nilling...'; flush].
  	self eassert: [self allOldMarkedWeakObjectsOnWeaklingStack].
  	weaklingStack = nilObj ifTrue:
  		[^self].
  	self objStack: weaklingStack from: 0 do:
  		[:weakling| | anyUnmarked |
  		anyUnmarked := self nilUnmarkedWeaklingSlotsIn: weakling.
  		anyUnmarked ifTrue:
  			["fireFinalization: could grow the mournQueue and if so,
  			  additional pages must be marked to avoid being GC'ed."
+ 			 self assert: marking.
- 			 self assert: marker marking.
  			 coInterpreter fireFinalization: weakling]].
  	self emptyObjStack: weaklingStack!

Item was added:
+ ----- Method: SpurMemoryManager>>numClassTablePages (in category 'accessing') -----
+ numClassTablePages
+ 
+ 	^ numClassTablePages!

Item was added:
+ ----- Method: SpurMemoryManager>>unscannedEphemerons (in category 'accessing') -----
+ unscannedEphemerons
+ 	<cmacro: '() GIV(unscannedEphemerons)'>
+ 	^ unscannedEphemerons!

Item was added:
+ ----- Method: VMClass class>>sourceSortingKey (in category 'translation') -----
+ sourceSortingKey
+ 	"Answer the key used to sort methods when generating a source file. By
+ 	 default this is the name of the class, but can be overridden to alter the
+ 	 source order, for example to ensure that methods are emitted in the same
+ 	 order during a refactoring where methods are moved to different classes."
+ 	^self name!

Item was changed:
  VMBasicConstants subclass: #VMSpurObjectRepresentationConstants
  	instanceVariableNames: ''
  	classVariableNames: 'BecameActiveClassFlag BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag SpurPrimitiveAccessorDepthShift SpurPrimitiveFlagsMask'
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
- 	category: 'VMMaker-Interpreter'!

Item was changed:
  VMBasicConstants subclass: #VMSqueakV3ObjectRepresentationConstants
  	instanceVariableNames: ''
  	classVariableNames: 'AllButTypeMask CompactClassMask HashBitsOffset HashMaskUnshifted HeaderTypeShort HeaderTypeSizeAndClass ImmutabilityBit LongSizeMask MarkBit RootBit Size4Bit SizeMask TypeMask'
  	poolDictionaries: ''
+ 	category: 'VMMaker-V3MemoryManager'!
- 	category: 'VMMaker-Interpreter'!
  
+ !VMSqueakV3ObjectRepresentationConstants commentStamp: '<historical>' prior: 0!
- !VMSqueakV3ObjectRepresentationConstants commentStamp: '' prior: 0!
  I am a shared pool for the constants that define the Squeak V3 object representation shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self ensureClassPool
  self classPool declare: #AllButTypeMask from: VMObjectOffsets classPool
  (ObjectMemory classPool keys select: [:k| k includesSubString: 'Compact']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list