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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 11 18:21:33 UTC 2013


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

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

Name: VMMaker.oscog-eem.556
Author: eem
Time: 11 December 2013, 10:19:12.819 am
UUID: c0ead074-8810-42cf-8e82-fbcf0a958348
Ancestors: VMMaker.oscog-eem.555

Refactor snapshot to avoid the duplicate context berveavement pass.
voidVMStateForSnapshot => voidVMStateForSnapshotFlushingExternalPrimitivesIf:

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

Item was removed:
- ----- Method: CoInterpreter>>ensureAllContextsHaveBytecodePCsOrAreBereaved (in category 'frame access') -----
- ensureAllContextsHaveBytecodePCsOrAreBereaved
- 	"Enumerate all contexts preparing them for a snapshot.  Map all native pcs to bytecoded pcs.
- 	 Convert widowed contexts to single contexts so that the snapshot contains only single contexts.
- 	 This allows the being married test to avoid checking for a context's frame pointer being in bounds
- 	 since all frame pointers must have been created in the current system and so be in bounds.
- 	 Thanks to Greg Nuyens for this idea."
- 	objectMemory allObjectsDo:
- 		[:oop|
- 		 (objectMemory isContextNonImm: oop) ifTrue:
- 			[(self isMarriedOrWidowedContext: oop)
- 				ifTrue: "The stack pages have already been discarded.  Any remaining married contexts are actually widows."
- 					[self markContextAsDead: oop]
- 				ifFalse:
- 					[| decodedIP |
- 					decodedIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: oop.
- 					((objectMemory isIntegerObject: decodedIP)
- 					 and: [decodedIP signedIntFromLong < 0]) ifTrue:
- 						[decodedIP := self mustMapMachineCodePC: (objectMemory integerValueOf: decodedIP)
- 											context: oop.
- 						 objectMemory storePointerUnchecked: InstructionPointerIndex ofObject: oop withValue: decodedIP]]]]!

Item was removed:
- ----- Method: CoInterpreter>>voidVMStateForSnapshot (in category 'frame access') -----
- voidVMStateForSnapshot
- 	"Make sure that all VM state that affects the heap contents is voided so that the heap is ready
- 	 to be snapshotted. Answer the activeContext object that should be stored in the snapshot."
- 	<inline: false>
- 	| activeContext |
- 	instructionPointer := 0. "in case of code compactions."
- 	activeContext := self divorceAllFrames.
- 	self ensureAllContextsHaveBytecodePCsOrAreBereaved.
- 	cogit voidCogCompiledCode.
- 	^activeContext!

