[Vm-dev] VM Maker: Cog-eem.185.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Aug 10 04:07:07 UTC 2014


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

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

Name: Cog-eem.185
Author: eem
Time: 9 August 2014, 9:06:32.998 pm
UUID: b4775a40-b52f-47cd-9031-e2a2de3a3f51
Ancestors: Cog-eem.184

Spur old to new method format conversion:
Replace relevant methods in a munged image

Refactor SpurBootstrap's execution methods into
SimulatorHarness and have the munger inherit from it.

Use  VMMaker.oscog-eem.854's changes to manage the
savedWindowSize more easily.

Needs  VMMaker.oscog-eem.854

=============== Diff against Cog-eem.184 ===============

Item was added:
+ Object subclass: #SimulatorHarness
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: 'VMObjectIndices'
+ 	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: SimulatorHarness>>interpreter:object:perform:withArguments: (in category 'bootstrap methods') -----
+ interpreter: sim object: receiver perform: selector withArguments: arguments
+ 	"Interpret an expression in oldHeap using oldInterpreter.
+ 	 Answer the result."
+ 	| fp savedpc savedsp result startByteCount |
+ 	self assert: ({receiver. selector}, arguments allSatisfy:
+ 					[:oop| oop isInteger and: [sim objectMemory addressCouldBeOop: oop]]).
+ 	savedpc := sim localIP.
+ 	savedsp := sim localSP.
+ 	sim internalPush: receiver.
+ 	arguments do: [:arg| sim internalPush: arg].
+ 	sim
+ 		argumentCount: arguments size;
+ 		messageSelector: selector.
+ 	fp := sim localFP.
+ 	startByteCount := sim byteCount.
+ 	"sim byteCount = 66849 ifTrue: [self halt]."
+ 	sim normalSend.
+ 	sim incrementByteCount. "otherwise, send is not counted"
+ 	["sim printFrame: sim localFP WithSP: sim localSP"
+ 	 "sim setBreakSelector: #elementsForwardIdentityTo:"
+ 	 "sim byteCount = 66849 ifTrue: [self halt]."
+ 	 "(sim byteCount > 7508930 and: [sim localFP = -16r27894]) ifTrue:
+ 		[self halt]."
+ 	 fp = sim localFP] whileFalse:
+ 		[sim singleStep].
+ 	result := sim internalPopStack.
+ 	self assert: savedsp = sim localSP.
+ 	self assert: sim localIP - 1 = savedpc.
+ 	sim localIP: savedpc.
+ 	^result!

Item was added:
+ ----- Method: SimulatorHarness>>withExecutableInterpreter:do: (in category 'bootstrap methods') -----
+ withExecutableInterpreter: sim do: aBlock
+ 	"With the oldInterpreter ready to execute code, evaluate aBlock,
+ 	 then return the interpreter (and the heap) to the ``just snapshotted'' state."
+ 	| savedpc initialContext finalContext |
+ 	sim
+ 		initStackPages;
+ 		loadInitialContext;
+ 		internalizeIPandSP.
+ 	initialContext := sim frameContext: sim localFP.
+ 	savedpc := sim localIP.
+ 	"sim printHeadFrame."
+ 	aBlock value.
+ 	"sim printHeadFrame."
+ 	sim
+ 		internalPush: sim localIP;
+ 		externalizeIPandSP.
+ 	"now undo the execution state"
+ 	finalContext := sim voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
+ 	self assert: initialContext = finalContext.
+ 	self assert: sim localIP = savedpc.
+ 	sim objectMemory
+ 		storePointer: SuspendedContextIndex
+ 		ofObject: sim activeProcess
+ 		withValue: finalContext!

