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

commits at source.squeak.org commits at source.squeak.org
Sat Nov 16 01:07:00 UTC 2013


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

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

Name: VMMaker.oscog-eem.511
Author: eem
Time: 15 November 2013, 5:04:13.256 pm
UUID: 2a9dbb56-4151-4ebd-a674-e445ed58b0c8
Ancestors: VMMaker.oscog-eem.510

Check-point cmmit prior to changing endOfMemory to be just past
the last bridge.  This for fixing the bug which is the last freeChunk
ending past the last bridge, not at the last bridge.

Fix Integer>>asUnsignedInteger for simulation when printing
frames in the StackInterpreter (which are negative there-in).

Add explicit bootstrapping inst vars to the StackInterpreterSimulator
and Spur32BitMMLESimulator now that there is a segment during the
bootstrap.

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

Item was changed:
  ----- Method: Integer>>asUnsignedInteger (in category '*VMMaker-interpreter simulator') -----
  asUnsignedInteger
- 	self assert: self >= 0.
  	^self!

Item was changed:
  Spur32BitMemoryManager subclass: #Spur32BitMMLESimulator
+ 	instanceVariableNames: 'bootstrapping'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManagerSimulation'!

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

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>bootstrapping: (in category 'accessing') -----
+ bootstrapping: aBoolean
+ 	bootstrapping := aBoolean.
+ 	segmentManager initForBootstrap!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>growOldSpaceByAtLeast: (in category 'growing/shrinking memory') -----
+ growOldSpaceByAtLeast: minAmmount
+ 	"Attempt to grow memory by at least minAmmount.
+ 	 Answer the size of the new segment, or nil if the attempt failed.
+ 	 Override to not grow during the Spur image bootstrap."
+ 	^bootstrapping ifFalse:
+ 		[super growOldSpaceByAtLeast: minAmmount]!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>initialize (in category 'initialization') -----
+ initialize
+ 	super initialize.
+ 	bootstrapping := false!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>memoryBaseForImageRead (in category 'snapshot') -----
+ memoryBaseForImageRead
+ 	"Answer the address to read the image into.  Override so that when bootstrapping,
+ 	 the segmentManager's segments are undisturbed in adjustSegmentSwizzlesBy:"
+ 	^bootstrapping
+ 		ifTrue: [0] 
+ 		ifFalse: [super memoryBaseForImageRead]!

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>
- 	| endBridgeBytes |
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
- 	endBridgeBytes := 2 * self baseHeaderSize.
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
+ 					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes) // 4.
- 					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes + endBridgeBytes) // 4.
  	startOfMemory := codeBytes + stackBytes.
+ 	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes - self bridgeSize.
- 	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + startOfMemory.
  	newSpaceLimit := newSpaceBytes + startOfMemory.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
  	scavenger := SpurGenerationScavengerSimulator new
  					manager: self
  					newSpaceStart: startOfMemory
  					newSpaceBytes: newSpaceBytes
  					edenBytes: newSpaceBytes * self scavengerDenominator - self numSurvivorSpaces // self scavengerDenominator!

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

Item was changed:
  ----- Method: SpurMemoryManager>>freeChunkWithBytes:at: (in category 'free space') -----
  freeChunkWithBytes: bytes at: address
  	<inline: false>
  	| freeChunk |
  	self assert: (lastSubdividedFreeChunk := address) ~= 0.
  	freeChunk := self initFreeChunkWithBytes: bytes at: address.
+ 	self assert: (self isInMemory: (self addressAfter: freeChunk)).
  	self addToFreeList: freeChunk bytes: bytes.
  	self assert: freeChunk = (self objectStartingAt: address).
  	^freeChunk!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeFreeSpacePostLoad: (in category 'snapshot') -----
  initializeFreeSpacePostLoad: freeListObj
  	"Reinitialize the free list info.  The freeLists object needs to be swizzled
  	 because its neither a free, nor a pointer object.  Free objects have already
  	 been swizzled in adjustAllOopsBy:"
  	
  	self assert: (self numSlotsOf: freeListObj) = self numFreeLists.
  	self assert: (self formatOf: freeListObj) = (self wordSize = 4
  													ifTrue: [self firstLongFormat]
  													ifFalse: [self sixtyFourBitIndexableFormat]).
- 
  	freeLists := self firstIndexableField: freeListObj.
+ 	freeListsMask := 0.
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[freeListsMask := freeListsMask bitOr: (1 << i).
+ 			 freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]].
+ 	totalFreeOldSpace := self totalFreeListBytes.
+ 	self checkFreeSpace!
- 			 segmentManager numSegments > 0 ifTrue: "false in Spur image bootstrap"
- 				[freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]]].
- 	totalFreeOldSpace := self totalFreeListBytes!

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.
  
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
+ 	specialObjectsOop := segmentManager swizzleObj: specialObjectsOop.
  
