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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 25 21:08:50 UTC 2013


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

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

Name: VMMaker.oscog-eem.519
Author: eem
Time: 25 November 2013, 1:05:43.721 pm
UUID: ac72e5fd-c896-42c5-acee-19a8df8047d0
Ancestors: VMMaker.oscog-eem.518

Commit a costly mistake before undoing the damage.  If the code
zone sits between newSpace and oldSpace then isMachineCodeFrame:
et al need two boundary checks, > newSpaceLimit & < oldSpaceStart.
If the code zone sits beneath newSpace then copyAndForward: needs two boundary checks, < newSpaceLimit & > newSpaceStart.  So
IIABDFI implies reverting to the code zone being beneath newSpace,
and fixing copyAndForward:.  Tube.  3 days. Ouch.

Change Spur's primitiveFullGC to answer the byte size of the largest
free chunk, which is what is needed to know whether a new segment is
needed.  Add primitiveSizeInBytes[OfInstance] so the image doesn't
have to assume anything about header sizes.

Fix checkMaybeObjRefAt: to filter-out the 0's from unused method
parameters in closed PICs.

Fix a return-type conflict in printOopShortInner:.

Slang:
Fix Integer << Integer to cast to 64-bits if the shift overflows 32-bits.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateShiftLeft:on:indent: (in category 'C translation') -----
  generateShiftLeft: msgNode on: aStream indent: level
+ 	"Generate a C bitShift.  If we can determine the result
+ 	 would overflow the word size, cast to a long integer."
+ 	| rcvr arg |
+ 	rcvr := msgNode receiver.
+ 	arg := msgNode args first.
+ 	self emitCExpression: rcvr on: aStream.
+ 	(rcvr isConstant and: [arg isConstant
+ 	 and: [rcvr value isInteger and: [arg value isInteger
+ 	 and: [rcvr value < (1 bitShift: BytesPerWord * 8)
+ 	 and: [(rcvr value bitShift: arg value) >= (1 bitShift: BytesPerWord * 8)]]]]]) ifTrue:
+ 		[aStream nextPutAll: 'LL'].
- 	"Generate the C code for this message onto the given stream."
- 
- 	self emitCExpression: msgNode receiver on: aStream.
  	aStream nextPutAll: ' << '.
+ 	self emitCExpression: arg on: aStream!
- 	self emitCExpression: msgNode args first on: aStream.!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  	"Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  	"This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr
+ 	  minimumMemory heapSize bytesRead bytesToShift firstSegSize
+ 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize |
- 	  minimumMemory heapSize bytesRead bytesToShift
- 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize firstSegSize |
  	<var: #f type: #sqImageFile>
  	<var: #dataSize type: #'size_t'>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - BytesPerWord.  "record header start position"
  
  	headerSize			:= self getLongFromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags			:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory		:= self getLongFromFile: f swap: swapBytes. "N.B.  not used."
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	hdrEdenBytes		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  
  	"compare memory requirements with availability"
  	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ objectMemory newSpaceBytes
  						+ self interpreterAllocationReserveBytes.
  	heapSize             :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ desiredHeapSize
  						"+ edenBytes" "don't include edenBytes; this is part of the heap and so part of desiredHeapSize"
  						+ self interpreterAllocationReserveBytes.
  	heapSize < minimumMemory ifTrue:
  		[self insufficientMemorySpecifiedError].
  
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
+ 	objectMemory memory ifNil: [self insufficientMemoryAvailableError].
- 	
- 	objectMemory memory = nil ifTrue: [self insufficientMemoryAvailableError].
- 	heapBase := objectMemory memory + cogCodeSize.
- 	self assert: objectMemory startOfMemory = heapBase.
- 	objectMemory
- 		setHeapBase: heapBase
- 		memoryLimit: objectMemory memory + heapSize - 24  "decrease memoryLimit a tad for safety (?!!?!!? eem eem 10/9/2013 15:15)"
- 		endOfMemory: heapBase + dataSize.
  
