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

commits at source.squeak.org commits at source.squeak.org
Sun Jul 20 05:30:46 UTC 2014


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

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

Name: VMMaker.oscog-eem.827
Author: eem
Time: 19 July 2014, 12:02:03.653 pm
UUID: 22325940-3a8c-40fc-9331-a9c37c875bbd
Ancestors: VMMaker.oscog-eem.826

Spur:
Move the rememberedSet into a pinned object in oldSpace.
Allow it to grow on demand, starting at 1k entries, doubling
on each grow.

Allow the number of compaction passes to vary, 2 on GC,
3 on GC for snapshot.

Add vm parameter 53 to answer the number of segments.

Slang:
Add support for deny:, and implement it in VMClass.

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

Item was added:
+ ----- Method: CCodeGenerator>>generateDeny:on:indent: (in category 'C translation') -----
+ generateDeny: denyMsgNode on: aStream indent: level
+ 	"Generate the C code for a deny: expr onto the given stream."
+ 
+ 	aStream nextPutAll: 'assert(!!('.
+ 	self emitCExpression: denyMsgNode args first on: aStream.
+ 	aStream nextPutAll: '))'!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
  	#rounded			#generateRounded:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#addressOf:put:			#generateAddressOf:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asVoidPointer				#generateAsVoidPointer:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  	#value:value:value:					#generateValue:on:indent:
  
+ 	#deny:								#generateDeny:on:indent:
+ 
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: CCodeGenerator>>isAssertSelector: (in category 'inlining') -----
  isAssertSelector: selector
+ 	^#(assert: asserta: assert:l: asserta:l: deny:) includes: selector!
- 	^#(assert: asserta: assert:l: asserta:l:) includes: selector!

Item was changed:
  CogClass subclass: #SpurGenerationScavenger