Item was changed:
+ SimulatorHarness subclass: #SpurBootstrap
- Object subclass: #SpurBootstrap
  	instanceVariableNames: 'oldHeap newHeap oldHeapSize newHeapSize oldHeapNumObjs newHeapNumObjs map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym classMetaclass imageTypes classMethodContextIndex classBlockClosureIndex'
  	classVariableNames: 'ImageHeaderFlags ImageName ImageScreenSize TransformedImage'
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
  !SpurBootstrap commentStamp: 'eem 9/11/2013 05:45' prior: 0!
  SpurBootstrap bootstraps an image in SpurMemoryManager format from a Squeak V3 + closures format.
  
  e.g.
  	(SpurBootstrap32 new on: '/Users/eliot/Cog/startreader.image')
  		transform;
  		launch
  
  Bootstrap issues:
  - should it implement a deterministic Symbol identityHash? This means set a Symbol's identityHash at instance creation time
    based on its string hash so that e.g. MethodDIctionary instances have a deterministic order and don't need to be rehashed on load.
  - should it collapse ContextPart and MethodContext down onto Context (and perhaps eliminate BlockContext)?
  
  Instance Variables
  	classToIndex:			<Dictionary>
  	lastClassTablePage:	<Integer>
  	map:					<Dictionary>
  	methodClasses:		<Set>
  	newHeap:				<SpurMemoryManager>
  	oldHeap:				<NewObjectMemory>
  	oldInterpreter:			<StackInterpreterSimulator>
  	reverseMap:			<Dictionary>
  	symbolMap:				<Dictionary>
  
  classToIndex
  	- oldClass to new classIndex map
  
  lastClassTablePage
  	- oop in newHeap of last classTable page.  U<sed in validation to filter-out class table.
  
  methodClasses
  	- cache of methodClassAssociations for classes in which modified methods are installed
  
  map
  	- oldObject to newObject map
  
  newHeap
  	- the output, bootstrapped image
  
  oldHeap
  	- the input, image
  
  oldInterpreter
  	- the interpreter associated with oldHeap, needed for a hack to grab WeakArray
  
  reverseMap
  	- newObject to oldObject map
  
  symbolMap
  	- symbol toi symbol oop in oldHeap, used to map prototype methdos to methods in oldHeap!

Item was removed:
- ----- Method: SpurBootstrap>>interpreter:object:perform:withArguments: (in category 'bootstrap methods') -----
- interpreter: sim object: receiver perform: selector withArguments: arguments
- 	"Interpret an expression in oldHeap using oldInterpreter.
- 	 Answer the result."
- 	| fp savedpc savedsp result startByteCount |
- 	self assert: ({receiver. selector}, arguments allSatisfy:
- 					[:oop| oop isInteger and: [sim objectMemory addressCouldBeOop: oop]]).
- 	savedpc := sim localIP.
- 	savedsp := sim localSP.
- 	sim internalPush: receiver.
- 	arguments do: [:arg| sim internalPush: arg].
- 	sim
- 		argumentCount: arguments size;
- 		messageSelector: selector.
- 	fp := sim localFP.
- 	startByteCount := sim byteCount.
- 	"sim byteCount = 66849 ifTrue: [self halt]."
- 	sim normalSend.
- 	sim incrementByteCount. "otherwise, send is not counted"
- 	["sim printFrame: sim localFP WithSP: sim localSP"
- 	 "sim setBreakSelector: #elementsForwardIdentityTo:"
- 	 "sim byteCount = 66849 ifTrue: [self halt]."
- 	 "(sim byteCount > 7508930 and: [sim localFP = -16r27894]) ifTrue:
- 		[self halt]."
- 	 fp = sim localFP] whileFalse:
- 		[sim singleStep].
- 	result := sim internalPopStack.
- 	self assert: savedsp = sim localSP.
- 	self assert: sim localIP - 1 = savedpc.
- 	sim localIP: savedpc.
- 	^result!