+ 	heapBase := objectMemory
+ 					setHeapBase: objectMemory memory
+ 					memoryLimit: objectMemory memory + heapSize
+ 					endOfMemory: objectMemory memory + dataSize.
+ 
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	self initializeCodeGenerator.
  	^dataSize!

Item was removed:
- ----- Method: CogVMSimulator>>heapBase: (in category 'accessing') -----
- heapBase: anObject
- 	"Set the value of heapBase; used by the Spur CoSimulator to reposition cog code between newSpace and oldSpace."
- 
- 	^heapBase := anObject!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize count heapSize oldBaseAddr bytesToShift swapBytes hdrNumStackPages
  	 hdrEdenBytes hdrCogCodeSize stackZoneSize methodCacheSize headerFlags primTraceLogSize firstSegSize hdrMaxExtSemTabSize |
  	"open image file and read the header"
  
  	["begin ensure block..."
  	f := FileStream readOnlyFileNamed: fileName.
  	imageName := f fullName.
  	f binary.
  	version := self nextLongFrom: f.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getLongFromFile: f swap: swapBytes.
  	heapSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = 40.
  	hdrEdenBytes	:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = 48.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * BytesPerWord.
  	primTraceLogSize := primTraceLog size * BytesPerWord.
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
+ 	heapBase := objectMemory
+ 					setHeapBase: heapBase
+ 					memoryLimit:  heapBase
+ 									+ heapSize
+ 									+ objectMemory newSpaceBytes
+ 									+ self interpreterAllocationReserveBytes
+ 									+ extraBytes
+ 					endOfMemory: heapBase + heapSize.
- 	objectMemory
- 		setHeapBase: heapBase
- 		memoryLimit:  heapBase
- 						+ heapSize
- 						+ objectMemory newSpaceBytes
- 						+ self interpreterAllocationReserveBytes
- 						+ extraBytes
- 		endOfMemory: heapBase + heapSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	objectMemory memory: ((cogit processor endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  	count := objectMemory readHeapFromImageFile: f dataBytes: heapSize.
  	count ~= heapSize ifTrue: [self halt].
  	]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

Item was changed:
  ----- Method: Cogit>>checkMaybeObjRefAt: (in category 'garbage collection') -----
  checkMaybeObjRefAt: mcpc
  	| maybeObject |
  	maybeObject := backEnd literalBeforeFollowingAddress: mcpc.
+ 	maybeObject = 0 ifTrue:
+ 		[^true].
  	(objectRepresentation couldBeObject: maybeObject) ifFalse:
  		[^true].
  	^objectRepresentation checkValidObjectReference: maybeObject!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFullGC (in category 'memory space primitives') -----
  primitiveFullGC
+ 	"Do a full garbage collection.  In SqueakV3ObjectMemory, answer the number
+ 	 of bytes available (including swap space if dynamic memory management is
+ 	 supported).  In Spur, answer the size of the largest free chunk."
- 	"Do a full garbage collection and return the number of bytes available (including swap space if dynamic memory management is supported)."
  
+ 	objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 		[^self pop: 1 thenPushInteger: objectMemory fullGC].
  	objectMemory fullGCLock > 0 ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
+ 	objectMemory incrementalGC.  "maximimize space for forwarding table"
- 	objectMemory hasSpurMemoryManagerAPI ifFalse:
- 		[objectMemory incrementalGC].  "maximimize space for forwarding table"
  	objectMemory fullGC.
+ 	self pop: 1 thenPushInteger: (objectMemory bytesLeft: true)!
- 	self pop: 1 thenPushInteger: (objectMemory bytesLeft: true).!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSizeInBytes (in category 'memory space primitives') -----
+ primitiveSizeInBytes
+ 	<option: #SpurObjectMemory>
+ 	self pop: argumentCount + 1
+ 		 thenPushInteger: (objectMemory totalByteSizeOf: self stackTop)!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSizeInBytesOfInstance (in category 'memory space primitives') -----
+ primitiveSizeInBytesOfInstance
+ 	<option: #SpurObjectMemory>
+ 	| byteSizeOrErr |
+ 	argumentCount > 1 ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 	argumentCount = 1 ifTrue:
+ 		[(objectMemory isIntegerObject: self stackTop) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument].
+ 		 byteSizeOrErr := objectMemory
+ 								byteSizeOfInstanceOf: (self stackValue: 1)
+ 								withIndexableSlots: (objectMemory integerValueOf: self stackTop).
+ 		 byteSizeOrErr < 0 ifTrue:
+ 			[^self primitiveFailFor: byteSizeOrErr negated].
+ 		 ^self pop: 2 thenPushInteger: byteSizeOrErr].
+ 	byteSizeOrErr := objectMemory byteSizeOfInstanceOf: (self stackValue: 1).
+ 	byteSizeOrErr < 0 ifTrue:
+ 		[^self primitiveFailFor: byteSizeOrErr negated].
+ 	self pop: 1 thenPushInteger: byteSizeOrErr!

Item was changed:
  ----- Method: ObjectMemory>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
+ setHeapBase: heapBase memoryLimit: memLimit endOfMemory: memEnd
+ 	"Set the dimentions of the heap, answering the start of oldSpace."
- setHeapBase: ignored memoryLimit: memLimit endOfMemory: memEnd
  	self setMemoryLimit: memLimit.
+ 	self setEndOfMemory: memEnd.
+ 	^heapBase!
- 	self setEndOfMemory: memEnd!

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
+ 	"Set the dimensions of the heap, answering the start of oldSpace.
+ 	 Override to position oldSpace above the cog code zone."
  	super setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd.
+ 	^oldSpaceStart := newSpaceLimit + coInterpreter cogCodeSize!
- 	oldSpaceStart := newSpaceLimit + coInterpreter cogCodeSize!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
+ 	"Set the dimensions of the heap, answering the start of oldSpace.
+ 	 Override to add a guard page beneath the heap."
+ 	"As invoked by CogVMSimulator>>openOn:extraBytes: baseOfHeap contains the combined
- 	"As invoced by CogVMSimulator>>openOn:extraBytes: baseOfHeap contains the combined
  	 zone sizes for cog methods, stack zone, etc.  The memory map in SqueakV3 looks like
  		0:	cogCode
  			stackZone
  			methodCache
  			primTraceLog
  			rumpCStack
  		heapBase:
  			nilObj etc
  	 But here in Spur we want
+ 		0:	guardPage
+ 		guardPageSize:
+ 			newSpace:
+ 				past/future survivor space
+ 				past/future survivor space
+ 				eden
- 		0:	(newSpace):
- 			past/future survivor space
- 			past/future survivor space
- 			eden
  		M:
  			cogCode
  			stackZone
  			methodCache
  			primTraceLog
  			rumpCStack
  		heapBase:
  			nilObj etc"
  	super setHeapBase: Cogit guardPageSize memoryLimit: memLimit endOfMemory: memEnd.
+ 	^oldSpaceStart := newSpaceLimit + baseOfHeap!
- 	oldSpaceStart := newSpaceLimit + baseOfHeap.
- 	coInterpreter heapBase: oldSpaceStart.!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'spur bootstrap') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes) // 4.
  	"N.B. This layout does NOT reflect the layout of SpurCoMemoryManager"
  	newSpaceStart := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + newSpaceStart.