- 	segmentManager numSegments > 0 "false if Spur image bootstrap"
- 		ifTrue: [specialObjectsOop := segmentManager swizzleObj: specialObjectsOop]
- 		ifFalse: [self assert: bytesToShift = 0].
- 
  	"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 = newSpaceLimit.
  	self assert: falseObj = (self objectAfter: nilObj).
  	self assert: trueObj = (self objectAfter: falseObj).
  	freeListObj := self objectAfter: trueObj.
  	self reInitializeClassTablePostLoad: (self objectAfter: freeListObj).
- 	self initializeFreeSpacePostLoad: freeListObj.
  	markStack := self swizzleObjStackAt: MarkStackRootIndex.
  	weaklingStack := self swizzleObjStackAt: WeaklingStackRootIndex.
  	ephemeronQueue := self swizzleObjStackAt: EphemeronQueueRootIndex.
  
  	segmentManager collapseSegmentsPostSwizzle.
+ 	self initializeFreeSpacePostLoad: freeListObj.
  
  	self initializeNewSpaceVariables.
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
  
  	"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"!

Item was changed:
  ----- Method: SpurMemoryManager>>isValidFreeObject: (in category 'free space') -----
  isValidFreeObject: objOop
  	| chunk |
  	^(self addressCouldBeObj: objOop)
  	  and: [(self isFreeObject: objOop)
+ 	  and: [(self isInMemory: (self addressAfter: objOop))
  	  and: [((chunk := (self fetchPointer: self freeChunkNextIndex ofFreeChunk: objOop)) = 0
  		   or: [self isFreeObject: chunk])
  	  and: [(self bytesInObject: objOop) / self allocationUnit < self numFreeLists
  		    or: [((chunk := (self fetchPointer: self freeChunkParentIndex ofFreeChunk: objOop)) = 0
  			   or: [self isFreeObject: chunk])
  			  and: [((chunk := (self fetchPointer: self freeChunkSmallerIndex ofFreeChunk: objOop)) = 0
  				    or: [self isFreeObject: chunk])
  			  and: [(chunk := (self fetchPointer: self freeChunkLargerIndex ofFreeChunk: objOop)) = 0
+ 				    or: [self isFreeObject: chunk]]]]]]]]!
- 				    or: [self isFreeObject: chunk]]]]]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>isValidSegmentBridge: (in category 'segments') -----
  isValidSegmentBridge: objOop
  	"Maybe this should be in SpurSegmentManager only"
+ 	^(objOop = endOfMemory or: [self addressCouldBeObj: objOop])
- 	^(self addressCouldBeObj: objOop)
  	 and: [(self isSegmentBridge: objOop)
  	 and: [self hasOverflowHeader: objOop]]!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'gc - scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
  	"Run the scavenger."
  
  	self assert: remapBufferCount = 0.
+ 	self assert: scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes.
- 	self assert: (segmentManager numSegments = 0 "true in the spur image bootstrap"
- 				or: [scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes]).
  	self checkFreeSpace.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter
  		preGCAction: GCModeScavenge;
  		"would prefer this to be in mapInterpreterOops, but
  		 compatibility with ObjectMemory dictates it goes here."
  		flushMethodCacheFrom: startOfMemory to: newSpaceLimit.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	self doScavenge: tenuringCriterion.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  	statRootTableCount := scavenger rememberedSetSize.
  
  	coInterpreter postGCAction: GCModeScavenge.
  	self runLeakCheckerForFullGC: false.
  
  	self checkFreeSpace!

Item was changed:
  ----- Method: SpurMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: heapBase memoryLimit: memLimit endOfMemory: memEnd
  	"Transcript
  		cr; nextPutAll: 'heapBase: '; print: heapBase; nextPut: $/; nextPutAll: heapBase hex;
  		nextPutAll: ' memLimit '; print: memLimit; nextPut: $/; nextPutAll: memLimit hex;
  		nextPutAll: ' memEnd '; print: memEnd; nextPut: $/; nextPutAll: memEnd hex; cr; flush."
+ 	startOfMemory := heapBase.
  	newSpaceLimit := heapBase
  					 + self newSpaceBytes
  					 + coInterpreter interpreterAllocationReserveBytes.
  	freeOldSpaceStart := memEnd.
  	endOfMemory := memLimit.
  	scavenger
  		newSpaceStart: heapBase
  		newSpaceBytes: newSpaceLimit - heapBase
  		edenBytes: newSpaceLimit - heapBase
  				   * (self scavengerDenominator - self numSurvivorSpaces) // self scavengerDenominator.
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start!