Item was added:
+ ----- Method: CoInterpreter>>voidVMStateForSnapshotFlushingExternalPrimitivesIf: (in category 'frame access') -----
+ voidVMStateForSnapshotFlushingExternalPrimitivesIf: flushExtPrims
+ 	"Make sure that all VM state that affects the heap contents is voided so that the heap is
+ 	 ready to be snapshotted.  If flushExtPrims is true, flush references to external
+ 	 primitives in methods.  Answer the activeContext that should be stored in the snapshot."
+ 	<inline: false>
+ 	| activeContext |
+ 	instructionPointer := 0. "in case of code compactions."
+ 	activeContext := super voidVMStateForSnapshotFlushingExternalPrimitivesIf: flushExtPrims.
+ 	cogit voidCogCompiledCode.
+ 	^activeContext!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveLongRunningPrimitiveSemaphore (in category 'process primitives') -----
  primitiveLongRunningPrimitiveSemaphore
  	"Primitive. Install the semaphore to be used for collecting long-running primitives, 
  	 or nil if no semaphore should be used."
  	| sema flushState activeContext |
  	<export: true>
  	sema := self stackValue: 0.
  	((objectMemory isIntegerObject: sema)
  	or: [self methodArgumentCount ~= 1]) ifTrue:
  		[^self primitiveFail].
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := longRunningPrimitiveCheckSemaphore notNil.
  			 longRunningPrimitiveCheckSemaphore := nil]
  		ifFalse:
  			[flushState := longRunningPrimitiveCheckSemaphore isNil.
  			 (objectMemory fetchClassOfNonImm: sema) = (objectMemory splObj: ClassSemaphore) ifFalse:
  				[^self primitiveFail].
  			 longRunningPrimitiveCheckSemaphore := sema].
  	"If we've switched checking on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop setting
  	 newMethod in machine code primitive invocations, and so generate
  	 slightly different code from here on in."
  	flushState ifTrue:
  		[self push: instructionPointer.
+ 		 activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 		 activeContext := self voidVMStateForSnapshot.
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self assert: (((self stackValue: 0) = objectMemory nilObject and: [longRunningPrimitiveCheckSemaphore isNil])
  				  or: [(self stackValue: 0) = longRunningPrimitiveCheckSemaphore
  					  and: [(objectMemory fetchClassOfNonImm: sema) = (objectMemory splObj: ClassSemaphore)]])].
  	self voidLongRunningPrimitive: 'install'.
  	self pop: 1.
  	flushState ifTrue:
  		[self siglong: reenterInterpreter jmp: ReturnToInterpreter]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveProfileSemaphore (in category 'process primitives') -----
  primitiveProfileSemaphore
  	"Primitive. Install the semaphore to be used for profiling, 
  	or nil if no semaphore should be used.
  	See also primitiveProfileStart."
  	| sema flushState activeContext |
  	<export: true>
  	sema := self stackValue: 0.
  	((objectMemory isIntegerObject: sema)
  	or: [self methodArgumentCount ~= 1]) ifTrue:
  		[^self primitiveFail].
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := profileSemaphore ~= objectMemory nilObject]
  		ifFalse:
  			[flushState := profileSemaphore = objectMemory nilObject.
  			 (objectMemory fetchClassOfNonImm: sema) = (objectMemory splObj: ClassSemaphore) ifFalse:
  				[^self primitiveFail]].
  	profileSemaphore := sema.
  	"If we've switched profiling on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop
  	 testing the profile clock in machine code primitive invocations,
  	 and so generate slightly different code from here on in."
  	flushState ifTrue:
  		[self push: instructionPointer.
+ 		 activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 		 activeContext := self voidVMStateForSnapshot.
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self assert: (((self stackValue: 0) = objectMemory nilObject and: [profileSemaphore = objectMemory nilObject])
  				  or: [(self stackValue: 0) = profileSemaphore
  					  and: [(objectMemory fetchClassOfNonImm: sema) = (objectMemory splObj: ClassSemaphore)]])].
  	profileProcess := profileMethod := objectMemory nilObject.
  	self pop: 1.
  	flushState ifTrue:
  		[self siglong: reenterInterpreter jmp: ReturnToInterpreter]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveVoidVMState (in category 'system control primitives') -----
  primitiveVoidVMState
  	"Void all internal VM state in the stack and machine code zones
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	| activeContext |
  	self push: instructionPointer.
+ 	activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 	activeContext := self voidVMStateForSnapshot.
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: NewObjectMemorySimulator>>storePointerUnchecked:ofObject:withValue: (in category 'interpreter access') -----
  storePointerUnchecked: index ofObject: oop withValue: valuePointer
  	"Override to ensure acess is within the heap, and within the object"
  	| fmt hdr |
  	self assert: oop >= self startOfMemory.
  	hdr := self baseHeader: oop.
  	fmt := self formatOfHeader: hdr.
+ 	self assert: ((fmt <= self lastPointerFormat or: [fmt >= self firstCompiledMethodFormat])
+ 				and: [index >= 0 and: [index < (self lengthOf: oop baseHeader: hdr format: fmt)]]).
- 	thisContext sender selector ~~ #snapshotCleanUp ifTrue:
- 		[self assert: ((fmt <= self lastPointerFormat or: [fmt >= self firstCompiledMethodFormat])
- 					and: [index >= 0 and: [index < (self lengthOf: oop baseHeader: hdr format: fmt)]])].
  	^super storePointerUnchecked: index ofObject: oop withValue: valuePointer!