+ 	oldSpaceStart := newSpaceLimit := newSpaceBytes + newSpaceStart.
- 	newSpaceLimit := newSpaceBytes + newSpaceStart.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
  	scavenger := SpurGenerationScavengerSimulator new.
  	scavenger manager: self.
  	scavenger newSpaceStart: newSpaceStart
  				newSpaceBytes: newSpaceBytes
  				edenBytes: newSpaceBytes * self scavengerDenominator
  						- self numSurvivorSpaces // self scavengerDenominator!

Item was added:
+ ----- Method: SpurMemoryManager>>byteSizeOfInstanceOf: (in category 'indexing primitive support') -----
+ byteSizeOfInstanceOf: classObj
+ 	| instSpec classFormat numSlots |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	(self isFixedSizePointerFormat: instSpec) ifFalse:
+ 		[^PrimErrBadReceiver negated]. "indexable"
+ 	numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 	^self objectBytesForSlots: numSlots!

Item was added:
+ ----- Method: SpurMemoryManager>>byteSizeOfInstanceOf:withIndexableSlots: (in category 'indexing primitive support') -----
+ byteSizeOfInstanceOf: classObj withIndexableSlots: nElements
+ 	| instSpec classFormat numSlots |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	instSpec caseOf: {
+ 		[self arrayFormat]	->
+ 			[numSlots := nElements].
+ 		[self indexablePointersFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements].
+ 		[self weakArrayFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements].
+ 		[self sixtyFourBitIndexableFormat]	->
+ 			[numSlots := self wordSize = 4 ifTrue: [nElements * 2] ifFalse: [nElements]].
+ 		[self firstLongFormat]	->
+ 			[numSlots := self wordSize = 4 ifTrue: [nElements] ifFalse: [nElements + 1 // 2]].
+ 		[self firstShortFormat]	->
+ 			[numSlots := self wordSize = 4 ifTrue: [nElements + 1 // 2] ifFalse: [nElements + 3 // 4]].
+ 		[self firstByteFormat]	->
+ 			[numSlots := nElements + (self wordSize - 1) // self wordSize] }
+ 		otherwise: [^PrimErrBadReceiver negated]. "non-indexable or CompiledMethod"
+ 	^self objectBytesForSlots: numSlots!

Item was changed:
  ----- Method: SpurMemoryManager>>fullGC (in category 'gc - global') -----
  fullGC
+ 	"Perform a full lazy compacting GC.  Answer the size of the largest free chunk."
  	<inline: false>
  	needGCFlag := false.
  	gcStartUsecs := self ioUTCMicrosecondsNow.
  	statMarkCount := 0.
  	coInterpreter preGCAction: GCModeFull.
  	self globalGarbageCollect.
  	coInterpreter postGCAction: GCModeFull.
  	statFullGCs := statFullGCs + 1.
  	statGCEndUsecs := self ioUTCMicrosecondsNow.
+ 	statFullGCUsecs := statFullGCUsecs + (statGCEndUsecs - gcStartUsecs).
+ 	^(freeLists at: 0) ~= 0
+ 		ifTrue: [self bytesInObject: self findLargestFreeChunk]
+ 		ifFalse: [0]!
- 	statFullGCUsecs := statFullGCUsecs + (statGCEndUsecs - gcStartUsecs).!

Item was changed:
  ----- Method: SpurMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
+ 	"Set the dimensions of the heap, answering the start of oldSpace."
  	"Transcript
  		cr; nextPutAll: 'heapBase: '; print: baseOfHeap; nextPut: $/; nextPutAll: baseOfHeap hex;
  		nextPutAll: ' memLimit '; print: memLimit; nextPut: $/; nextPutAll: memLimit hex;
  		nextPutAll: ' memEnd '; print: memEnd; nextPut: $/; nextPutAll: memEnd hex; cr; flush."
  	"This is a little counter-intuitive.  Eden must include interpreterAllocationReserveBytes."
  	newSpaceStart := baseOfHeap.
  	newSpaceLimit := baseOfHeap
  					 + self newSpaceBytes
  					 + coInterpreter interpreterAllocationReserveBytes.
  	scavenger
  		newSpaceStart: newSpaceStart
  		newSpaceBytes: newSpaceLimit - newSpaceStart
  		edenBytes: newSpaceLimit - newSpaceStart
  				   * (self scavengerDenominator - self numSurvivorSpaces) // self scavengerDenominator.
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start.
  
  	freeOldSpaceStart := memEnd.
  	endOfMemory := memLimit.
+ 	oldSpaceStart := newSpaceLimit.
+ 	^oldSpaceStart!
- 	oldSpaceStart := newSpaceLimit!

Item was added:
+ ----- Method: SpurMemoryManager>>totalByteSizeOf: (in category 'indexing primitive support') -----
+ totalByteSizeOf: oop
+ 	^(self isImmediate: oop)
+ 		ifTrue: [0]
+ 		ifFalse: [self bytesInObject: oop]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>printOopShortInner: (in category 'debug printing') -----
  printOopShortInner: oop
  	| classOop name nameLen |
  	<var: #name type: #'char *'>
  	<inline: true>
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
+ 			[^self
+ 				printChar: $$;
- 			[self printChar: $$;
  				printChar: (objectMemory characterValueOf: oop);
  				printChar: $(;
  				printHex: (objectMemory integerValueOf: oop);
+ 				printChar: $)].
+ 		^self
+ 			printNum: (objectMemory integerValueOf: oop);
- 				printChar: $).
- 			 ^nil].
- 		self printNum: (objectMemory integerValueOf: oop);
  			printChar: $(;
  			printHex: (objectMemory integerValueOf: oop);
+ 			printChar: $)].
- 			printChar: $).
- 		 ^nil].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
+ 		[^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
- 		[self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  						ifTrue: [' is misaligned']
+ 						ifFalse: [' is not on the heap'])].
- 						ifFalse: [' is not on the heap']); cr.
- 		 ^nil].
  	(self isFloatObject: oop) ifTrue:
+ 		[^self printFloat: (self dbgFloatValueOf: oop)].
- 		[self printFloat: (self dbgFloatValueOf: oop).
- 		 ^nil].
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	(objectMemory addressCouldBeObj: classOop) ifFalse:
+ 		[^self print: 'a ??'].
- 		[self print: 'a ??'. ^nil].
  	(objectMemory numSlotsOf: classOop) = metaclassNumSlots ifTrue:
+ 		[^self printNameOfClass: oop count: 5].
+ 	oop = objectMemory nilObject ifTrue: [^self print: 'nil'].
+ 	oop = objectMemory trueObject ifTrue: [^self print: 'true'].
+ 	oop = objectMemory falseObject ifTrue: [^self print: 'false'].
- 		[self printNameOfClass: oop count: 5.
- 		 ^nil].
- 	oop = objectMemory nilObject ifTrue: [self print: 'nil'. ^nil].
- 	oop = objectMemory trueObject ifTrue: [self print: 'true'. ^nil].
- 	oop = objectMemory falseObject ifTrue: [self print: 'false'. ^nil].
  	nameLen := self lengthOfNameOfClass: classOop.
+ 	nameLen = 0 ifTrue: [^self print: 'a ??'].
- 	nameLen = 0 ifTrue: [self print: 'a ??'. ^nil].
  	name := self nameOfClass: classOop.
  	nameLen = 10 ifTrue:
  		[(self str: name n: 'ByteString' cmp: 10) not "strncmp is weird" ifTrue:
+ 			[^self printChar: $'; printStringOf: oop; printChar: $'].
- 			[self printChar: $'; printStringOf: oop; printChar: $'.
- 			 ^nil].
  		 (self str: name n: 'ByteSymbol' cmp: 10) not "strncmp is weird" ifTrue:
+ 			[self printChar: $#; printStringOf: oop. ^self]].
- 			[self printChar: $#; printStringOf: oop.
- 			 ^nil]].
  	(nameLen = 9 and: [(self str: name n: 'Character' cmp: 9) not]) ifTrue:
+ 		[^self printChar: $$; printChar: (objectMemory integerValueOf: (objectMemory fetchPointer: 0 ofObject: oop))].
- 		[self printChar: $$; printChar: (objectMemory integerValueOf: (objectMemory fetchPointer: 0 ofObject: oop)).
- 		 ^nil].
  	self print: 'a(n) '.
  	self
  		cCode: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]
  		inSmalltalk:
  			[name isString
  				ifTrue: [self print: name]
  				ifFalse: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]].
  	"Try to spot association-like things; they're all subclasses of LookupKey"
  	((objectMemory instanceSizeOf: classOop) = (ValueIndex + 1)
  	 and: [(self superclassOf: classOop) = (self superclassOf: (objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation)))
  	 and: [objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop)]]) ifTrue:
  		[self space;
  			printOopShort: (objectMemory fetchPointer: KeyIndex ofObject: oop);
  			print: ' -> ';
  			printHex: (objectMemory fetchPointer: ValueIndex ofObject: oop)]!