Item was removed:
- ----- Method: SpurBootstrap>>withExecutableInterpreter:do: (in category 'bootstrap methods') -----
- withExecutableInterpreter: sim do: aBlock
- 	"With the oldInterpreter ready to execute code, evaluate aBlock,
- 	 then return the interpreter (and the heap) to the ``just snapshotted'' state."
- 	| savedpc initialContext finalContext |
- 	sim
- 		initStackPages;
- 		loadInitialContext;
- 		internalizeIPandSP.
- 	initialContext := sim frameContext: sim localFP.
- 	savedpc := sim localIP.
- 	"sim printHeadFrame."
- 	aBlock value.
- 	"sim printHeadFrame."
- 	sim
- 		internalPush: sim localIP;
- 		externalizeIPandSP.
- 	"now undo the execution state"
- 	finalContext := sim voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 	self assert: initialContext = finalContext.
- 	self assert: sim localIP = savedpc.
- 	sim objectMemory
- 		storePointer: SuspendedContextIndex
- 		ofObject: sim activeProcess
- 		withValue: finalContext!

Item was changed:
  ----- Method: SpurBootstrap>>writeSnapshot:ofTransformedImage:headerFlags:screenSize: (in category 'testing') -----
  writeSnapshot: imageFileName ofTransformedImage: spurHeap headerFlags: headerFlags screenSize: screenSizeInteger
  	"The bootstrapped image typically contains a few big free chunks and one huge free chunk.
  	 Test snapshot writing and loading by turning the largest non-huge chunks into segment bridges
  	 and saving."
  	| penultimate ultimate sizes counts barriers sim |
  	sim := StackInterpreterSimulator onObjectMemory: spurHeap.
  	sim bootstrapping: true.
  	spurHeap
  		coInterpreter: sim;
  		setEndOfMemory: spurHeap endOfMemory + spurHeap bridgeSize. "hack; initializeInterpreter: cuts it back by bridgeSize"
  	sim initializeInterpreter: 0;
  		setImageHeaderFlagsFrom: headerFlags;
+ 		setDisplayForm: nil.
- 		setDisplayForm: (Form extent: screenSizeInteger >> 16 @ (screenSizeInteger bitAnd: 16rFFFF)).
  	spurHeap allOldSpaceEntitiesDo: [:e| penultimate := ultimate. ultimate := e].
  	(spurHeap isFreeObject: penultimate) ifTrue: "old, pre-pigCompact segmented save"
  		[self assert: (spurHeap isSegmentBridge: ultimate).
  		 sizes := Bag new.
  		 spurHeap allObjectsInFreeTree: (spurHeap freeLists at: 0) do:
  			[:f|
  			sizes add: (spurHeap bytesInObject: f)].
  		 counts := sizes sortedCounts.
  		 self assert: counts last key = 1. "1 huge chunk"
  		 counts size > 1
  			ifTrue:
  				[self assert: ((counts at: counts size - 1) key > 2
  							and: [(counts at: counts size - 1) value > 1024]).
  				barriers := (1 to: (counts at: counts size - 1) key) collect:
  								[:ign| spurHeap allocateOldSpaceChunkOfExactlyBytes: (counts at: counts size - 1) value].
  				barriers := barriers, {spurHeap allocateOldSpaceChunkOfExactlyBytes: (spurHeap bytesInObject: penultimate)}]
  			ifFalse:
  				[barriers := {spurHeap allocateOldSpaceChunkOfExactlyBytes: (spurHeap bytesInObject: penultimate)}].
  		 barriers last ifNotNil:
  			[:end|
  			spurHeap setEndOfMemory: end.
  			spurHeap allOldSpaceEntitiesDo: [:e| penultimate := ultimate. ultimate := e].
  			self assert: (spurHeap addressAfter: ultimate) = end]].
  	spurHeap checkFreeSpace.
  	spurHeap runLeakCheckerForFullGC: true.
  	barriers ifNotNil: "old, pre-pigCompact segmented save"
  		[spurHeap segmentManager initializeFromFreeChunks: (barriers sort collect: [:b| spurHeap objectStartingAt: b])].
  	spurHeap checkFreeSpace.
  	spurHeap runLeakCheckerForFullGC: true.
  	sim bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: true.
  	sim imageName: imageFileName.
  	sim writeImageFileIO!

