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

commits at source.squeak.org commits at source.squeak.org
Thu May 22 21:03:05 UTC 2014


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

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

Name: VMMaker.oscog-eem.732
Author: eem
Time: 22 May 2014, 2:00:24.946 pm
UUID: 8390b0f2-ae2c-4fc6-9abf-41d6cefda0fd
Ancestors: VMMaker.oscog-eem.731

Spur:
Fix traversal in sortedFreeListPairwiseReverseDo: when there is only
one element in the sorted free list.

Weak containers and ephemerons in new space must be
processed after all strongly reachable objects have been
scavenged.  So when the scavenger reaches a weak
container or ephemeron it copies it to future space, leaving
behind a forwarding pointer in the corpse, but it does not
yet scavenge its contents.  The corpse is used to construct
the list of scavenged weak/ephemeral objects.  The
corpse's forwarding pointer is already taken to point to the
survivor.  Instead, the list is constructed by having a list
head variable, and linking the list through a value stored in
some of the corpse's unused header fields (format &
identityHash).  0 marks the end of the list.  Of course this
doesn't work if an object is the first object in newSpace as
this offset will be computed to be zero, improperly
teminating the list!

Fix this by adding one to the corpse offset and substracting 1 when decoding.

Implement a simple policy to deal with the fact that typically
heap growth happens during tenuring, not after a failed
allocation.  If, after scavenging, the heap has grown by some
factor of its size at the previous global GC, do a global GC.
Default the factor to 0.333333.
Provide VM parameter access to this value:

55	ratio of growth and image size at or above which a GC will be performed post scavenge

Add a printFreeChunks debugging utility that sweeps
through memory instead of traversing the free lists.

Fix the shadowed variable warnings in primitiveIsPinned &
primitivePin.  Format the shadowing warning a little more carefully.

Simulator:
Move the halt on Spur global GC into globalGarbageCollect and
nuke the subclass methods.

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