Item was added:
+ ----- Method: ObjectMemory>>garbageCollectForSnapshot (in category 'image save/restore') -----
+ garbageCollectForSnapshot
+ 	self incrementalGC. "maximimize space for forwarding table"
+ 	self fullGC.
+ 	self clearRootsTable!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
  	"This list records the valid senders of isIntegerObject: as we replace uses of
  	  isIntegerObject: by isImmediate: where appropriate."
  	| sel |
  	sel := thisContext sender method selector.
  	(#(	DoIt
  		DoItIn:
  		on:do: "from the debugger"
  		makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		objCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		bytecodePrimAtPut
  		commonAt:
  		commonAtPut:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
  		primitiveVMParameter
  		checkIsStillMarriedContext:currentFP:
  		displayBitsOf:Left:Top:Right:Bottom:
  		fetchStackPointerOf:
  		primitiveContextAt
  		primitiveContextAtPut
  		subscript:with:storing:format:
  		printContext:
  		compare31or32Bits:equal:
  		signed64BitValueOf:
  		primDigitMultiply:negative:
  		digitLength:
  		isNegativeIntegerValueOf:
  		magnitude64BitValueOf:
  		primitiveMakePoint
  		primitiveAsCharacter
  		primitiveInputSemaphore
  		baseFrameReturn
  		primitiveExternalCall
  		primDigitCompare:
  		isLiveContext:
  		numPointerSlotsOf:
  		fileValueOf:
  		loadBitBltDestForm
  		fetchIntOrFloat:ofObject:ifNil:
  		fetchIntOrFloat:ofObject:
  		loadBitBltSourceForm
  		loadPoint:from:
  		primDigitAdd:
  		primDigitSubtract:
  		positive64BitValueOf:
  		digitBitLogic:with:opIndex:
  		signed32BitValueOf:
  		isNormalized:
  		primDigitDiv:negative:
  		bytesOrInt:growTo:
  		primitiveNewMethod
  		isCogMethodReference:
  		functionForPrimitiveExternalCall:
  		genSpecialSelectorArithmetic
  		genSpecialSelectorComparison
  		ensureContextHasBytecodePC:
  		instVar:ofContext:
  		ceBaseFrameReturn:
  		inlineCacheTagForInstance:
  		primitiveObjectAtPut
  		commonVariable:at:put:cacheIndex:
  		primDigitBitShiftMagnitude:
  		externalInstVar:ofContext:
  		primitiveGrowMemoryByAtLeast
  		primitiveFileSetPosition
  		cogMethodDoesntLookKosher:
  		shortPrintOop:
+ 		primitiveSizeInBytesOfInstance
+ 		bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf:) includes: sel) ifFalse:
- 		primitiveSizeInBytesOfInstance) includes: sel) ifFalse:
  		[self halt].
  	^super isIntegerObject: oop!

Item was added:
+ ----- Method: SpurMemoryManager>>garbageCollectForSnapshot (in category 'snapshot') -----
+ garbageCollectForSnapshot
+ 	self flushNewSpace. "There is no place to put newSpace in the snapshot file."
+ 	self fullGC!

Item was changed:
  ----- Method: SpurMemoryManager>>mapExtraRoots (in category 'gc - global') -----
  mapExtraRoots
  	self assert: remapBufferCount = 0.