Item was changed:
  ----- Method: SpurBootstrap>>writeSnapshotOfTransformedImageAs: (in category 'testing') -----
  writeSnapshotOfTransformedImageAs: imageFileName
  	"The bootstrapped image typically contains a few big free chunks and one huge free chunk.
  	 Test snapshot writing and loading by turning the largest non-huge chunks into segment bridges
  	 and saving."
  	| penultimate ultimate heap sizes counts barriers sim |
  	heap := TransformedImage veryDeepCopy.
  	sim := StackInterpreterSimulator onObjectMemory: heap.
  	sim bootstrapping: true.
  	heap coInterpreter: sim.
  	sim initializeInterpreter: 0;
  		setImageHeaderFlagsFrom: ImageHeaderFlags;
+ 		setDisplayForm: nil;
+ 		setSavedWindowSize: ImageScreenSize >> 16 @ (ImageScreenSize bitAnd: 16rFFFF).
- 		setDisplayForm: (Form extent: ImageScreenSize >> 16 @ (ImageScreenSize bitAnd: 16rFFFF)).
  	heap allOldSpaceEntitiesDo: [:e| penultimate := ultimate. ultimate := e].
  	self assert: (heap isFreeObject: penultimate).
  	self assert: (heap isSegmentBridge: ultimate).
  	sizes := Bag new.
  	heap allObjectsInFreeTree: (heap freeLists at: 0) do:
  		[:f|
  		sizes add: (heap bytesInObject: f)].
  	counts := sizes sortedCounts.
  	self assert: counts last key = 1. "1 huge chunk"
  	counts size > 1
  		ifTrue:
  			[self assert: ((counts at: counts size - 1) key > 2
  						and: [(counts at: counts size - 1) value > 1024]).
  			barriers := (1 to: (counts at: counts size - 1) key) collect:
  							[:ign| heap allocateOldSpaceChunkOfExactlyBytes: (counts at: counts size - 1) value].
  			barriers := barriers, {heap allocateOldSpaceChunkOfExactlyBytes: (heap bytesInObject: penultimate)}]
  		ifFalse:
  			[barriers := {heap allocateOldSpaceChunkOfExactlyBytes: (heap bytesInObject: penultimate)}].
  	heap setEndOfMemory: barriers last.
  	heap allOldSpaceEntitiesDo: [:e| penultimate := ultimate. ultimate := e].
  	self assert: (heap addressAfter: ultimate) = barriers last.
  	heap checkFreeSpace.
  	heap runLeakCheckerForFullGC: true.
  	heap segmentManager initializeFromFreeChunks: (barriers sort collect: [:b| heap objectStartingAt: b]).
  	heap checkFreeSpace.
  	heap runLeakCheckerForFullGC: true.
  	sim bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: true.
  	sim imageName: imageFileName.
  	sim writeImageFileIO!