Item was changed:
  ----- Method: StackInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  	"Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  	"This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
  
+ 	| headerStart headerSize headerFlags dataSize oldBaseAddr swapBytes
+ 	  minimumMemory bytesRead bytesToShift heapSize firstSegSize
+ 	  hdrEdenBytes hdrMaxExtSemTabSize hdrNumStackPages |
- 	| swapBytes headerStart headerSize dataSize oldBaseAddr hdrNumStackPages
- 	  minimumMemory heapBase bytesRead bytesToShift heapSize hdrEdenBytes
- 	  headerFlags hdrMaxExtSemTabSize firstSegSize |
  	<var: #f type: #sqImageFile>
  	<var: #dataSize type: #'size_t'>
- 	<var: #heapBase type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - BytesPerWord.  "record header start position"
  
  	headerSize			:= self getLongFromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	hdrEdenBytes		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"decrease Squeak object heap to leave extra memory for the VM"
  	heapSize := desiredHeapSize
  				+ objectMemory newSpaceBytes
  				+ self interpreterAllocationReserveBytes.
  	heapSize := self reserveExtraCHeap: heapSize Bytes: extraVMMemory.
  
  	"compare memory requirements with availability".
  	minimumMemory := dataSize + objectMemory newSpaceBytes + self interpreterAllocationReserveBytes.
  	heapSize < minimumMemory ifTrue:
  		[self insufficientMemorySpecifiedError].
  
  	"allocate a contiguous block of memory for the Squeak heap"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