+ 	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize rememberedSetRedZone rememberedSetLimit weakList ephemeronList tenureCriterion tenureThreshold tenuringClassIndex tenuringProportion numRememberedEphemerons statTenures'
+ 	classVariableNames: ''
- 	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize weakList ephemeronList tenureCriterion tenureThreshold tenuringClassIndex tenuringProportion numRememberedEphemerons statTenures'
- 	classVariableNames: 'RememberedSetLimit RememberedSetRedZone'
  	poolDictionaries: 'SpurMemoryManagementConstants'
  	category: 'VMMaker-SpurMemoryManager'!
  
  !SpurGenerationScavenger commentStamp: 'eem 9/30/2013 11:05' prior: 0!
  SpurGenerationScavenger is an implementation of David Ungar's Generation Scavenging garbage collection algorithm.  See
  	Generation Scavenging, A Non-disruptive, High-Performance Storage Reclamation Algorithm
  	David Ungar
  	Proceeding
  	SDE 1 Proceedings of the first ACM SIGSOFT/SIGPLAN software engineering symposium on Practical software development environments
  	Pages 157 - 167 
  	ACM New York, NY, USA ©1984 
  
  Also relevant are
  	An adaptive tenuring policy for generation scavengers
  	David Ungar & Frank Jackson
  	ACM Transactions on Programming Languages and Systems (TOPLAS) TOPLAS Homepage archive
  	Volume 14 Issue 1, Jan. 1992 
  	Pages 1 - 27 
  	ACM New York, NY, USA ©1992
  and
  	Ephemerons: a new finalization mechanism
  	Barry Hayes
  	Proceedings of the 12th ACM SIGPLAN conference on Object-oriented programming, systems, languages, and applications
  	Pages 176-183 
  	ACM New York, NY, USA ©1997
  
  See text below the variable definitions and explanation below for a full explanation of weak and ephemeron processing.
  
  Instance Variables
  	coInterpreter:					<StackInterpreterSimulator|CogVMSimulator>
  	eden:							<SpurNewSpaceSpace>
  	ephemeronList:					<Integer|nil>
  	futureSpace:					<SpurNewSpaceSpace>
  	futureSurvivorStart:				<Integer address>
  	manager:						<SpurMemoryManager|Spur32BitMMLESimulator et al>
  	numRememberedEphemerons:	<Integer>
  	pastSpace:						<SpurNewSpaceSpace>
  	previousRememberedSetSize:	<Integer>
  	rememberedSet:				<CArrayAccessor on: Array>
  	rememberedSetSize:			<Integer>
  	tenuringProportion:				<Float>
  	tenuringThreshold:				<Integer address>
  	weakList:						<Integer|nil>
  
  coInterpreter
  	- the interpreter/vm, in this context, the mutator
  
  manager
  	- the Spur memory manager
  
  eden
  	- the space containing newly created objects
  
  futureSpace
  	- the space to which surviving objects are copied during a scavenge
  
  futureSurvivorStart
  	- the allocation pointer into futureSpace
  
  pastSpace
  	- the space surviving objects live in until the next scavenge
  
  rememberedSet
  	- the root old space objects that refer to objects in new space; a scavenge starts form these roots and the interpreter's stack
  
  rememberedSetSize
  	- the size of the remembered set, also the first unused index in the rememberedSet
  
  previousRememberedSetSize:
  	- the size of the remembered set before scavenging objects in future space.
  
  numRememberedEphemerons
  	- the number of unscavenged ephemerons at the front of the rememberedSet.
  
  ephemeronList
  	- the head of the list of corpses of unscavenged ephemerons reached in the current phase
  
  weakList
  	- the head of the list of corpses of weak arrays reached during the scavenge.
  
  tenuringProportion
  	- the amount of pastSpace below which the system will not tenure unless futureSpace fills up, and above which it will eagerly tenure
  
  tenuringThreshold
  	- the pointer into pastSpace below which objects will be tenured
  
  Weakness and Ephemerality in the Scavenger.
  Weak arrays should not hold onto their referents (except from their strong fileds, their named inst vars).  Ephemerons are objects that implement instance-based finalization; attaching an ephemeron to an object keeps that object alive and causes the ephemeron to "fire" when the object is only reachable from the ephemeron (or other ephemerons & weak arrays).  They are a special kind of Associations that detect when their keys are about to die, i.e. when an ephemeron's key is not reachable from the roots except from weak arrays and other ephemerons with about-to-die keys.  Note that if an ephemeron's key is not about to die then references from the rest of the ephemeron can indeed prevent ephemeron keys from dying.
  
  The scavenger is concerned with collecting objects in new space, therefore it ony deals with weak arrays and ephemerons that are either in the remembered set or in new space.  By deferring scanning these objects until other reachable objects have been scavenged, the scavenger can detect dead or dying references.
  
  Weak Array Processing
  In the case of weak arrays this is simple.  The scavenger refuses to scavenge the referents of weak arrays in scavengeReferentsOf: until the entire scavenge is over.  It then scans the weak arrays in the remembered set and in future space and nils all fields in them that are referring to unforwarded objects in eden and past space, because these objects have not survived the scavenge.  The root weak arrays remaining to be scavenged are in the remembered table.  Surviving weak arrays in future space are collected on a list.  The list is threaded through the corpses of weak arrays in eden and/or past space.  weakList holds the slot offset of the first weak array found in eden and/or past space.  The next offset is stored in the weak array corpse's identityHash and format fields (22 bits & 5 bits of allocationUnits, for a max new space size of 2^28 bytes, 256Mb).  The list is threaded throguh corpses, but the surviving arrays are pointed to by the corpses' forwarding pointers.
  
  Ephemeron Processing
  The case of ephemerons is a little more complicated because an ephemeron's key should survive.  The scavenger is cyclical.  It scavenges the remembered set, which may copy and forward surviving objects in past and/or eden spaces to future space.  It then scavenges those promoted objects in future space until no more are promoted, which may in turn remember more objects.  The cycles continue until no more objects get promoted to future space and no more objects get remembered.  At this point all surviving objecta are in futureSpace.
  
  So if the scavenger does not scan ephemerons in the remembered set or in future space until the scavenger finishes cycling, it can detect ephemerons whose keys are about to die because these will be unforwarded objects in eden and/or past space.  Ephemerons encountered in the remembered set are either processed like ordinary objects if their keys have been promoted to futureSpace, or are moved to the front of the rememberedSet (because, dear reader, it is a sequence) if their keys have not been promoted.  Ephemerons encountered in scavengeReferentsOf: are either scanned like normal objects if their keys have been promoted, or added to the ephemeronList, organized identically to the weakList, if their keys are yet to be promoted.  Since references from other ephemerons with surviving keys to ephemeron keys can and should prevent the ephemerons whose keys they are from firing the scavenger does not fire ephemerons unless all unscavenged ephemerons have unscavenged keys.  So the unscavenged ephemerons (the will be at the beginning of the remembered set and on the ephemeronList) are scanned and any that have promoted keys are scavenged.  But if no unscavenged ephemerons have surviving keys then all the unscavenged ephemerons are fired and then scavenged.  This in turn may remember more objects and promote more objects to future space, and encounter more unscavenged ephemerons.  So the scavenger continues until no more objects are remembered, no more objects are promoted to future space and no more unscavenged ephemerons exist.!