Item was changed:
+ SimulatorHarness subclass: #SpurOldToNewMethodFormatMunger
+ 	instanceVariableNames: 'interpreter heap prototypes replacements symbolOops'
- Object subclass: #SpurOldToNewMethodFormatMunger
- 	instanceVariableNames: 'interpreter heap'
  	classVariableNames: ''
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>cloneArrayLiteral: (in category 'munging') -----
+ cloneArrayLiteral: anArray
+ 	"Currently serves only to clone the #(0 0) literal in SpaceTallyPROTOTYPEspaceForInstancesOf:"
+ 	| array |
+ 	array := heap instantiateClass: (heap splObj: ClassArray) indexableSize: anArray size.
+ 	1 to: anArray size do:
+ 		[:i| | lit |
+ 		lit := anArray at: i.
+ 		lit class caseOf: {
+ 			[SmallInteger] -> [heap
+ 									storePointerUnchecked: i - 1
+ 									ofObject: array
+ 									withValue: (heap integerObjectOf: lit)].
+ 			[ByteSymbol] -> [heap
+ 									storePointer: i - 1
+ 									ofObject: array
+ 									withValue: (symbolOops at: lit)].
+ 			[UndefinedObject] -> [heap
+ 									storePointerUnchecked: i - 1
+ 									ofObject: array
+ 									withValue: heap nilObject] }].
+ 	^array
+ !

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>indexOfSelector:in: (in category 'munging') -----
+ indexOfSelector: selectorOop in: methodDict
+ 	SelectorStart to: (heap numSlotsOf: methodDict) - 1 do:
+ 		[:i|
+ 		(heap fetchPointer: i ofObject: methodDict) = selectorOop ifTrue:
+ 			[^i]].
+ 	self error: 'could not find selector in method dict'!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>installableMethodFor:selector:siblingMethod: (in category 'munging') -----
+ installableMethodFor: method selector: selectorOop siblingMethod: sibling 
+ 	| classOop clone delta numBytes |
+ 	delta := (method primitive > 0
+ 			  and: [(method at: method initialPC) ~= method methodClass callPrimitiveCode])
+ 				ifTrue: [3]
+ 				ifFalse: [0].
+ 	clone := heap
+ 				allocateSlots: ((numBytes := heap numSlotsForBytes: method endPC + 1) + delta)
+ 				format: (heap compiledMethodFormatForNumBytes: numBytes + delta)
+ 				classIndex: (heap classIndexOf: sibling).
+ 	classOop := interpreter methodClassOf: sibling.
+ 	method methodClass isMeta ifTrue:
+ 		[classOop := heap fetchPointer: interpreter thisClassIndex ofObject: classOop].
+ 	heap storePointer: 0
+ 		ofObject: clone
+ 		withValue: (self methodHeaderForMethod: method).
+ 	1 to: method numLiterals - 2 do:
+ 		[:i|
+ 		heap storePointer: i
+ 			ofObject: clone
+ 			withValue: (self literalFor: (method literalAt: i) inClass: classOop)].
+ 	heap
+ 		storePointer: method numLiterals - 1
+ 			ofObject: clone
+ 				withValue: selectorOop;
+ 		storePointer: method numLiterals
+ 			ofObject: clone
+ 				withValue: (interpreter methodClassAssociationOf: sibling).
+ 
+ 	delta > 0 ifTrue:
+ 		[heap
+ 			storeByte: method initialPC - 1 ofObject: clone 	withValue: 139;
+ 			storeByte: method initialPC + 0 ofObject: clone withValue: (method primitive bitAnd: 255);
+ 			storeByte: method initialPC + 1 ofObject: clone withValue: (method primitive bitShift: -8)].
+ 	method initialPC to: method endPC do:
+ 		[:i|
+ 		 heap storeByte: i - 1 + delta ofObject: clone withValue: (method at: i)].
+ 
+ 	^clone!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>literalFor:inClass: (in category 'munging') -----
+ literalFor: aLiteral inClass: classOop
+ 	| bindingOrNil |
+ 	aLiteral isSymbol ifTrue:
+ 		[^symbolOops at: aLiteral].
+ 	aLiteral isString ifTrue:
+ 		[^heap stringForCString: aLiteral].
+ 	(aLiteral isInteger and: [aLiteral class == SmallInteger]) ifTrue:
+ 		[^heap integerObjectOf: aLiteral].
+ 	aLiteral isFloat ifTrue:
+ 		[^interpreter floatObjectOf: aLiteral].
+ 	aLiteral isArray ifTrue:
+ 		[^self cloneArrayLiteral: aLiteral].
+ 	self assert: aLiteral isVariableBinding.
+ 	"interpreter
+ 		ensureDebugAtEachStepBlock;
+ 		instVarNamed: 'printBytecodeAtEachStep' put: true;
+ 		instVarNamed: 'printFrameAtEachStep' put: true."
+ 	bindingOrNil := self interpreter: interpreter
+ 						object: classOop
+ 						perform: (symbolOops at: #bindingOf:)
+ 						withArguments: {symbolOops at: aLiteral key}.
+ 	bindingOrNil ~= heap nilObject ifTrue:
+ 		[^bindingOrNil].
+ 	self error: 'couldn''t find literal ', aLiteral printString!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>methodHeaderForMethod: (in category 'munging') -----
+ methodHeaderForMethod: method
+ 	^heap integerObjectOf:
+ 		   (method numArgs << 24)
+ 		+ (method numTemps << 18)
+ 		+ (method frameSize > method class smallFrameSize ifTrue: [1 << 17] ifFalse: [0])
+ 		+ (method primitive > 0 ifTrue: [1 << 16] ifFalse: [0])
+ 		+ method numLiterals!

Item was changed:
  ----- Method: SpurOldToNewMethodFormatMunger>>munge: (in category 'public access') -----
  munge: imageName
  	interpreter := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur32BitMemoryManager).
  	interpreter desiredNumStackPages: 4; initStackPages.
  	heap := interpreter objectMemory.
  	self assert: heap class == Spur32BitMMLESimulator.
  	SpurOldFormat32BitMMLESimulator adoptInstance: heap.
  	interpreter openOn: imageName extraMemory: 0.
  	self mapPCs.