Item was changed:
  ----- Method: CCodeGenerator>>prepareMethods (in category 'utilities') -----
  prepareMethods
  	| globals |
  	globals := Set new: 200.
  	globals addAll: variables.
  	methods do:
  		[:m |
  		m locals, m args do:
  			[:var |
  			(globals includes: var) ifTrue:
  				[self error: 'Local variable ''', var, ''' may mask global when inlining ', m selector].
  			((methods at: var ifAbsent: [nil]) ifNil: [false] ifNotNil: [:m1| m1 isStructAccessor not]) ifTrue:
  				[logger
  					ensureCr;
  					nextPutAll: 'Local variable name ''', var, ''' in ';
  					nextPutAll: m selector;
+ 					nextPutAll: ' may mask method when inlining';
+ 					cr]].
- 					nextPutAll: ' may mask method when inlining']].
  		m bindClassVariablesIn: constants.
  		m prepareMethodIn: self]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIsPinned (in category 'memory space primitives') -----
  primitiveIsPinned
  	"Answer if the receiver is pinned, i.e. immobile."
+ 	| obj |
+ 	obj := self stackTop.
+ 	((objectMemory isImmediate: obj)
+ 	 or: [objectMemory isForwarded: obj]) ifTrue:
- 	| receiver |
- 	receiver := self stackTop.
- 	((objectMemory isImmediate: receiver)
- 	 or: [objectMemory isForwarded: receiver]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
  	self pop: argumentCount - 1.
  	self stackTopPut:
  			(objectMemory hasSpurMemoryManagerAPI
+ 				ifTrue: [objectMemory booleanObjectOf: (objectMemory isPinned: obj)]
- 				ifTrue: [objectMemory booleanObjectOf: (objectMemory isPinned: receiver)]
  				ifFalse: [objectMemory falseObject])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitivePin (in category 'memory space primitives') -----
  primitivePin
  	"Pin or unpin the receiver, i.e. make it immobile or mobile.  Answer whether the object was
  	 already pinned. N.B. pinning does *not* prevent an object from being garbage collected."
+ 	| obj boolean wasPinned failure |
- 	| receiver boolean wasPinned failure |
  	objectMemory hasSpurMemoryManagerAPI ifFalse:
  		[^self primitiveFailFor: PrimErrUnsupported].
  
+ 	obj := self stackValue: 1.
+ 	((objectMemory isImmediate: obj)
+ 	 or: [(objectMemory isForwarded: obj)
+ 	 or: [(objectMemory isContext: obj)
+ 		and: [self isStillMarriedContext: obj]]]) ifTrue:
- 	receiver := self stackValue: 1.
- 	((objectMemory isImmediate: receiver)
- 	 or: [(objectMemory isForwarded: receiver)
- 	 or: [(objectMemory isContext: receiver)
- 		and: [self isStillMarriedContext: receiver]]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
  	boolean := self stackTop.
  	(boolean = objectMemory falseObject
  	 or: [boolean = objectMemory trueObject]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
+ 	(objectMemory isPinned: obj)
- 	(objectMemory isPinned: receiver)
  		ifTrue:
  			[wasPinned := objectMemory trueObject.
+ 			 objectMemory setIsPinnedOf: obj to: false]
- 			 objectMemory setIsPinnedOf: receiver to: false]
  		ifFalse:
  			[wasPinned := objectMemory falseObject.
+ 			 failure := objectMemory pinObject: obj.
- 			 failure := objectMemory pinObject: receiver.
  			 failure ~= 0 ifTrue:
  				[^self primitiveFailFor: failure]].
  	
  	self pop: argumentCount - 1 thenPush: wasPinned!

Item was removed:
- ----- Method: Spur32BitMMLECoSimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	self halt: 'GC number ', statFullGCs printString.
- 	^super globalGarbageCollect!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	self halt: 'GC number ', statFullGCs printString.
- 	^super globalGarbageCollect!

Item was changed:
  ----- Method: SpurGenerationScavenger>>corpseForCorpseOffset: (in category 'weakness and ephemerality') -----
  corpseForCorpseOffset: corpseOffset
  	"Use the identityHash and format fields to construct a 27 bit offset through
  	 non-future newSpace and use this to implement lists for weak array and
+ 	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30
+ 	 bytes, or 1Gb, big enough for newSpace for a good few years yet."
+ 	^corpseOffset - 1 << manager shiftForAllocationUnit + manager newSpaceStart!
- 	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30 bytes
- 	 or 1Gb, big enough for newSpace for a good few years yet."
- 	^corpseOffset << manager shiftForAllocationUnit + manager newSpaceStart!

Item was changed:
  ----- Method: SpurGenerationScavenger>>corpseOffsetOf: (in category 'weakness and ephemerality') -----
  corpseOffsetOf: corpse
  	"Answer the offset of the corpse in newSpace as a multiple of allocationUnits.
  	 Use the identityHash and format fields to construct a 27 bit offset through
  	 non-future newSpace and use this to implement lists for weak array and
  	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30
+ 	 bytes or 1Gb, big enough for newSpace for a good few years yet.  Add
+ 	 one to ensure that a corpse offset is always non-zero, even when it is
+ 	 that of the first object in newSpace."
+ 	^corpse - manager newSpaceStart >> manager shiftForAllocationUnit + 1!
- 	 bytes or 1Gb, big enough for newSpace for a good few years yet."
- 	^corpse - manager newSpaceStart >> manager shiftForAllocationUnit.!

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

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
  							lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory sortedFreeChunks)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs'])
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #freeListsMask type: #usqInt;
  		var: #freeLists type: #'sqInt *';
  		var: #classTableBitmap type: #'unsigned char *';
  		var: #objStackInvalidBecause type: #'char *';
  		var: #highestObjects type: #SpurCircularBuffer;
+ 		var: #unscannedEphemerons type: #SpurContiguousObjStack;
+ 		var: #heapGrowthToSizeGCRatio type: #float;
+ 		var: #heapSizeAtPreviousGC type: #usqInt.
- 		var: #unscannedEphemerons type: #SpurContiguousObjStack.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'!

Item was added:
+ ----- Method: SpurMemoryManager>>getHeapGrowthToSizeGCRatio (in category 'accessing') -----
+ getHeapGrowthToSizeGCRatio
+ 	<returnTypeC: #float>
+ 	^heapGrowthToSizeGCRatio!

Item was changed:
  ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
  globalGarbageCollect
+ 	self cCode: [] inSmalltalk: [self halt: 'GC number ', statFullGCs printString].
+ 
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  
  	self markObjects.
  	self expungeDuplicateAndUnmarkedClasses: true.
  	self nilUnmarkedWeaklingSlots.
  	self freeUnmarkedObjectsAndSortAndCoalesceFreeSpaceForPigCompact.
  
  	"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 runLeakCheckerForFullGC: true
  		excludeUnmarkedNewSpaceObjs: true
  		classIndicesShouldBeValid: true.
  
  	self compact.
+ 	self setHeapSizeAtPreviousGC.
  
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  	self assert: self allObjectsUnmarked.
  	self runLeakCheckerForFullGC: true!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory is initially set (by the image-reading code) to the end of the last object in the image. Initialization redefines endOfMemory to be the end of the object allocation area based on the total available memory, but reserving some space for forwarding blocks."
  	"Assume: image reader initializes the following variables:
  		memory
  		memoryLimit
  		specialObjectsOop
  		lastHash
  	"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: BaseHeaderSize = self baseHeaderSize.
  	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].
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
  	segmentManager checkSegments.
  
  	"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"!
- 	shrinkThreshold := 32*1024*1024.		"free space before shrinking"!

Item was added:
+ ----- Method: SpurMemoryManager>>printFreeChunks (in category 'debug support') -----
+ printFreeChunks
+ 	"This version goes through memory, printing all free chunks.
+ 	 Other versions go through the free lists.  This one will show
+ 	 all free chunks even if the free lists are corrupt."
+ 	<api>
+ 	| seenNewFreeChunk |
+ 	seenNewFreeChunk := false.
+ 	self allNewSpaceEntitiesDo:
+ 		[:o|
+ 		(self isFreeObject: o) ifTrue:
+ 			[seenNewFreeChunk ifFalse:
+ 				[coInterpreter print: 'NewSpace CONTAINS FREE OBJECT(S)!!!!'; cr.
+ 				 seenNewFreeChunk := true].
+ 			 self printFreeChunk: o]].
+ 	self allOldSpaceEntitiesDo:
+ 		[:o|
+ 		(self isFreeObject: o) ifTrue:
+ 			[self printFreeChunk: o]]!

Item was added:
+ ----- Method: SpurMemoryManager>>setHeapGrowthToSizeGCRatio: (in category 'accessing') -----
+ setHeapGrowthToSizeGCRatio: aDouble
+ 	<var: #aDouble type: #double>
+ 	heapGrowthToSizeGCRatio := aDouble!

Item was added:
+ ----- Method: SpurMemoryManager>>setHeapSizeAtPreviousGC (in category 'gc - global') -----
+ setHeapSizeAtPreviousGC
+ 	heapSizeAtPreviousGC := endOfMemory - nilObj - totalFreeOldSpace!

Item was changed:
  ----- Method: SpurMemoryManager>>sortedFreeListPairwiseReverseDo: (in category 'compaction') -----
  sortedFreeListPairwiseReverseDo: aBinaryBlock
  	"Evaluate aBinaryBlock with adjacent entries in the free list, from
  	 high address to low address.  The second argument is in fact the
  	 start of the next free chunk, not the free chunk itself.  Use
  	 endOfMemory - bridgeSize as the second argument in the first evaluation."
  	| free nextFree prevFree prevPrevFree |
  	<inline: true>
  	free := lastFreeChunk.
  	prevPrevFree := prevFree := 0.
  	[free ~= 0] whileTrue:
  		[nextFree := self nextInSortedFreeListLink: free given: prevFree.
  		 self assert: (free = 0 or: [self isFreeObject: free]).
  		 self assert: (prevFree = 0 or: [prevFree > free]).
  	 	 aBinaryBlock value: free value: (prevFree = 0
  											ifTrue: [endOfMemory - self bridgeSize]
  											ifFalse: [self startOfObject: prevFree]).
  		 self assert: (prevFree = 0 or: [self isFreeObject: prevFree]).
  		 self assert: (prevPrevFree = 0 or: [self isFreeObject: prevPrevFree]).
  		 (self isFreeObject: free) ifFalse:
  			[free := self nextInSortedFreeListLink: prevFree given: prevPrevFree].
  		 (nextFree = 0 or: [self isFreeObject: nextFree])
  			ifTrue:
  				[prevPrevFree := prevFree.
  				 prevFree := free.
+ 				 free := prevFree = firstFreeChunk ifTrue: [0] ifFalse: [nextFree]]
- 				 free := nextFree]
  			ifFalse:
  				[free := lastFreeChunk.
  				 prevPrevFree := prevFree := 0.
  				 [free > nextFree] whileTrue:
  					[nextFree := self nextInSortedFreeListLink: free given: prevFree.
  					 self assert: (self isFreeObject: nextFree).
  					 prevPrevFree := prevFree.
  					 prevFree := free.
  					 free := nextFree]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>sufficientSpaceAfterGC: (in category 'gc - scavenging') -----
  sufficientSpaceAfterGC: numBytes
  	"This is ObjectMemory's funky entry-point into its incremental GC,
  	 which is a stop-the-world a young generation reclaimer.  In Spur
  	 we run the scavenger.  Answer if space is not low."
  
+ 	| heapSizePostGC |
  	self assert: numBytes = 0.
  	self scavengingGCTenuringIf: TenureByAge.
+ 	heapSizePostGC := endOfMemory - nilObj - totalFreeOldSpace.
+ 	(heapSizePostGC - heapSizeAtPreviousGC) asFloat / heapSizeAtPreviousGC >= heapGrowthToSizeGCRatio ifTrue:
+ 		[self fullGC].
  	[totalFreeOldSpace < growHeadroom
  	 and: [(self growOldSpaceByAtLeast: 0) notNil]] whileTrue:
  		[totalFreeOldSpace >= growHeadroom ifTrue:
  			[^true]].
  	lowSpaceThreshold > totalFreeOldSpace ifTrue: "space is low"
  		[lowSpaceThreshold := 0. "avoid signalling low space twice"
  		 ^false].
  	^true!

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



More information about the Vm-dev mailing list