+ 	"1 to: remapBufferCount do:
+ 		[:i | | oop |
+ 		oop := remapBufferCount at: i.
+ 		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
+ 			[(self shouldRemapObj: oop) ifTrue:
+ 				[remapBuffer at: i put: (self remapObj: oop)]]]."
  	1 to: extraRootCount do:
  		[:i | | oop |
  		oop := (extraRoots at: i) at: 0.
  		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
  			[(self shouldRemapObj: oop) ifTrue:
  				[(extraRoots at: i) at: 0 put: (self remapObj: oop)]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>markAccessibleObjects (in category 'gc - global') -----
  markAccessibleObjects
  	self assert: self validClassTableRootPages.
  	self assert: segmentManager allBridgesMarked.
  	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
  
  	marking := true.
  	"This must come first to enable stack page reclamation.  It clears
  	  the trace flags on stack pages and so must preceed any marking.
  	  Otherwise it will clear the trace flags of reached pages."
  	coInterpreter initStackPageGC.
  	self markAndTraceHiddenRoots.
+ 	self markAndTraceExtraRoots.
  	self assert: self validClassTableRootPages.
  	coInterpreter markAndTraceInterpreterOops: true.
  	self assert: self validObjStacks.
  	self markWeaklingsAndMarkAndFireEphemerons.
  	self assert: self validObjStacks.
  	marking := false!

Item was added:
+ ----- Method: SpurMemoryManager>>markAndTraceExtraRoots (in category 'gc - global') -----
+ markAndTraceExtraRoots
+ 	| oop |
+ 	self assert: remapBufferCount = 0.
+ 	"1 to: remapBufferCount do:
+ 		[:i|
+ 		 oop := remapBuffer at: i.
+ 		 ((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
+ 			[self markAndTrace: oop]]."
+ 	1 to: extraRootCount do:
+ 		[:i|
+ 		oop := (extraRoots at: i) at: 0.
+ 		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
+ 			[self markAndTrace: oop]]!

Item was changed:
  ----- Method: SpurSegmentManager>>readHeapFromImageFile:dataBytes: (in category 'snapshot') -----
  readHeapFromImageFile: f dataBytes: numBytes
  	"Read numBytes of image data from f into memory at memoryBaseForImageRead.
  	 Answer the number of bytes written.  In addition, read each segment, build up the
  	 segment info, while eliminating the bridge objects that end each segment and
  	 give the size of the subsequent segment."
  	<var: #f type: #sqImageFile>
  	<inline: false>
  	| bytesRead totalBytesRead bridge nextSegmentSize oldBase newBase segInfo bridgeSpan |
  	<var: 'segInfo' type: 'SpurSegmentInfo *'>
  	self allocateOrExtendSegmentInfos.
  
  	"segment sizes include the two-header-word bridge at the end of each segment."
  	numSegments := totalBytesRead := 0.
  	oldBase := 0. "N.B. still must be adjusted by oldBaseAddr."
  	newBase := manager oldSpaceStart.
  	nextSegmentSize := firstSegmentSize.
  	bridge := firstSegmentSize + manager oldSpaceStart - manager baseHeaderSize.
  	[segInfo := self addressOf: (segments at: numSegments).
  	 segInfo
  		segStart: oldBase;					"N.B. still must be adjusted by oldBaseAddr."
  		segSize: nextSegmentSize;
  		swizzle: newBase - oldBase.	"N.B. still must be adjusted by oldBaseAddr."
  	 bytesRead := self readHeapFrom: f at: newBase dataBytes: nextSegmentSize.
  	 bytesRead > 0 ifTrue:
  			[totalBytesRead := totalBytesRead + bytesRead].
  	 bytesRead ~= nextSegmentSize ifTrue:
  		[^totalBytesRead].
  	 numSegments := numSegments + 1.
  	 bridgeSpan := manager bytesPerSlot * (manager rawOverflowSlotsOf: bridge).
  	 oldBase := oldBase + nextSegmentSize + bridgeSpan.
  	 newBase := newBase + nextSegmentSize - manager bridgeSize.
  	 nextSegmentSize := manager longLongAt: bridge.
  	 nextSegmentSize ~= 0] whileTrue:
  		[bridge := bridge - manager bridgeSize + nextSegmentSize].
  	"newBase should point just past the last bridge. all others should have been eliminated."
  	self assert: newBase - manager oldSpaceStart
  				= (totalBytesRead - (numSegments * manager bridgeSize)).
  	"set freeOldSpaceStart now for adjustAllOopsBy:"
  	manager setFreeOldSpaceStart: newBase.
+ 	"we're done. nil firstSegmentSize for a subsequent snapshot."
+ 	firstSegmentSize := nil.
  	^totalBytesRead!

Item was changed:
  ----- Method: SpurSegmentManager>>writeImageToFile: (in category 'snapshot') -----
  writeImageToFile: aBinaryStream
  	| total |
  	total := 0.
+ 	self assert: (manager endOfMemory = (segments at: numSegments - 1) segLimit
+ 				 or: [manager endOfMemory + manager bridgeSize = (segments at: numSegments - 1) segLimit]).
- 	self assert: (segments at: numSegments - 1) segLimit = 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 removed:
- ----- Method: StackInterpreter>>bereaveAllMarriedContexts (in category 'frame access') -----
- bereaveAllMarriedContexts
- 	"Enumerate all contexts and convert married contexts to widowed contexts so
- 	 that the snapshot contains only single contexts.  This allows the test for being
- 	 married to avoid checking for a context's frame pointer being in bounds.
- 	 Thanks to Greg Nuyens for this idea."
- 	<asmLabel: false>
- 	objectMemory allObjectsDo:
- 		[:obj|
- 		((objectMemory isContextNonImm: obj)
- 		  and: [self isMarriedOrWidowedContext: obj]) ifTrue:
- 			[self markContextAsDead: obj]]!

Item was added:
+ ----- Method: StackInterpreter>>bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: (in category 'frame access') -----
+ bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: flushExtPrims
+ 	"Enumerate all contexts and convert married contexts to widowed contexts so
+ 	 that the snapshot contains only single contexts.  This allows the test for being
+ 	 married to avoid checking for a context's frame pointer being in bounds.  If
+ 	 flushExtPrims is true, flush references to external primitives in methods."
+ 	<asmLabel: false>
+ 	objectMemory allObjectsDo:
+ 		[:obj| | fmt |
+ 		fmt := objectMemory formatOf: obj.
+ 		(fmt = objectMemory indexablePointersFormat
+ 		  and: [objectMemory isContextNonImm: obj]) ifTrue:
+ 			[(self isMarriedOrWidowedContext: obj) ifTrue:
+ 				[self markContextAsDead: obj].
+ 			 "Fill slots beyond top of stack with nil"
+ 			 (self fetchStackPointerOf: obj) + CtxtTempFrameStart
+ 				to: (objectMemory numSlotsOf: obj) - 1
+ 				do: [:i |
+ 					objectMemory
+ 						storePointerUnchecked: i
+ 						ofObject: obj
+ 						withValue: objectMemory nilObject]].
+ 		 "Clean out external functions from compiled methods"
+ 		 (flushExtPrims
+ 		  and: [fmt >= objectMemory firstCompiledMethodFormat]) ifTrue:
+ 			["Its primitiveExternalCall"
+ 			 (self primitiveIndexOf: obj) = PrimitiveExternalCallIndex ifTrue:
+ 				[self flushExternalPrimitiveOf: obj]]]!

Item was removed:
- ----- Method: StackInterpreter>>bereaveAndNormalizeContextsAndFlushExternalPrimitives (in category 'image save/restore') -----
- bereaveAndNormalizeContextsAndFlushExternalPrimitives
- 	"Clean up right before saving an image, sweeping memory and:
- 	* nilling out all fields of contexts above the stack pointer
- 	* bereaving widowed contexts. 
- 	* flushing external primitives.
- 	 By ensuring that all contexts are single in a snapshot (i.e. that no married contexts
- 	 exist) we can maintain the invariant that a married or widowed context's frame
- 	 reference (in its sender field) must point into the stack pages since no married or
- 	 widowed contexts are present from older runs of the system."
- 	objectMemory allObjectsDo:
- 		[:obj| | header fmt sz |
- 		 header := self longAt: obj.
- 		 fmt := objectMemory formatOfHeader: header.
- 		 "Clean out context"
- 		 (fmt = objectMemory indexablePointersFormat
- 		  and: [objectMemory isContextHeader: header]) ifTrue:
- 			["All contexts have been divorced. Bereave remaining widows."
- 			 (self isMarriedOrWidowedContext: obj) ifTrue:
- 				[self markContextAsDead: obj].
- 			 "Fill slots beyond top of stack with nil"
- 			 (self fetchStackPointerOf: obj) + CtxtTempFrameStart
- 				to: (objectMemory numSlotsOf: obj) - 1
- 				do: [:i |
- 					objectMemory
- 						storePointerUnchecked: i
- 						ofObject: obj
- 						withValue: objectMemory nilObject]].
- 		 "Clean out external functions from compiled methods"
- 		 fmt >= objectMemory firstCompiledMethodFormat ifTrue:
- 			["Its primitiveExternalCall"
- 			 (self primitiveIndexOf: obj) = PrimitiveExternalCallIndex ifTrue:
- 				[self flushExternalPrimitiveOf: obj]]].!

Item was changed:
  ----- Method: StackInterpreter>>snapshot: (in category 'image save/restore') -----
  snapshot: embedded 
  	"update state of active context"
  	| activeContext activeProc rcvr setMacType stackIndex |
  	<var: #setMacType type: #'void *'>
  
  	"For now the stack munging below doesn't deal with more than one argument.
  	 It can, and should."
  	argumentCount ~= 0 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  
  	"Need to convert all frames into contexts since the snapshot file only holds objects."
  	self push: instructionPointer.
+ 	activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: true.
- 	activeContext := self voidVMStateForSnapshot.
  
  	"update state of active process"
  	activeProc := self activeProcess.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  
+ 	tempOop := activeContext.
+ 	objectMemory garbageCollectForSnapshot.
- 	objectMemory pushRemappableOop: activeContext.
- 
- 	"garbage collect, bereave contexts and flush external methods."
- 	self snapshotCleanUp.
- 
  	"Nothing moves from here on so it is safe to grab the activeContext again."
+ 	activeContext := tempOop.
+ 	tempOop := 0.
- 	activeContext := objectMemory popRemappableOop.
  
  	self successful ifTrue:
  		["Without contexts or stacks simulate
  			rcvr := self popStack. ''pop rcvr''
  			self push: trueObj.
  		  to arrange that the snapshot resumes with true.  N.B. stackIndex is one-relative."
  		stackIndex := self quickFetchInteger: StackPointerIndex ofObject: activeContext.
  		rcvr := objectMemory fetchPointer: stackIndex + CtxtTempFrameStart - 1 ofObject: activeContext.
  		objectMemory
  			storePointerUnchecked: stackIndex + CtxtTempFrameStart - 1
  			ofObject: activeContext
  			withValue: objectMemory trueObject.
  		"now attempt to write the snapshot file"
  		self writeImageFileIO.
  		(self successful and: [embedded not]) ifTrue:
  			["set Mac file type and creator; this is a noop on other platforms"
  			setMacType := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
  			setMacType = 0 ifFalse:
  				[self cCode: '((sqInt (*)(char *, char *, char *))setMacType)(imageName, "STim", "FAST")']].
  		"Without contexts or stacks simulate
  			self pop: 1"
  		objectMemory
  			storePointerUnchecked: StackPointerIndex
  			ofObject: activeContext
  			withValue: (objectMemory integerObjectOf: stackIndex - 1)].
  
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  	self successful
  		ifTrue: [self push: objectMemory falseObject]
  		ifFalse:
  			[self push: rcvr.
  			 self justActivateNewMethod]!

Item was removed:
- ----- Method: StackInterpreter>>snapshotCleanUp (in category 'image save/restore') -----
- snapshotCleanUp
- 	"Clean up right before saving an image, garbage collecting, sweeping memory and:
- 	* nilling out all fields of contexts above the stack pointer.
- 	* flushing external primitives
- 	* bereaving widowed contexts
- 	* clearing the root bit of any object in the root table.
- 	 By ensuring that all contexts are single in a snapshot (i.e. that no married contexts
- 	 exist) we can maintain the invariant that a married or widowed context's frame
- 	 reference (in its sender field) must point into the stack pages since no married or
- 	 widowed contexts are present from older runs of the system."
- 
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue: [objectMemory flushNewSpace]
- 		ifFalse: [objectMemory incrementalGC].	"compact memory and compute the size of the memory actually in use"
- 
- 	"maximimize space for forwarding table"
- 	objectMemory fullGC.
- 
- 	self bereaveAndNormalizeContextsAndFlushExternalPrimitives.
- 
- 	objectMemory hasSpurMemoryManagerAPI ifFalse:
- 		[objectMemory clearRootsTable]!

Item was removed:
- ----- Method: StackInterpreter>>voidVMStateForSnapshot (in category 'frame access') -----
- voidVMStateForSnapshot
- 	"Make sure that all VM state that affects the heap contents is voided so that the heap is ready
- 	 to be snapshotted. Answer the activeContext object that should be stored in the snapshot."
- 	| activeContext |
- 	<inline: false>
- 	activeContext := self divorceAllFrames.
- 	self bereaveAllMarriedContexts.
- 	^activeContext!

Item was added:
+ ----- Method: StackInterpreter>>voidVMStateForSnapshotFlushingExternalPrimitivesIf: (in category 'frame access') -----
+ voidVMStateForSnapshotFlushingExternalPrimitivesIf: flushExtPrims
+ 	"Make sure that all VM state that affects the heap contents is voided so that the heap is
+ 	 ready to be snapshotted.  If flushExtPrims is true, flush references to external
+ 	 primitives in methods.  Answer the activeContext that should be stored in the snapshot."
+ 	| activeContext |
+ 	<inline: false>
+ 	activeContext := self divorceAllFrames.
+ 	self bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: flushExtPrims.
+ 	^activeContext!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: (in category 'frame access') -----
+ bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: flushExtPrims
+ 	"Enumerate all contexts and convert married contexts to widowed contexts so
+ 	 that the snapshot contains only single contexts.  This allows the test for being
+ 	 married to avoid checking for a context's frame pointer being in bounds.  If
+ 	 flushExtPrims is true, flush references to external primitives in methods."
+ 	<asmLabel: false>
+ 	objectMemory allObjectsDo:
+ 		[:obj| | fmt |
+ 		fmt := objectMemory formatOf: obj.
+ 		(fmt = objectMemory indexablePointersFormat
+ 		  and: [objectMemory isContextNonImm: obj]) ifTrue:
+ 			[(self isMarriedOrWidowedContext: obj)
+ 				ifTrue: "The stack pages have already been discarded.  Any remaining married contexts are actually widows."
+ 					[self markContextAsDead: obj]
+ 				ifFalse:
+ 					[| decodedIP |
+ 					decodedIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: obj.
+ 					((objectMemory isIntegerObject: decodedIP)
+ 					 and: [decodedIP signedIntFromLong < 0]) ifTrue:
+ 						[decodedIP := self mustMapMachineCodePC: (objectMemory integerValueOf: decodedIP)
+ 											context: obj.
+ 						 objectMemory storePointerUnchecked: InstructionPointerIndex ofObject: obj withValue: decodedIP]].
+ 			 "Fill slots beyond top of stack with nil"
+ 			 (self fetchStackPointerOf: obj) + CtxtTempFrameStart
+ 				to: (objectMemory numSlotsOf: obj) - 1
+ 				do: [:i |
+ 					objectMemory
+ 						storePointerUnchecked: i
+ 						ofObject: obj
+ 						withValue: objectMemory nilObject]].
+ 		 "Clean out external functions from compiled methods"
+ 		 (flushExtPrims
+ 		  and: [fmt >= objectMemory firstCompiledMethodFormat]) ifTrue:
+ 			["Its primitiveExternalCall"
+ 			 (self primitiveIndexOf: obj) = PrimitiveExternalCallIndex ifTrue:
+ 				[self flushExternalPrimitiveOf: obj]]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVoidVMState (in category 'system control primitives') -----
  primitiveVoidVMState
  	"Void all internal VM state in the stack and machine code zones"
  	| activeContext |
  	self push: instructionPointer.
+ 	activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 	activeContext := self voidVMStateForSnapshot.
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext!



More information about the Vm-dev mailing list