+ 	self preparePrototypes.
  	self updateAndForwardMethods.
  	self snapshot!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>preparePrototypes (in category 'munging') -----
+ preparePrototypes
+ 	replacements := OrderedCollection new.
+ 	heap classTableObjectsDo:
+ 		[:class| | name isMeta |
+ 		name := heap
+ 					fetchPointer: interpreter classNameIndex
+ 					ofObject: ((isMeta := (heap numSlotsOf: class) = interpreter metaclassNumSlots)
+ 								ifTrue: [heap fetchPointer: interpreter thisClassIndex ofObject: class]
+ 								ifFalse: [class]).
+ 		name := interpreter stringOf: name.
+ 		self prototypeClassNameMetaSelectorMethodDo:
+ 			[:protoClassName :protoIsMeta :selector :method|
+ 			 (protoClassName = name
+ 			  and: [protoIsMeta = isMeta]) ifTrue:
+ 				[replacements addLast: {class. selector. method}]]]!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>prototypeClassNameMetaSelectorMethodDo: (in category 'munging') -----
+ prototypeClassNameMetaSelectorMethodDo: quaternaryBlock
+ 	prototypes ifNil:
+ 		[prototypes := OrderedCollection new.
+ 		SpurBootstrap new prototypeClassNameMetaSelectorMethodDo:
+ 			[:className :isMeta :selector :method| 
+ 			(#(BytecodeEncoder CompiledMethod EncoderForSqueakV4PlusClosures
+ 				InstructionClient InstructionStream MethodNode) includes: className) ifTrue:
+ 					[prototypes addLast: {className. isMeta. selector. method}]]].
+ 	prototypes do: [:tuple| quaternaryBlock valueWithArguments: tuple]!

