Squeak memory allocation

lex at cc.gatech.edu lex at cc.gatech.edu
Tue Nov 3 22:02:27 UTC 1998


Okay, since my words have been unconvincing, I hacked a little code to see how this really works.

First, my gloom and doom about static memory allocations was worse than the true case.  I claimed that if you allocate a larger heap (via command line flags or whatever) than you have actual RAM, that you will definately get swapping.  In fact this is not quite true.  The current ObjectMemory does an incremental collection after every 2000 allocations, and so in the typical case the upper parts of a large but mostly empty heap will never get touched.

However, that's only the typical case.  If you start allocating very large objects, then you can allocate tons of space before the 2000-allocations trigger goes off.  To test this,  I ran an image with 50 megs of heap, and executed:

	10000 timesRepat: [ Array new: 1000000 ]


The Squeak process grew to 40 megs resident, and all my other running apps started getting swapped out.


Next, I modified the ObjectMemory to also trigger a GC if more than 3 megs have been allocated since the last GC.  When I executed the above line with the new VM, the Squeak process only went up to 17 megs.

The patch is below, for anyone who wants to play with it.  It's a bit of a hack as is, but simply adding a "maxAllocationBetweenGCs" instance variable, and finding a better name than "lastFreeSpace" would make it pretty clean. 

Also, maybe the max allocation should be smaller for smaller images; for a 2 meg image, for instance, you might want to do a GC after just 1 meg of allocation.



Lex



'From Squeak 2.2 of Sept 23, 1998 on 3 November 1998 at 4:52:29 pm'!
"Change Set:		FrequentGCs
Date:			3 November 1998
Author:			Lex Spoon

trigger a GC after every 3 megabytes of allocation, so that Squeak doesn't use memory high in its heap unless it really needs it."!

Object subclass: #ObjectMemory
	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit lastFreeStart nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount child field parentField freeBlock lastHash freeLargeContexts freeSmallContexts allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount interruptCheckCounter checkAssertions allocationsBetweenGCs tenuringThreshold statFullGCs statFullGCMSecs statIncrGCs statIncrGCMSecs statTenures statRootTableOverflows displayBits '
	classVariableNames: 'AllButHashBits AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit AllButTypeMask BaseHeaderSize CharacterTable ClassArray ClassBitmap ClassBlockContext ClassByteArray ClassCharacter ClassCompiledMethod ClassFloat ClassInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassPoint ClassProcess ClassPseudoContext ClassSemaphore ClassString ClassTranslatedMethod CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero Done ExternalObjectsArray FalseObject FreeSizeMask GCTopMarker HashBits HashBitsOffset HeaderTypeClass HeaderTypeFree HeaderTypeGC HeaderTypeShort HeaderTypeSizeAndClass LargeContextSize MarkBit MinimumForwardTableBytes NilContext NilObject RemapBufferSize RootBit RootTableSize SchedulerAssociation SelectorCannotReturn SelectorDoesNotUnderstand SelectorMustBeBoolean SmallBlockContext SmallContextSize SmallMethodContext SpecialSelectors StackStart StartField StartObj TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterr!
!
!
uptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject TypeMask Upward '
	poolDictionaries: ''
	category: 'Squeak-Interpreter'!

!ObjectMemory methodsFor: 'initialization' stamp: 'ls 11/3/1998 15:43'!
initializeMemoryFirstFree: firstFree 
	"Initialize endOfMemory to the top of oop storage space, reserving some space for forwarding blocks, and create the freeBlock from which space is allocated. Also create a fake free chunk at endOfMemory to act as a sentinal for memory scans."
	"Note: The amount of space reserved for forwarding blocks should be chosen to ensure that incremental compactions can usually be done in a single pass. However, there should be enough forwarding blocks so a full compaction can be done in a reasonable number of passes, say ten. (A full compaction requires N object-moving passes, where N = number of non-garbage objects / number of forwarding blocks)."

	| fwdBlockBytes |
	"reserve space for forwarding blocks"
	fwdBlockBytes _ MinimumForwardTableBytes.
	(memoryLimit - fwdBlockBytes) >= (firstFree + BaseHeaderSize) ifFalse: [
		"reserve enough space for a minimal free block of BaseHeaderSize bytes"
		fwdBlockBytes _ memoryLimit - (firstFree + BaseHeaderSize).
	].

	"set endOfMemory and initialize freeBlock"
	endOfMemory _ memoryLimit - fwdBlockBytes.
	freeBlock _ firstFree.
	self setSizeOfFree: freeBlock to: (endOfMemory - firstFree).  "bytes available for oops"

	"make a fake free chunk at endOfMemory for use as a sentinal in memory scans"
	self setSizeOfFree: endOfMemory to: BaseHeaderSize.

	checkAssertions ifTrue: [
		((freeBlock < endOfMemory) and: [endOfMemory < memoryLimit])
			ifFalse: [ self error: 'error in free space computation' ].	
		(self oopFromChunk: endOfMemory) = endOfMemory
			ifFalse: [ self error: 'header format must have changed' ].
		(self objectAfter: freeBlock) = endOfMemory
			ifFalse: [ self error: 'free block not properly initialized' ].
	].

	lastFreeStart _ freeBlock.! !

!ObjectMemory methodsFor: 'allocation' stamp: 'ls 11/3/1998 15:57'!
allocateChunk: byteSize 
	"Allocate a chunk of the given size. Sender must be sure that the requested size includes enough space for the header word(s)."
	"Details: To limit the time per incremental GC, do one every so many allocations."

	| enoughSpace newFreeSize newChunk |
	self inline: true.
	allocationCount >= allocationsBetweenGCs ifTrue: [
		"do an incremental GC every so many allocations to keep pauses short"
		self incrementalGC.
	].

	freeBlock - lastFreeStart > (3*1024 * 1024) ifTrue: [
		"do a GC if we've allocadet more than 3 megs"
		self incrementalGC. ].

	enoughSpace _ self sufficientSpaceToAllocate: byteSize.
	enoughSpace ifFalse: [
		"signal that space is running low, put proceed with allocation if possible"
		signalLowSpace _ true.
		lowSpaceThreshold _ 0.  "disable additional interrupts until lowSpaceThreshold is reset by image"
		interruptCheckCounter _ 0.
	].

	(self sizeOfFree: freeBlock) < (byteSize + BaseHeaderSize) ifTrue: [
		self error: 'out of memory'.
	].

	"if we get here, there is enough space for allocation to succeed"
	newFreeSize _ (self sizeOfFree: freeBlock) - byteSize.
	newChunk _ freeBlock.
	freeBlock _ freeBlock + byteSize.
	"Assume: client will initialize object header of free chunk, so following is not needed:"
	"self setSizeOfFree: newChunk to: byteSize."
	self setSizeOfFree: freeBlock to: newFreeSize.
	allocationCount _ allocationCount + 1.

	^ newChunk! !


!Interpreter methodsFor: 'object memory support' stamp: 'ls 11/3/1998 15:42'!
postGCAction
	"Mark the active and home contexts as roots if old. This allows the interpreter to use storePointerUnchecked to store into them."

	(activeContext    < youngStart) ifTrue: [ self beRootIfOld: activeContext ].
	(theHomeContext < youngStart) ifTrue: [ self beRootIfOld: theHomeContext ].

	lastFreeStart _ freeBlock.! !





More information about the Squeak-dev mailing list