Item was changed:
  ----- Method: SpurSegmentManager>>collapseSegmentsPostSwizzle (in category 'snapshot') -----
  collapseSegmentsPostSwizzle
  	"The image has been loaded, old segments reconstructed, and the heap
  	 swizzled into a single contiguous segment.  Collapse the segments into one."
  	<inline: false>
- 	| bridge |
  	canSwizzle := false.
+ 	self cCode: []
+ 		inSmalltalk:
+ 			[segments ifNil:
+ 				[self allocateOrExtendSegmentInfos]].
- 	firstSegmentSize ifNil: "true when used by SpurBootstrap to transform an image"
- 		[^self].
- 
  	numSegments := 1.
  	(segments at: 0)
  		segStart: manager newSpaceLimit;
+ 		segSize: manager endOfMemory + manager bridgeSize - manager newSpaceLimit.
+ 	manager bootstrapping
+ 		ifTrue:
+ 			["finally plant a bridge at the end of the coalesced segment and cut back the
+ 			  manager's notion of the end of memory to immediately before the bridge."
+ 			 self assert: manager endOfMemory = ((segments at: 0) segLimit - manager bridgeSize).
+ 			 manager initSegmentBridgeWithBytes: manager bridgeSize at: manager endOfMemory]
+ 		ifFalse:
+ 			[self assert: (manager isValidSegmentBridge: manager endOfMemory).
+ 			 self assert: (manager numSlotsOfAny: manager endOfMemory) = 0]!
- 		segSize: manager endOfMemory - manager newSpaceLimit.
- 	"finally plant a bridge at the end of the coalesced segment and cut back the
- 	 manager's notion of the end of memory to immediately before the bridge."
- 	bridge := manager endOfMemory - manager bridgeSize.
- 	self assert: bridge = ((segments at: 0) segLimit - manager bridgeSize).
- 	manager
- 		initSegmentBridgeWithBytes: manager bridgeSize at: bridge;
- 		setEndOfMemory: bridge!

Item was added:
+ ----- Method: SpurSegmentManager>>initForBootstrap (in category 'spur bootstrap') -----
+ initForBootstrap
+ 	self allocateOrExtendSegmentInfos!

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

Item was changed:
  ----- Method: SpurSegmentManager>>writeImageToFile: (in category 'snapshot') -----
  writeImageToFile: aBinaryStream
  	| total |
  	total := 0.
+ 	self assert: (segments at: numSegments - 1) segLimit - manager bridgeSize = manager endOfMemory.
  	firstSegmentSize ifNotNil:
  		[self assert: firstSegmentSize = (segments at: 0) segSize].
  	0 to: numSegments - 1 do:
  		[:i| | nextSegSize |
  		nextSegSize := i = (numSegments - 1)
  							ifTrue: [0]
  							ifFalse: [(segments at: i + 1) segSize].
  		total := total + (self writeSegment: (self addressOf: (segments at: i))
  							nextSegmentSize: nextSegSize
  							toFile: aBinaryStream)].
  	^total!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'bootstrapping byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat'
- 	instanceVariableNames: 'byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(StackInterpreterSimulator new openOn: Smalltalk imageName) test
  
  	((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  		openOn: 'ns101.image') test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was added:
+ ----- Method: StackInterpreterSimulator>>bootstrapping (in category 'spur bootstrap') -----
+ bootstrapping
+ 	^bootstrapping!

Item was added:
+ ----- Method: StackInterpreterSimulator>>bootstrapping: (in category 'spur bootstrap') -----
+ bootstrapping: aBoolean
+ 	bootstrapping := aBoolean.
+ 	objectMemory ifNotNil:
+ 		[objectMemory bootstrapping: aBoolean]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the StackInterpreterSimulator when running the interpreter
  	 inside Smalltalk. The primary responsibility of this method is to allocate
  	 Smalltalk Arrays for variables that will be declared as statically-allocated
  	 global arrays in the translated code."
  
+ 	bootstrapping := false.
+ 
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	objectMemory coInterpreter: self.
  
  	"Note: we must initialize ConstMinusOne differently for simulation,
  		due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  
  	methodCache := Array new: MethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	pluginList := {'' -> self }.
  	mappedPluginEntries := #().
  	desiredNumStackPages := desiredEdenBytes := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := 0.
  	sendCount := 0.
  	quitBlock := [^ self].
  	traceOn := true.
  	printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	transcript := Transcript.
  	displayForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := false.
  	extSemTabSize := 256.
  	disableBooleanCheat := false!

Item was added:
+ ----- Method: StackInterpreterSimulator>>interpreterAllocationReserveBytes (in category 'stack pages') -----
+ interpreterAllocationReserveBytes
+ 	^bootstrapping
+ 		ifTrue: [0]
+ 		ifFalse: [super interpreterAllocationReserveBytes]!



More information about the Vm-dev mailing list