Item was added:
+ ----- Method: SpurOldToNewMethodFormatMunger>>replaceMethodsAddingThemTo: (in category 'munging') -----
+ replaceMethodsAddingThemTo: replacedSet
+ 	| byteSymbolClassIndex symbols symbolSizes |
+ 	byteSymbolClassIndex := heap classIndexOf: (heap splObj: SelectorDoesNotUnderstand).
+ 	symbols := Set with: #bindingOf:.
+ 	replacements do:
+ 		[:tuple| | method adder |
+ 		symbols add: tuple second.
+ 		method := tuple last.
+ 		adder := [:lit|
+ 				   (lit isSymbol and: [lit ~~ method selector]) ifTrue: [symbols add: lit].
+ 				   (lit isVariableBinding and: [lit key isSymbol]) ifTrue: [symbols add: lit key].
+ 				   lit isArray ifTrue: [lit do: adder]].
+ 		method literals do: adder].
+ 	symbolSizes := symbols collect: [:ea| ea size].
+ 	symbolOops := Dictionary new.
+ 	heap allObjectsDo:
+ 		[:obj| | sz |
+ 		((heap classIndexOf: obj) = byteSymbolClassIndex
+ 		 and: [symbolSizes includes: (sz := heap numBytesOf: obj)]) ifTrue:
+ 			[symbols do:
+ 				[:s|
+ 				 (sz = s size
+ 				  and: [(interpreter stringOf: obj) = s]) ifTrue:
+ 					[symbolOops at: s put: obj]]]].
+ 	replacements do:
+ 		[:tuple|
+ 		[:classOop :selector :method| | replacement methodDict methodArray index |
+ 		methodDict := heap fetchPointer: MethodDictionaryIndex ofObject: classOop.
+ 		methodArray := heap fetchPointer: MethodArrayIndex ofObject: methodDict.
+ 		index := (0 to: (heap numSlotsOf: methodArray) - 1) detect: [:i| (heap fetchPointer: i ofObject: methodArray) ~= heap nilObject].
+ 		replacement := self installableMethodFor: method
+ 							selector: (symbolOops at: selector)
+ 							siblingMethod: (heap fetchPointer: index ofObject: methodArray).
+ 		index := self indexOfSelector: (symbolOops at: selector) in: methodDict.
+ 		heap
+ 			storePointer: index - SelectorStart
+ 			ofObject: methodArray
+ 			withValue: replacement.
+ 		replacedSet add: replacement] valueWithArguments: tuple]!

Item was changed:
  ----- Method: SpurOldToNewMethodFormatMunger>>snapshot (in category 'saving') -----
  snapshot
  	Spur32BitMMLESimulator adoptInstance: heap.
  	interpreter imageName: 'munged-', (FileDirectory default localNameFor: interpreter imageName).
+ 	[heap parent: heap; setCheckForLeaks: 15; garbageCollectForSnapshot]
- 	[heap parent: heap; setCheckForLeaks: 15; fullGC; fullGC]
  		on: Halt
  		do: [:ex|
  			"suppress halts from the usual suspects (development time halts)"
  			(#(fullGC globalGarbageCollect) includes: ex signalerContext sender selector)
  				ifTrue: [ex resume]
  				ifFalse: [ex pass]].
+ 	interpreter
+ 		setDisplayForm: nil; "gets it to use savedWindowSize"
+ 		writeImageFileIO!
- 	interpreter halt; writeImageFileIO!

Item was changed:
  ----- Method: SpurOldToNewMethodFormatMunger>>updateAndForwardMethods (in category 'munging') -----
  updateAndForwardMethods
  	| new now lastDotTime |
  	new := Set new: 1000.
  	lastDotTime := Time now asSeconds.
  	heap allObjectsDo:
  		[:obj|
- 		obj = 16rAC9A30 ifTrue: [self halt].
  		((heap isCompiledMethod: obj)
  		 and: [(new includes: obj) not]) ifTrue:
  			[| header |
  			 (heap primitiveIndexOfMethodHeader: (header := heap methodHeaderOf: obj)) > 0
  				ifTrue:
  					[new add: (self mungePrimitiveMethod: obj).
  					 (now := Time now asSeconds) > lastDotTime ifTrue:
  						[Transcript nextPut: $.; flush.
  						 lastDotTime := now]]
  				ifFalse:
  					[heap
  						storePointerUnchecked: 0
  						ofObject: obj
+ 						withValue: (self convertOldMethodHeader: header)]]].
+ 	Spur32BitMMLESimulator adoptInstance: interpreter objectMemory.
+ 	self withExecutableInterpreter: interpreter
+ 		do: [self replaceMethodsAddingThemTo: new]!
- 						withValue: (self convertOldMethodHeader: header)]]]!



More information about the Vm-dev mailing list