+ 	objectMemory memory ifNil: [self insufficientMemoryAvailableError].
- 	objectMemory memory = nil ifTrue: [self insufficientMemoryAvailableError].
  
- 	heapBase := objectMemory memory.
  	objectMemory
+ 		setHeapBase: objectMemory memory
+ 		memoryLimit: objectMemory memory + heapSize
+ 		endOfMemory: objectMemory memory + dataSize.
- 		setHeapBase: heapBase
- 		memoryLimit: (heapBase + heapSize) - 24  "decrease memoryLimit a tad for safety"
- 		endOfMemory: heapBase + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	^dataSize!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveFullGC (in category 'memory space primitives') -----
  primitiveFullGC
+ 	"Do a full garbage collection.  In SqueakV3ObjectMemory, answer the number
+ 	 of bytes available (including swap space if dynamic memory management is
+ 	 supported).  In Spur, answer the size of the largest free chunk."
- 	"Do a full garbage collection and return the number of bytes available.
- 	 If on SqueakV3ObjectMemory include swap space if dynamic memory
- 	 management is supported."
  
- 	objectMemory fullGCLock > 0 ifTrue:
- 		[^self primitiveFailFor: PrimErrInappropriate].
  	self externalWriteBackHeadFramePointers.
+ 	super primitiveFullGC!
- 	objectMemory hasSpurMemoryManagerAPI ifFalse:
- 		[objectMemory incrementalGC].  "maximimize space for forwarding table"
- 	objectMemory fullGC.
- 	"In Spur we exclude swap space."
- 	self pop: 1
- 		thenPushInteger: (objectMemory hasSpurMemoryManagerAPI
- 							ifTrue: [objectMemory bytesLeftInOldSpace]
- 							ifFalse: [objectMemory bytesLeft: true])!



More information about the Vm-dev mailing list