Item was changed:
  ----- Method: SpurGenerationScavenger class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(eden futureSpace pastSpace) do:
  		[:var| aCCodeGenerator var: var type: #SpurNewSpaceSpace].
+ 	aCCodeGenerator var: #rememberedSet type: #'sqInt *'!
- 	aCCodeGenerator
- 		var: #rememberedSet
- 		declareC: 'sqInt rememberedSet[RememberedSetLimit + 1 /* ', (RememberedSetLimit + 1) printString, ' */]'!

Item was changed:
  ----- Method: SpurGenerationScavenger class>>initialize (in category 'class initialization') -----
  initialize
  	"SpurGenerationScavenger initialize"
- 	RememberedSetLimit := 64 * 1024. "temporary; must move to heap"
- 	RememberedSetRedZone := RememberedSetLimit - (RememberedSetLimit // 2).
- 
  	TenureByAge := 1.
  	TenureByClass := 2.
  	DontTenure := 3.
  	DontTenureButDoUnmark := 4.
  	MarkOnTenure := 5!

Item was added:
+ ----- Method: SpurGenerationScavenger>>growRememberedSet (in category 'store check') -----
+ growRememberedSet
+ 	| obj numSlots newObj base |
+ 	<inline: false> "Don't ruin locality in remember:"
+ 	<var: #base type: #'sqInt *'>
+ 	obj := manager rememberedSetObj.
+ 	numSlots := manager numSlotsOf: obj.
+ 	self assert: numSlots >= 1024.
+ 	newObj := manager allocatePinnedSlots: numSlots * 2.
+ 	manager rememberedSetObj: newObj.
+ 	base := manager firstIndexableField: newObj.
+ 	0 to: rememberedSetSize - 1 do:
+ 		[:i| base at: i put: (rememberedSet at: i)].
+ 	"if growing in the middle of a GC, need to preserve marked status."
+ 	(manager isMarked: obj) ifTrue:
+ 		[manager
+ 			setIsMarkedOf: newObj to: true;
+ 			setIsMarkedOf: obj to: false].
+ 	manager freeObject: obj.
+ 	rememberedSet := base.
+ 	rememberedSetLimit := numSlots * 2.
+ 	rememberedSetRedZone := rememberedSetLimit * 3 + 3 // 4!

Item was changed:
  ----- Method: SpurGenerationScavenger>>initialize (in category 'initialization') -----
  initialize
  	pastSpace := SpurNewSpaceSpace new.
  	futureSpace := SpurNewSpaceSpace new.
  	eden := SpurNewSpaceSpace new.
- 	rememberedSet := CArrayAccessor on: (Array new: RememberedSetLimit).
  	rememberedSetSize := 0.
  	tenureThreshold := 0.
  	statTenures := 0!

Item was added:
+ ----- Method: SpurGenerationScavenger>>initializeRememberedSet (in category 'initialization') -----
+ initializeRememberedSet
+ 	| obj |
+ 	obj := manager rememberedSetObj.
+ 	obj = manager nilObject ifTrue:
+ 		[obj := manager allocatePinnedSlots: 1024.
+ 		 manager rememberedSetObj: obj].
+ 	rememberedSet := manager firstIndexableField: obj.
+ 	rememberedSetSize := 0.
+ 	rememberedSetLimit := manager numSlotsOf: obj.
+ 	rememberedSetRedZone := rememberedSetLimit * 3 + 3 // 4!

Item was changed:
  ----- Method: SpurGenerationScavenger>>remember: (in category 'store check') -----
  remember: objOop
  	"Add the argument to the remembered set and set its isRemembered bit to true.
  	 Answer the argument for the benefit of the Cogit."
  	<api>
  	<inline: false>
  	self assert: (manager isNonImmediate: objOop).
+ 	self deny: (manager isYoungObject: objOop).
+ 	self deny: (manager isRemembered: objOop).
+ 	self deny: (self isInRememberedSet: objOop).
- 	self assert: (manager isYoungObject: objOop) not.
- 	self assert: (manager isRemembered: objOop) not.
- 	self assert: (manager isInRememberedSet: objOop) not.
  	manager setIsRememberedOf: objOop to: true.
+ 	rememberedSetSize >= rememberedSetLimit ifTrue:
+ 		[self growRememberedSet].
+ 	rememberedSet at: rememberedSetSize put: objOop.
+ 	(rememberedSetSize := rememberedSetSize + 1) >= rememberedSetRedZone ifTrue:
+ 		[manager scheduleScavenge].
- 	rememberedSetSize < RememberedSetLimit
- 		ifTrue:
- 			[rememberedSet at: rememberedSetSize put: objOop.
- 			 (rememberedSetSize := rememberedSetSize + 1) >= RememberedSetRedZone ifTrue:
- 				[manager scheduleScavenge]]
- 		ifFalse:
- 			[self error: 'remembered set overflow' "for now"].
  	^objOop!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
  	"SpurMemoryManager initialize"
  	BitsPerByte := 8.
  
+ 	"Pig compact can be repeated to compact better.  Experience shows that 3 times
+ 	 compacts very well, desirable for snapshots.  But this is overkill for normal GCs."
+ 	CompactionPassesForGC := 2.
+ 	CompactionPassesForSnapshot := 3.
+ 
  	"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.  The list goes through
  	 ObjStackNextx. We don't want to shrink objStacks, since they're used
  	 in GC and its good to keep their memory around.  So unused pages
  	 created by popping emptying pages are kept on the ObjStackFreex list.
  	 ObjStackNextx must be the last field for swizzleObjStackAt:."
  	ObjStackPageSlots := 4092. "+ double header = 16k bytes per page in 32-bits"
  	ObjStackTopx := 0.
  	ObjStackMyx := 1.
  	ObjStackFreex := 2.
  	ObjStackNextx := 3.
  	ObjStackFixedSlots := 4.
  	ObjStackLimit := ObjStackPageSlots - ObjStackFixedSlots.
+ 	"The hiddenHootsObject contains the classTable pages and up to 8 additional objects.
+ 	 Currently we use four; the three objStacks, the mark stack, the weaklings and the
+ 	 ephemeron queue, and the rememberedSet."
- 	"There are currently three obj stacks, the mark stack, the weaklings and the ephemeron queue."
  	MarkStackRootIndex := self basicNew classTableRootSlots.
  	WeaklingStackRootIndex := MarkStackRootIndex + 1.
  	EphemeronQueueRootIndex := MarkStackRootIndex + 2.
+ 	RememberedSetRootIndex := MarkStackRootIndex + 3.
  
  	MarkObjectsForEnumerationPrimitives := false.
  
  	"The remap buffer support is for compatibility; Spur doesn't GC during allocation.
  	 Eventually this should die."
  	RemapBufferSize := 25.
  
  	"Extra roots are for plugin support."
  	ExtraRootsSize := 2048 "max. # of external roots"!

Item was changed:
  ----- Method: SpurMemoryManager>>allocatePinnedSlots: (in category 'sista support') -----
  allocatePinnedSlots: nSlots
  	<api>
- 	<option: #NewspeakVM>
- 	<option: #SistaStackToRegisterMappingCogit>
  	| obj |
  	obj := self allocateSlotsForPinningInOldSpace: nSlots
  				bytes: (self objectBytesForSlots: nSlots)
  				format: self wordIndexableFormat
  				classIndex: 	self wordSizeClassIndexPun.
  	obj ifNotNil:
  		[self fillObj: obj numSlots: nSlots with: 0].
  	^obj!

Item was changed:
  ----- Method: SpurMemoryManager>>compact (in category 'compaction') -----
  compact
  	"We'd like to use exact fit followed by best or first fit, but it doesn't work
  	 well enough in practice.  So use pig compact.  Fill large free objects starting
  	 from low memory with objects taken from the end of memory."
  	<inline: #never> "for profiling"
  	statCompactPassCount := statCompactPassCount + 1.
  	self assert: (firstFreeChunk = 0 or: [self isFreeObject: firstFreeChunk]).
+ 	1 to: numCompactionPasses do:
- 	1 to: 3 do:
  		[:i|
  		 self pigCompact.
  		 self eliminateAndFreeForwardersForPigCompact].
  	
  	"The free lists are zeroed in freeUnmarkedObjectsAndSortAndCoalesceFreeSpaceForPigCompact.
  	 They should still be zero here"
  	self assert: self freeListHeadsEmpty.
  	self rebuildFreeListsForPigCompact!

Item was changed:
  ----- Method: SpurMemoryManager>>garbageCollectForSnapshot (in category 'snapshot') -----
  garbageCollectForSnapshot
  	self flushNewSpace. "There is no place to put newSpace in the snapshot file."
+ 	self flag: 'If we wanted to shrink the rememberedSet prior to snapshot this is the place to do it.'.
+ 	numCompactionPasses := CompactionPassesForSnapshot.
  	self fullGC.
+ 	numCompactionPasses := CompactionPassesForGC.
  	segmentManager prepareForSnapshot.
  	self checkFreeSpace!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory at al are
  	 initialised by the image-reading code via setHeapBase:memoryLimit:endOfMemory:.
  	 endOfMemory is assumed to point to the end of the last object in the image.
  	 Assume: image reader also initializes the following variables:
  		specialObjectsOop
  		lastHash"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: BaseHeaderSize = self baseHeaderSize.
  	self assert: (self maxSlotsForAlloc * BytesPerWord) asInteger > 0.
  	self bootstrapping ifFalse:
  		[self
  			initSegmentBridgeWithBytes: self bridgeSize
  			at: endOfMemory - self bridgeSize].
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  	specialObjectsOop := segmentManager swizzleObj: specialObjectsOop.
  
  	"heavily used special objects"
  	nilObj		:= self splObj: NilObject.
  	falseObj	:= self splObj: FalseObject.
  	trueObj		:= self splObj: TrueObject.
  
  	"In Cog we insist that nil, true & false are next to each other (Cogit generates tighter
  	 conditional branch code as a result).  In addition, Spur places the free lists and
  	 class table root page immediately following them."
  	self assert: nilObj = oldSpaceStart.
  	self assert: falseObj = (self objectAfter: nilObj).
  	self assert: trueObj = (self objectAfter: falseObj).
  	freeListObj := self objectAfter: trueObj.
  	self reInitializeClassTablePostLoad: (self objectAfter: freeListObj).
  	markStack := self swizzleObjStackAt: MarkStackRootIndex.
  	weaklingStack := self swizzleObjStackAt: WeaklingStackRootIndex.
  	ephemeronQueue := self swizzleObjStackAt: EphemeronQueueRootIndex.
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  
  	self initializeFreeSpacePostLoad: freeListObj.
  	segmentManager collapseSegmentsPostSwizzle.
  	self computeFreeSpacePostSwizzle.
  	self bootstrapping ifFalse:
+ 		[self initializeNewSpaceVariables.
+ 		 scavenger initializeRememberedSet].
- 		[self initializeNewSpaceVariables].
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
  	segmentManager checkSegments.
  
+ 	numCompactionPasses := CompactionPassesForGC.
+ 
  	"These defaults should depend on machine size; e.g. too small on a powerful laptop, too big on a Pi."
  	growHeadroom := 16*1024*1024.		"headroom when growing"
  	shrinkThreshold := 32*1024*1024.		"free space before shrinking"
  	self setHeapSizeAtPreviousGC.
  	heapGrowthToSizeGCRatio := 0.333333. "By default GC after scavenge if heap has grown by a third since the last GC"!

Item was changed:
  ----- Method: SpurMemoryManager>>markAndTraceHiddenRoots (in category 'gc - global') -----
  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 ephemeronQueue 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: markStack andContents: false.
  	self markAndTraceObjStack: weaklingStack andContents: false.
  	self markAndTraceObjStack: ephemeronQueue andContents: true.
  
+ 	self setIsMarkedOf: self rememberedSetObj to: true.
  	self setIsMarkedOf: self freeListsObj to: true.
  
  	(self isWeakNonImm: classTableFirstPage) ifTrue:
  		[^self markAndTrace: hiddenRootsObj].
  
  	self setIsMarkedOf: hiddenRootsObj to: true.
  	self markAndTrace: classTableFirstPage.
  	1 to: numClassTablePages - 1 do:
  		[:i| self setIsMarkedOf: (self fetchPointer: i ofObject: hiddenRootsObj)
  				to: true]!

Item was added:
+ ----- Method: SpurMemoryManager>>numSegments (in category 'segments') -----
+ numSegments
+ 	<doNotGenerate>
+ 	^segmentManager numSegments!

Item was added:
+ ----- Method: SpurMemoryManager>>rememberedSetObj (in category 'scavenger') -----
+ rememberedSetObj
+ 	^self fetchPointer: RememberedSetRootIndex ofObject: hiddenRootsObj!

Item was added:
+ ----- Method: SpurMemoryManager>>rememberedSetObj: (in category 'scavenger') -----
+ rememberedSetObj: anObj
+ 	self assert: (self isOldObject: anObj).
+ 	self storePointerUnchecked: RememberedSetRootIndex ofObject: hiddenRootsObj withValue: anObj!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: VMClass>>deny: (in category 'simulation support') -----
+ deny: aBooleanOrBlock
+ 	<doNotGenerate>
+ 	self assert: aBooleanOrBlock value not!



More information about the Vm-dev mailing list