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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 7 03:07:24 UTC 2020


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

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

Name: Cog-eem.396
Author: eem
Time: 6 February 2020, 7:07:21.895367 pm
UUID: cb6ea351-e518-4d50-9406-af35798b0c0b
Ancestors: Cog-eem.395

Refactor and rename Spur32to64BitBootstrap into SpurMtoNBitImageConverter with two subclasses, Spur32to64BitImageConverter and Spur64to32BitImageConverter.  Ensure 32 to 64-bit conversion still works. 64 to 32-bit conversion is WIP.

=============== Diff against Cog-eem.395 ===============

Item was changed:
  SimulatorHarness subclass: #Spur32BitPreen
  	instanceVariableNames: 'oldHeap newHeap map reverseMap oldInterpreter newInterpreter imageHeaderFlags savedWindowSize writeDefaultHeader'
  	classVariableNames: ''
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
+ !Spur32BitPreen commentStamp: 'eem 2/6/2020 18:44' prior: 0!
+ A Spur32BitPreen is a simple image rewriter for 32-bit Spur images that eliminates free space and hence shrinks the preened image.  Use via
- !Spur32BitPreen commentStamp: 'eem 8/15/2016 19:49' prior: 0!
- A Spur32BitPreen is a simple image rewriter for 32-bit Spru images that eliminates free space and hence shrinks the preened image.  Use via
  	Spur32BitPreen new preenImage: 'spur'
  which will produce spur-preen.image and spur-preen.changes from spur.image and spur.changes.
  
  Instance Variables
  	imageHeaderFlags:		<Integer>
  	map:					<Dictionary>
  	newHeap:				<Spur32BitMMLESimulator>
  	newInterpreter:			<StackInterpreterSimulatorLSB>
  	oldHeap:				<Spur32BitMMLESimulator>
  	oldInterpreter:			<StackInterpreterSimulatorLSB>
  	reverseMap:			<Dictionary>
  	savedWindowSize:		<Integer>
  
  imageHeaderFlags
  	- flags word in image header
  
  map
  	- map from oops in old image to oops in new image
  
  newHeap
  	- the preened heap
  
  newInterpreter
  	- the interpreter wrapping the preened heap
  
  oldHeap
  	- the heap to be preened
  
  oldInterpreter
  	- the interpreter wrapping the heap to be preened
  
  reverseMap
  	- map from oops in new image to oops in old image
  
  savedWindowSize
  	- screen size word in mage header
  !

Item was removed:
- SimulatorHarness subclass: #Spur32to64BitBootstrap
- 	instanceVariableNames: 'heap32 heap64 map reverseMap interpreter32 interpreter64 imageHeaderFlags savedWindowSize literalMap'
- 	classVariableNames: ''
- 	poolDictionaries: 'VMObjectIndices VMSqueakClassIndices'
- 	category: 'Cog-Bootstrapping'!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>alterSystem (in category 'bootstrap image') -----
- alterSystem
- 	self ensureSmallFloatInClassTable.
- 	self nilWordSize!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>bootstrapImage (in category 'public access') -----
- bootstrapImage
- 	self cloneObjects.
- 	self fillInObjects.
- 	self fillInHeap.
- 	self alterSystem!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>bootstrapImage: (in category 'public access') -----
- bootstrapImage: imageName
- 	(Smalltalk classNamed: #FileReference) ifNotNil:
- 		[^self bootstrapImageUsingFileReference: imageName].
- 	(Smalltalk classNamed: #FileDirectory) ifNotNil:
- 		[^self bootstrapImageUsingFileDirectory: imageName].
- 	self error: 'at a loss as to what file system support to use'!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>bootstrapImageUsingFileDirectory: (in category 'public access') -----
- bootstrapImageUsingFileDirectory: imageName
- 	| dirName baseName dir |
- 	dirName := FileDirectory dirPathFor: imageName.
- 	baseName := (imageName endsWith: '.image')
- 					ifTrue: [FileDirectory baseNameFor: imageName]
- 					ifFalse: [FileDirectory localNameFor: imageName].
- 	dir := dirName isEmpty ifTrue: [FileDirectory default] ifFalse: [FileDirectory default on: dirName].
- 	self on: (dir fullNameFor: baseName, '.image').
- 	[self bootstrapImage]
- 		on: Halt
- 		do: [:ex|
- 			"suppress halts from the usual suspects (development time halts)"
- 			(#(fullGC compactImage) includes: ex signalerContext sender selector)
- 				ifTrue: [ex resume]
- 				ifFalse: [ex pass]].
- 	self writeSnapshot: (dir fullNameFor: baseName, '-64.image')
- 		headerFlags: imageHeaderFlags
- 		screenSize: savedWindowSize.
- 	dir deleteFileNamed: baseName, '-64.changes';
- 		copyFileNamed: baseName, '.changes' toFileNamed: baseName, '-64.changes'!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>clone: (in category 'bootstrap image') -----
- clone: obj32
- 	| obj64 format numSlots numBytes hash |
- 	format := heap32 formatOf: obj32.
- 	numSlots := heap32 numSlotsOf: obj32.
- 	format > heap32 lastPointerFormat ifTrue:
- 		[format < heap32 firstByteFormat
- 			ifTrue:
- 				[format = heap32 firstLongFormat
- 					ifTrue:
- 						[numSlots := heap32 numSlotsOf: obj32.
- 						 numSlots odd ifTrue:
- 							[format := format + 1].
- 						 numSlots := numSlots + 1 // 2]
- 					ifFalse: [self error: 'bad format']]
- 			ifFalse:
- 				[numBytes := heap32 numBytesOf: obj32.
- 				 format < heap32 firstCompiledMethodFormat
- 					ifTrue:
- 						[format := heap64 byteFormatForNumBytes: numBytes.
- 						 numSlots := numSlots + 1 // 2]
- 					ifFalse:
- 						[numSlots := heap32 numPointerSlotsOf: obj32.
- 						 numBytes := numBytes - (numSlots * heap32 bytesPerOop).
- 						 format := (heap64 byteFormatForNumBytes: numBytes) + heap32 firstCompiledMethodFormat - heap32 firstByteFormat.
- 						 numSlots := numSlots + (heap64 numSlotsForBytes: numBytes)]]].
- 	obj64 := heap64
- 				allocateSlots: numSlots
- 				format: format
- 				classIndex: (heap32 classIndexOf: obj32).
- 	(hash := heap32 rawHashBitsOf: obj32) ~= 0 ifTrue:
- 		[heap64 setHashBitsOf: obj64 to: hash].
- 	(heap32 isImmutable: obj32) ifTrue:
- 		[heap64 setIsImmutableOf: obj64 to: true].
- 	(heap32 isPinned: obj32) ifTrue:
- 		[heap64 setIsPinnedOf: obj64 to: true].
- 	self deny: (heap32 isRemembered: obj32).
- 	self deny: (heap32 isMarked: obj32).
- 	self deny: (heap32 isGrey: obj32).
- 	reverseMap at: obj64 put: obj32.
- 	^map at: obj32 put: obj64!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>cloneFreeLists: (in category 'bootstrap image') -----
- cloneFreeLists: obj32
- 	| obj64 |
- 	obj64 := heap64
- 				allocateSlots: heap64 numFreeLists
- 				format: heap64 wordIndexableFormat
- 				classIndex: heap64 wordSizeClassIndexPun.
- 	reverseMap at: obj64 put: obj32.
- 	^map at: obj32 put: obj64!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>cloneObjects (in category 'bootstrap image') -----
- cloneObjects
- 	"Clone all normal objects.  Of hidden objects only clone the freeLists object and
- 	 the classTableRoot and class table pages. In particular, dont clone objStacks.
- 	 The refs to the objStacks are nilled out in fillInHeap."
- 	| i freeListsObject |
- 	i := 0.
- 	freeListsObject := heap32 freeListsObject.
- 	heap32 allOldSpaceObjectsDo:
- 		[:obj32|
- 		(i := i + 1) >= 100000 ifTrue:
- 			[Transcript nextPut: $:; flush. i := 0].
- 		 obj32 = freeListsObject
- 			ifTrue:
- 				[self cloneFreeLists: obj32]
- 			ifFalse:
- 				[(self shouldClone: obj32) ifTrue:
- 					[self clone: obj32]]]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>ensureSmallFloatInClassTable (in category 'bootstrap image') -----
- ensureSmallFloatInClassTable
- 	| firstClassTablePage smallFloatClass |
- 	firstClassTablePage := heap64 fetchPointer: 0 ofObject: heap64 classTableRootObj.
- 	smallFloatClass := self smallFloatClass.
- 	(heap64 hashBitsOf: smallFloatClass) = heap64 smallFloatTag
- 		ifTrue:
- 			[heap64 nilObject = (heap64 fetchPointer: heap64 smallFloatTag ofObject: firstClassTablePage)
- 				ifTrue:
- 					[heap64
- 						storePointer: heap64 smallFloatTag ofObject: firstClassTablePage withValue: smallFloatClass;
- 						setHashBitsOf: smallFloatClass to: heap64 smallFloatTag]
- 				ifFalse:
- 					[self assert: (heap64 fetchPointer: heap64 smallFloatTag ofObject: firstClassTablePage)
- 									= smallFloatClass]]
- 		ifFalse:
- 			[self assert: (heap64 hashBitsOf: smallFloatClass) = 0.
- 			 heap64
- 				storePointer: heap64 smallFloatTag ofObject: firstClassTablePage withValue: smallFloatClass;
- 				setHashBitsOf: smallFloatClass to: heap64 smallFloatTag]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInBitsObject:from: (in category 'bootstrap image') -----
- fillInBitsObject: obj64 from: obj32
- 	0 to: (heap32 numBytesOf: obj32) - 1 do:
- 		[:i|
- 		heap64
- 			storeByte: i
- 			ofObject: obj64
- 			withValue: (heap32 fetchByte: i ofObject: obj32)]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
- fillInCompiledMethod: obj64 from: obj32
- 	| offset |
- 	"interpreter32 printOop: oop32"
- 	"interpreter64 printOop: oop64"
- 	0 to: (heap32 numPointerSlotsOf: obj32) - 1 do:
- 		[:i| | oop32 oop64 |
- 		 oop32 := heap32 fetchPointer: i ofObject: obj32.
- 		 oop64 := self map32BitOop: oop32.
- 		 heap64
- 			storePointerUnchecked: i
- 			ofObject: obj64
- 			withValue: oop64.
- 		 (heap64 isIntegerObject: oop64) ifTrue:
- 			[interpreter32 initPrimCall.
- 			 self assert: (interpreter32 signed64BitValueOf: oop32) = (heap64 integerValueOf: oop64)]].
- 	offset := (interpreter64 startPCOfMethod: obj64)
- 			- (interpreter32 startPCOfMethod: obj32).
- 	(interpreter32 startPCOfMethod: obj32)
- 		to: (heap32 numBytesOf: obj32) - 1
- 		do: [:j|
- 			heap64
- 				storeByte: offset + j 
- 				ofObject: obj64
- 				withValue: (heap32 fetchByte: j ofObject: obj32)]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInHeap (in category 'bootstrap image') -----
- fillInHeap
- 	| heapEnd freeListsObj |
- 	heapEnd := heap64 freeStart.
- 	heap64
- 		nilObject: (map at: heap32 nilObject);
- 		falseObject: (map at: heap32 falseObject);
- 		trueObject: (map at: heap32 trueObject);
- 		specialObjectsOop: (map at: heap32 specialObjectsOop);
- 		lastHash: heap32 lastHash;
- 		setHiddenRootsObj: (map at: heap32 classTableRootObj).
- 	heap64 segmentManager
- 		initSegmentForInImageCompilationFrom: heap64 nilObject
- 		to: heapEnd + heap64 bridgeSize.
- 	freeListsObj := heap64 objectAfter: heap64 trueObject.
- 	"Nil-out the free lists."
- 	heap64
- 		fillObj: freeListsObj numSlots: (heap64 numSlotsOf: freeListsObj) with: 0;
- 		initializeFreeSpacePostLoad: freeListsObj;
- 		initializePostBootstrap;
- 		setEndOfMemory: (heap64 segmentManager bridgeAt: 0) + heap64 baseHeaderSize!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInObjects (in category 'bootstrap image') -----
- fillInObjects
- 	"interpreter32 printOop: obj32"
- 	| i |
- 	{heap32 markStack. heap32 weaklingStack. heap32 mournQueue} do:
- 		[:obj|
- 		obj ~= heap32 nilObject ifTrue:
- 			[map at: obj put: (map at: heap32 nilObject)]].
- 	i := 0.
- 	heap32 allObjectsDo:
- 		[:obj32|
- 		(i := i + 1) >= 10000 ifTrue:
- 			[Transcript nextPut: $.; flush. i := 0].
- 		(map at: obj32 ifAbsent: nil)
- 			ifNotNil:
- 				[:obj64| | format classIndex |
- 				(heap64 numSlotsOf: obj64) > 0 ifTrue: "filter-out filtered objStack pages"
- 					[format := heap32 formatOf: obj32.
- 					 (heap64 isPointersFormat: format)
- 						ifTrue:
- 							[((heap64 isIndexableFormat: format)
- 								and: [(classIndex := heap64 classIndexOf: obj64) <= ClassBlockClosureCompactIndex
- 								and: [classIndex >= ClassMethodContextCompactIndex]])
- 								ifTrue: [self fillInPointerObjectWithPC: obj64 from: obj32]
- 								ifFalse: [self fillInPointerObject: obj64 from: obj32]]
- 						ifFalse:
- 							[(heap64 isCompiledMethodFormat: format)
- 								ifTrue: [self fillInCompiledMethod: obj64 from: obj32]
- 								ifFalse: [self fillInBitsObject: obj64 from: obj32]]]]
- 			ifNil: [self assert: (self isUnmappedObject: obj32)]]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInPointerObject:from: (in category 'bootstrap image') -----
- fillInPointerObject: obj64 from: obj32 
- 	0 to: (heap64 numSlotsOf: obj64) - 1 do:
- 		[:i|
- 		 heap64
- 			storePointerUnchecked: i
- 			ofObject: obj64
- 			withValue: (self map32BitOop: (heap32 fetchPointer: i ofObject: obj32))]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>fillInPointerObjectWithPC:from: (in category 'bootstrap image') -----
- fillInPointerObjectWithPC: obj64 from: obj32
- 	| method |
- 	self fillInPointerObject: obj64 from: obj32.
- 	(heap64 classIndexOf: obj64) = ClassBlockClosureCompactIndex ifTrue:
- 		[method := heap32
- 						fetchPointer: MethodIndex
- 						ofObject: (heap32
- 									fetchPointer: ClosureOuterContextIndex
- 									ofObject: obj32).
- 		self incrementPCField: ClosureStartPCIndex ofObject: obj64 for: method].
- 	(heap64 classIndexOf: obj64) = ClassMethodContextCompactIndex ifTrue:
- 		[method := heap32
- 						fetchPointer: MethodIndex
- 						ofObject: obj32.
- 		 self incrementPCField: InstructionPointerIndex ofObject: obj64 for: method]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>findSymbol: (in category 'public access') -----
- findSymbol: aString
- 	"Find the Symbol equal to aString in oldHeap."
- 	| symbolClass |
- 	(literalMap at: aString ifAbsent: nil) ifNotNil:
- 		[:oop| ^oop].
- 	symbolClass := self symbolClass.
- 	heap64 allObjectsDo:
- 		[:obj|
- 		(symbolClass = (heap64 fetchClassOfNonImm: obj)
- 		 and: [(heap64 numBytesOf: obj) = aString size
- 		 and: [aString = (heap64 stringOf: obj)]]) ifTrue:
- 			[aString isSymbol ifTrue:
- 				[literalMap at: aString asSymbol put: obj].
- 			 ^obj]].
- 	Transcript cr; nextPutAll: 'Warning, could not find '; store: aString; flush.
- 	^nil!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>incrementPCField:ofObject:for: (in category 'bootstrap image') -----
- incrementPCField: fieldIndex ofObject: obj64 for: method32
- 	| value nLits |
- 	value := heap64 fetchPointer: fieldIndex ofObject: obj64.
- 	(heap64 isIntegerObject: value)
- 		ifTrue:
- 			[nLits := heap32 literalCountOf: method32.
- 			 heap64
- 				storePointerUnchecked: fieldIndex
- 				ofObject: obj64
- 				withValue: (heap64 integerObjectOf: nLits + LiteralStart * 4 + (heap64 integerValueOf: value))]
- 		ifFalse:
- 			[self assert: (reverseMap at: value) = heap32 nilObject]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>initMaps (in category 'initialize-release') -----
- initMaps
- 	map := Dictionary new: heap32 memory size // 32.
- 	reverseMap := Dictionary new: heap32 memory size // 32.
- 	literalMap := IdentityDictionary new!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>isUnmappedObject: (in category 'bootstrap image') -----
- isUnmappedObject: obj32
- 	"Answer if obj32 is an object that is not cloned by the bootstrap."
- 	^((heap32 classIndexOf: obj32)
- 			between: ClassLargeNegativeIntegerCompactIndex
- 			and: ClassFloatCompactIndex)
- 	  or: [obj32 = heap32 freeListsObject
- 	  or: [(heap32 isValidObjStackPage: obj32)]]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>map32BitOop: (in category 'bootstrap image') -----
- map32BitOop: obj32
- 	"interpreter32 printOop: obj32"
- 	^map
- 		at: obj32
- 		ifAbsent:
- 			[(heap32 isImmediate: obj32)
- 				ifTrue:
- 					[(heap32 isImmediateCharacter: obj32)
- 						ifTrue: [heap64 characterObjectOf: (heap32 characterValueOf: obj32)]
- 						ifFalse: [heap64 integerObjectOf: (heap32 integerValueOf: obj32)]]
- 				ifFalse:
- 					[| value |
- 					 self assert: (self isUnmappedObject: obj32).
- 					 (heap32 isFloatInstance: obj32)
- 						ifTrue:
- 							[heap64 smallFloatObjectOf: (heap32 floatValueOf: obj32)]
- 						ifFalse:
- 							[interpreter32 initPrimCall.
- 							 value := interpreter32 signed64BitValueOf: obj32.
- 							 self deny: interpreter32 failed.
- 							 heap64 integerObjectOf: value]]]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>nilWordSize (in category 'bootstrap image') -----
- nilWordSize
- 	| wordSizeSym |
- 	wordSizeSym := self findSymbol: #WordSize.
- 	heap64 allOldSpaceObjectsDo:
- 		[:o|
- 		((heap64 numSlotsOf: o) > ValueIndex
- 		and: [(heap64 isPointersNonImm: o)
- 		and: [(heap64 fetchPointer: KeyIndex ofObject: o) = wordSizeSym
- 		and: [(heap64 fetchPointer: ValueIndex ofObject: o) = (heap64 integerObjectOf: 4)]]]) ifTrue:
- 			[heap64 storePointer: ValueIndex ofObject: o withValue: heap64 nilObject]]!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>on: (in category 'public access') -----
- on: imageName
- 	(interpreter32 := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur32BitMemoryManager))
- 		openOn: imageName extraMemory: 0.
- 	heap32 := interpreter32 objectMemory.
- 	imageHeaderFlags := interpreter32 getImageHeaderFlags.
- 	savedWindowSize := interpreter32 savedWindowSize.
- 	interpreter64 := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur64BitMemoryManager).
- 	heap64 := interpreter64 objectMemory.
- 	heap64
- 		allocateMemoryOfSize: heap32 oldSpaceSize * 2
- 		newSpaceSize: 8 * 1024 * 1024
- 		stackSize: 16 * 1024
- 		codeSize: 0.
- 	heap64 bootstrapping: true.
- 	self initMaps!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>shouldClone: (in category 'bootstrap image') -----
- shouldClone: obj32
- 	| classIndex value |
- 	(heap32 isValidObjStackPage: obj32) ifTrue:
- 		[^false].
- 
- 	classIndex := heap32 classIndexOf: obj32.
- 
- 	((classIndex between: ClassLargeNegativeIntegerCompactIndex and: ClassLargePositiveIntegerCompactIndex)
- 	 and: [interpreter32 initPrimCall.
- 		   value := interpreter32 signed64BitValueOf: obj32.
- 		   interpreter32 failed not
- 		   and: [heap64 isIntegerValue: value]]) ifTrue:
- 		[^false].
- 
- 	(classIndex = ClassFloatCompactIndex
- 	and: [value := heap32 floatValueOf: obj32.
- 		heap64 isSmallFloatValue: value]) ifTrue:
- 		[^false].
- 
- 	^true!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>smallFloatClass (in category 'bootstrap image') -----
- smallFloatClass
- 	| sf64sym |
- 	sf64sym := self findSymbol: #SmallFloat64.
- 	heap64 allObjectsDo:
- 		[:o|
- 		((heap64 isPointersNonImm: o)
- 		 and: [(heap64 numSlotsOf: o) > interpreter32 classNameIndex
- 		 and: [(interpreter64 addressCouldBeClassObj: o)
- 		 and: [(heap64 fetchPointer: interpreter32 classNameIndex ofObject: o) = sf64sym]]]) ifTrue:
- 			[^o]].
- 	^nil!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>symbolClass (in category 'public access') -----
- symbolClass
- 	^heap64 fetchClassOfNonImm: (heap64 splObj: SelectorDoesNotUnderstand)!

Item was removed:
- ----- Method: Spur32to64BitBootstrap>>writeSnapshot:headerFlags:screenSize: (in category 'snapshot') -----
- writeSnapshot: imageFileName headerFlags: headerFlags screenSize: screenSizeInteger
- 	heap64
- 		checkFreeSpace;
- 		runLeakCheckerForFullGC.
- 	interpreter64
- 		setImageHeaderFlagsFrom: headerFlags;
- 		setDisplayForm: nil;
- 		setSavedWindowSize: savedWindowSize;
- 		imageName: imageFileName;
- 		writeImageFileIO.
- 	Transcript cr; show: 'Done!!'!

Item was added:
+ SpurMtoNBitImageConverter subclass: #Spur32to64BitImageConverter
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>clone: (in category 'bootstrap image') -----
+ clone: sourceObj
+ 	| targetObj format numSlots numBytes hash |
+ 	format := sourceHeap formatOf: sourceObj.
+ 	numSlots := sourceHeap numSlotsOf: sourceObj.
+ 	format > sourceHeap lastPointerFormat ifTrue:
+ 		[format < sourceHeap firstByteFormat
+ 			ifTrue:
+ 				[format = sourceHeap firstLongFormat
+ 					ifTrue:
+ 						[numSlots := sourceHeap numSlotsOf: sourceObj.
+ 						 numSlots odd ifTrue:
+ 							[format := format + 1].
+ 						 numSlots := numSlots + 1 // 2]
+ 					ifFalse: [self error: 'bad format']]
+ 			ifFalse:
+ 				[numBytes := sourceHeap numBytesOf: sourceObj.
+ 				 format < sourceHeap firstCompiledMethodFormat
+ 					ifTrue:
+ 						[format := targetHeap byteFormatForNumBytes: numBytes.
+ 						 numSlots := numSlots + 1 // 2]
+ 					ifFalse:
+ 						[numSlots := sourceHeap numPointerSlotsOf: sourceObj.
+ 						 numBytes := numBytes - (numSlots * sourceHeap bytesPerOop).
+ 						 format := (targetHeap byteFormatForNumBytes: numBytes) + sourceHeap firstCompiledMethodFormat - sourceHeap firstByteFormat.
+ 						 numSlots := numSlots + (targetHeap numSlotsForBytes: numBytes)]]].
+ 	targetObj := targetHeap
+ 				allocateSlots: numSlots
+ 				format: format
+ 				classIndex: (sourceHeap classIndexOf: sourceObj).
+ 	(hash := sourceHeap rawHashBitsOf: sourceObj) ~= 0 ifTrue:
+ 		[targetHeap setHashBitsOf: targetObj to: hash].
+ 	(sourceHeap isImmutable: sourceObj) ifTrue:
+ 		[targetHeap setIsImmutableOf: targetObj to: true].
+ 	(sourceHeap isPinned: sourceObj) ifTrue:
+ 		[targetHeap setIsPinnedOf: targetObj to: true].
+ 	self deny: (sourceHeap isRemembered: sourceObj).
+ 	self deny: (sourceHeap isMarked: sourceObj).
+ 	self deny: (sourceHeap isGrey: sourceObj).
+ 	reverseMap at: targetObj put: sourceObj.
+ 	^map at: sourceObj put: targetObj!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>ensureSmallFloatInClassTable (in category 'bootstrap image') -----
+ ensureSmallFloatInClassTable
+ 	| firstClassTablePage smallFloatClass |
+ 	firstClassTablePage := targetHeap fetchPointer: 0 ofObject: targetHeap classTableRootObj.
+ 	smallFloatClass := self smallFloatClass.
+ 	(targetHeap hashBitsOf: smallFloatClass) = targetHeap smallFloatTag
+ 		ifTrue:
+ 			[targetHeap nilObject = (targetHeap fetchPointer: targetHeap smallFloatTag ofObject: firstClassTablePage)
+ 				ifTrue:
+ 					[targetHeap
+ 						storePointer: targetHeap smallFloatTag ofObject: firstClassTablePage withValue: smallFloatClass;
+ 						setHashBitsOf: smallFloatClass to: targetHeap smallFloatTag]
+ 				ifFalse:
+ 					[self assert: (targetHeap fetchPointer: targetHeap smallFloatTag ofObject: firstClassTablePage)
+ 									= smallFloatClass]]
+ 		ifFalse:
+ 			[(sourceHeap hashBitsOf: smallFloatClass) ~= targetHeap smallFloatTag ifTrue:
+ 				[self assert: (targetHeap hashBitsOf: smallFloatClass) = 0.
+ 				 targetHeap
+ 					storePointer: targetHeap smallFloatTag ofObject: firstClassTablePage withValue: smallFloatClass;
+ 					setHashBitsOf: smallFloatClass to: targetHeap smallFloatTag]]!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>fileNameExtension (in category 'private-accessing') -----
+ fileNameExtension
+ 	^'-64'!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>mapSourceOop: (in category 'bootstrap image') -----
+ mapSourceOop: sourceObj
+ 	"sourceInterpreter printOop: sourceObj"
+ 	"Map in-range Floats to SmallFloat64's, and in-range LargePointiveIntegers and LargeNegativeIntegers to SmallInteger"
+ 	^map
+ 		at: sourceObj
+ 		ifAbsent:
+ 			[(sourceHeap isImmediate: sourceObj)
+ 				ifTrue:
+ 					[(sourceHeap isImmediateCharacter: sourceObj)
+ 						ifTrue: [targetHeap characterObjectOf: (sourceHeap characterValueOf: sourceObj)]
+ 						ifFalse: [targetHeap integerObjectOf: (sourceHeap integerValueOf: sourceObj)]]
+ 				ifFalse:
+ 					[| value |
+ 					 self assert: (self isUnmappedObject: sourceObj).
+ 					 (sourceHeap isFloatInstance: sourceObj)
+ 						ifTrue:
+ 							[targetHeap smallFloatObjectOf: (sourceHeap floatValueOf: sourceObj)]
+ 						ifFalse:
+ 							[sourceInterpreter initPrimCall.
+ 							 value := sourceInterpreter signed64BitValueOf: sourceObj.
+ 							 self deny: sourceInterpreter failed.
+ 							 targetHeap integerObjectOf: value]]]!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>on: (in category 'public access') -----
+ on: imageName
+ 	(sourceInterpreter := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur32BitMemoryManager))
+ 		openOn: imageName extraMemory: 0.
+ 	sourceHeap := sourceInterpreter objectMemory.
+ 	imageHeaderFlags := sourceInterpreter getImageHeaderFlags.
+ 	savedWindowSize := sourceInterpreter savedWindowSize.
+ 	targetInterpreter := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur64BitMemoryManager).
+ 	targetHeap := targetInterpreter objectMemory.
+ 	targetHeap
+ 		allocateMemoryOfSize: sourceHeap oldSpaceSize * 2
+ 		newSpaceSize: 8 * 1024 * 1024
+ 		stackSize: 16 * 1024
+ 		codeSize: 0.
+ 	targetHeap bootstrapping: true.
+ 	self initMaps!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>pcDeltaForSourceMethod: (in category 'bootstrap image') -----
+ pcDeltaForSourceMethod: sourceMethod
+ 	^(sourceHeap literalCountOf: sourceMethod) + LiteralStart * 4!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>shouldClone: (in category 'bootstrap image') -----
+ shouldClone: sourceObj
+ 	| classIndex value |
+ 	(sourceHeap isValidObjStackPage: sourceObj) ifTrue:
+ 		[^false].
+ 
+ 	classIndex := sourceHeap classIndexOf: sourceObj.
+ 
+ 	((classIndex between: ClassLargeNegativeIntegerCompactIndex and: ClassLargePositiveIntegerCompactIndex)
+ 	 and: [sourceInterpreter initPrimCall.
+ 		   value := sourceInterpreter signed64BitValueOf: sourceObj.
+ 		   sourceInterpreter failed not
+ 		   and: [targetHeap isIntegerValue: value]]) ifTrue:
+ 		[^false].
+ 
+ 	(classIndex = ClassFloatCompactIndex
+ 	and: [value := sourceHeap floatValueOf: sourceObj.
+ 		targetHeap isSmallFloatValue: value]) ifTrue:
+ 		[^false].
+ 
+ 	^true!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>smallFloatClass (in category 'bootstrap image') -----
+ smallFloatClass
+ 	| sf64sym |
+ 	sf64sym := self findSymbol: #SmallFloat64.
+ 	targetHeap allObjectsDo:
+ 		[:o|
+ 		((targetHeap isPointersNonImm: o)
+ 		 and: [(targetHeap numSlotsOf: o) > sourceInterpreter classNameIndex
+ 		 and: [(targetInterpreter addressCouldBeClassObj: o)
+ 		 and: [(targetHeap fetchPointer: sourceInterpreter classNameIndex ofObject: o) = sf64sym]]]) ifTrue:
+ 			[^o]].
+ 	^nil!

Item was added:
+ SpurMtoNBitImageConverter subclass: #Spur64to32BitImageConverter
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>clone: (in category 'bootstrap image') -----
+ clone: sourceObj
+ 	| targetObj format numSlots numBytes hash |
+ 	format := sourceHeap formatOf: sourceObj.
+ 	numSlots := sourceHeap numSlotsOf: sourceObj.
+ 	format > sourceHeap lastPointerFormat ifTrue:
+ 		[format < sourceHeap firstByteFormat
+ 			ifTrue:
+ 				[format = sourceHeap sixtyFourBitIndexableFormat
+ 					ifTrue:
+ 						[numSlots := (sourceHeap numSlotsOf: sourceObj) * 2]
+ 					ifFalse:
+ 						[(format between: sourceHeap firstLongFormat and: sourceHeap firstLongFormat + 1)
+ 							ifTrue:
+ 								[numSlots := (sourceHeap numSlotsOf: sourceObj) * 2 - (format bitAnd: 1).
+ 								 format := format bitClear: 1]
+ 							ifFalse: [self error: 'bad format']]]
+ 			ifFalse:
+ 				[numBytes := sourceHeap numBytesOf: sourceObj.
+ 				 format < sourceHeap firstCompiledMethodFormat
+ 					ifTrue:
+ 						[numSlots := numBytes + 3 // 4.
+ 						 format := targetHeap byteFormatForNumBytes: numBytes]
+ 					ifFalse:
+ 						[numSlots := sourceHeap numPointerSlotsOf: sourceObj.
+ 						 numBytes := numBytes - (numSlots * sourceHeap bytesPerOop).
+ 						 format := (targetHeap byteFormatForNumBytes: numBytes) + sourceHeap firstCompiledMethodFormat - sourceHeap firstByteFormat.
+ 						 numSlots := numSlots + (targetHeap numSlotsForBytes: numBytes)]]].
+ 	targetObj := targetHeap
+ 				allocateSlots: numSlots
+ 				format: format
+ 				classIndex: (sourceHeap classIndexOf: sourceObj).
+ 	(hash := sourceHeap rawHashBitsOf: sourceObj) ~= 0 ifTrue:
+ 		[targetHeap setHashBitsOf: targetObj to: hash].
+ 	(sourceHeap isImmutable: sourceObj) ifTrue:
+ 		[targetHeap setIsImmutableOf: targetObj to: true].
+ 	(sourceHeap isPinned: sourceObj) ifTrue:
+ 		[targetHeap setIsPinnedOf: targetObj to: true].
+ 	self deny: (sourceHeap isRemembered: sourceObj).
+ 	self deny: (sourceHeap isMarked: sourceObj).
+ 	self deny: (sourceHeap isGrey: sourceObj).
+ 	reverseMap at: targetObj put: sourceObj.
+ 	^map at: sourceObj put: targetObj!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>ensureSmallFloatInClassTable (in category 'bootstrap image') -----
+ ensureSmallFloatInClassTable
+ 	"it should already be there..."
+ 	self assert: (targetHeap hashBitsOf: self smallFloatClass) = targetHeap smallFloatTag!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>fileNameExtension (in category 'private-accessing') -----
+ fileNameExtension
+ 	^'-32'!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>mapSourceOop: (in category 'bootstrap image') -----
+ mapSourceOop: sourceObj
+ 	"sourceInterpreter printOop: sourceObj"
+ 	"Map in-range Floats to SmallFloat64's, and in-range LargePointiveIntegers and LargeNegativeIntegers to SmallInteger"
+ 	^map
+ 		at: sourceObj
+ 		ifAbsent:
+ 			[| value box |
+ 			 self assert: (sourceHeap isImmediate: sourceObj).
+ 			 (sourceHeap isImmediateCharacter: sourceObj)
+ 				ifTrue: [targetHeap characterObjectOf: (sourceHeap characterValueOf: sourceObj)]
+ 				ifFalse:
+ 					[(sourceHeap isIntegerObject: sourceObj)
+ 						ifTrue:
+ 							[(targetHeap isIntegerValue: (value := sourceHeap integerValueOf: sourceObj))
+ 								ifTrue: [targetHeap integerObjectOf: value]
+ 								ifFalse:
+ 									[box := targetHeap
+ 													allocateSlots: 2
+ 													format: (targetHeap byteFormatForNumBytes: value digitLength)
+ 													classIndex: (value < 0
+ 																	ifTrue: [ClassLargeNegativeIntegerCompactIndex]
+ 																	ifFalse: [ClassLargePositiveIntegerCompactIndex]).
+ 									 targetHeap storeLong64: 0 ofObject: box withValue: value abs.
+ 									 box]]
+ 						ifFalse:
+ 							[self assert: (sourceHeap isImmediateFloat: sourceObj).
+ 							 box := targetHeap
+ 											allocateSlots: 2
+ 											format: (targetHeap byteFormatForNumBytes: value digitLength)
+ 											classIndex: (value < 0
+ 															ifTrue: [ClassLargeNegativeIntegerCompactIndex]
+ 															ifFalse: [ClassLargePositiveIntegerCompactIndex]).
+ 							 targetHeap storeLong64: 0 ofObject: box withValue: (sourceHeap smallFloatBitsOf: sourceObj).
+ 							 box]]]!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>on: (in category 'public access') -----
+ on: imageName
+ 	(sourceInterpreter := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur64BitMemoryManager))
+ 		openOn: imageName extraMemory: 0.
+ 	sourceHeap := sourceInterpreter objectMemory.
+ 	imageHeaderFlags := sourceInterpreter getImageHeaderFlags.
+ 	savedWindowSize := sourceInterpreter savedWindowSize.
+ 	targetInterpreter := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur32BitMemoryManager).
+ 	targetHeap := targetInterpreter objectMemory.
+ 	targetHeap
+ 		allocateMemoryOfSize: sourceHeap oldSpaceSize * 5 // 8 "LargeInteger and Float objects are created for out-of-range immediates"
+ 		newSpaceSize: 8 * 1024 * 1024
+ 		stackSize: 16 * 1024
+ 		codeSize: 0.
+ 	targetHeap bootstrapping: true.
+ 	self initMaps!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>pcDeltaForSourceMethod: (in category 'bootstrap image') -----
+ pcDeltaForSourceMethod: sourceMethod
+ 	^(sourceHeap literalCountOf: sourceMethod) + LiteralStart * -4!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>shouldClone: (in category 'bootstrap image') -----
+ shouldClone: sourceObj
+ 	^(sourceHeap isValidObjStackPage: sourceObj) not!

Item was added:
+ SimulatorHarness subclass: #SpurMtoNBitImageConverter
+ 	instanceVariableNames: 'sourceHeap targetHeap map reverseMap sourceInterpreter targetInterpreter imageHeaderFlags savedWindowSize literalMap'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'VMObjectIndices VMSqueakClassIndices'
+ 	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>alterSystem (in category 'bootstrap image') -----
+ alterSystem
+ 	self ensureSmallFloatInClassTable.
+ 	self nilWordSize!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>bootstrapImage (in category 'public access') -----
+ bootstrapImage
+ 	self cloneObjects.
+ 	self fillInObjects.
+ 	self fillInHeap.
+ 	self alterSystem!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>bootstrapImage: (in category 'public access') -----
+ bootstrapImage: imageName
+ 	(Smalltalk classNamed: #FileReference) ifNotNil:
+ 		[^self bootstrapImageUsingFileReference: imageName].
+ 	(Smalltalk classNamed: #FileDirectory) ifNotNil:
+ 		[^self bootstrapImageUsingFileDirectory: imageName].
+ 	self error: 'at a loss as to what file system support to use'!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>bootstrapImageUsingFileDirectory: (in category 'public access') -----
+ bootstrapImageUsingFileDirectory: imageName
+ 	| dirName baseName dir |
+ 	dirName := FileDirectory dirPathFor: imageName.
+ 	baseName := (imageName endsWith: '.image')
+ 					ifTrue: [FileDirectory baseNameFor: imageName]
+ 					ifFalse: [FileDirectory localNameFor: imageName].
+ 	dir := dirName isEmpty ifTrue: [FileDirectory default] ifFalse: [FileDirectory default on: dirName].
+ 	self on: (dir fullNameFor: baseName, '.image').
+ 	[self bootstrapImage]
+ 		on: Halt
+ 		do: [:ex|
+ 			"suppress halts from the usual suspects (development time halts)"
+ 			(#(fullGC compactImage) includes: ex signalerContext sender selector)
+ 				ifTrue: [ex resume]
+ 				ifFalse: [ex pass]].
+ 	self writeSnapshot: (dir fullNameFor: baseName, self fileNameExtension, '.image')
+ 		headerFlags: imageHeaderFlags
+ 		screenSize: savedWindowSize.
+ 	dir deleteFileNamed: baseName,  self fileNameExtension, '.changes';
+ 		copyFileNamed: baseName, '.changes' toFileNamed: baseName,  self fileNameExtension, '.changes'!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>clone: (in category 'bootstrap image') -----
+ clone: sourceObj
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>cloneFreeLists: (in category 'bootstrap image') -----
+ cloneFreeLists: sourceObj
+ 	| targetObj |
+ 	targetObj := targetHeap
+ 				allocateSlots: targetHeap numFreeLists
+ 				format: targetHeap wordIndexableFormat
+ 				classIndex: targetHeap wordSizeClassIndexPun.
+ 	reverseMap at: targetObj put: sourceObj.
+ 	^map at: sourceObj put: targetObj!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>cloneObjects (in category 'bootstrap image') -----
+ cloneObjects
+ 	"Clone all normal objects.  Of hidden objects only clone the freeLists object and
+ 	 the classTableRoot and class table pages. In particular, dont clone objStacks.
+ 	 The refs to the objStacks are nilled out in fillInHeap."
+ 	| i freeListsObject |
+ 	i := 0.
+ 	freeListsObject := sourceHeap freeListsObject.
+ 	sourceHeap allOldSpaceObjectsDo:
+ 		[:sourceObj|
+ 		(i := i + 1) >= 100000 ifTrue:
+ 			[Transcript nextPut: $:; flush. i := 0].
+ 		 sourceObj = freeListsObject
+ 			ifTrue:
+ 				[self cloneFreeLists: sourceObj]
+ 			ifFalse:
+ 				[(self shouldClone: sourceObj) ifTrue:
+ 					[self clone: sourceObj]]]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>ensureSmallFloatInClassTable (in category 'bootstrap image') -----
+ ensureSmallFloatInClassTable
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fileNameExtension (in category 'private-accessing') -----
+ fileNameExtension
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInBitsObject:from: (in category 'bootstrap image') -----
+ fillInBitsObject: targetObj from: sourceObj
+ 	0 to: (sourceHeap numBytesOf: sourceObj) - 1 do:
+ 		[:i|
+ 		targetHeap
+ 			storeByte: i
+ 			ofObject: targetObj
+ 			withValue: (sourceHeap fetchByte: i ofObject: sourceObj)]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
+ fillInCompiledMethod: targetObj from: sourceObj
+ 	| offset |
+ 	"sourceInterpreter printOop: sourceOop"
+ 	"targetInterpreter printOop: targetOop"
+ 	0 to: (sourceHeap numPointerSlotsOf: sourceObj) - 1 do:
+ 		[:i| | sourceOop targetOop |
+ 		 sourceOop := sourceHeap fetchPointer: i ofObject: sourceObj.
+ 		 targetOop := self mapSourceOop: sourceOop.
+ 		 targetHeap
+ 			storePointerUnchecked: i
+ 			ofObject: targetObj
+ 			withValue: targetOop].
+ 	offset := (targetInterpreter startPCOfMethod: targetObj) - (sourceInterpreter startPCOfMethod: sourceObj).
+ 	(sourceInterpreter startPCOfMethod: sourceObj)
+ 		to: (sourceHeap numBytesOf: sourceObj) - 1
+ 		do: [:j|
+ 			targetHeap
+ 				storeByte: offset + j 
+ 				ofObject: targetObj
+ 				withValue: (sourceHeap fetchByte: j ofObject: sourceObj)]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInHeap (in category 'bootstrap image') -----
+ fillInHeap
+ 	| heapEnd freeListsObj |
+ 	heapEnd := targetHeap freeStart.
+ 	targetHeap
+ 		nilObject: (map at: sourceHeap nilObject);
+ 		falseObject: (map at: sourceHeap falseObject);
+ 		trueObject: (map at: sourceHeap trueObject);
+ 		specialObjectsOop: (map at: sourceHeap specialObjectsOop);
+ 		lastHash: sourceHeap lastHash;
+ 		setHiddenRootsObj: (map at: sourceHeap classTableRootObj).
+ 	targetHeap segmentManager
+ 		initSegmentForInImageCompilationFrom: targetHeap nilObject
+ 		to: heapEnd + targetHeap bridgeSize.
+ 	freeListsObj := targetHeap objectAfter: targetHeap trueObject.
+ 	"Nil-out the free lists."
+ 	targetHeap
+ 		fillObj: freeListsObj numSlots: (targetHeap numSlotsOf: freeListsObj) with: 0;
+ 		initializeFreeSpacePostLoad: freeListsObj;
+ 		initializePostBootstrap;
+ 		setEndOfMemory: (targetHeap segmentManager bridgeAt: 0) + targetHeap baseHeaderSize!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInObjects (in category 'bootstrap image') -----
+ fillInObjects
+ 	"sourceInterpreter printOop: sourceObj"
+ 	| i |
+ 	{sourceHeap markStack. sourceHeap weaklingStack. sourceHeap mournQueue} do:
+ 		[:obj|
+ 		obj ~= sourceHeap nilObject ifTrue:
+ 			[map at: obj put: (map at: sourceHeap nilObject)]].
+ 	i := 0.
+ 	sourceHeap allObjectsDo:
+ 		[:sourceObj|
+ 		(i := i + 1) >= 10000 ifTrue:
+ 			[Transcript nextPut: $.; flush. i := 0].
+ 		(map at: sourceObj ifAbsent: nil)
+ 			ifNotNil:
+ 				[:targetObj| | format classIndex |
+ 				(targetHeap numSlotsOf: targetObj) > 0 ifTrue: "filter-out filtered objStack pages"
+ 					[format := sourceHeap formatOf: sourceObj.
+ 					 (targetHeap isPointersFormat: format)
+ 						ifTrue:
+ 							[((targetHeap isIndexableFormat: format)
+ 								and: [(classIndex := targetHeap classIndexOf: targetObj) <= ClassBlockClosureCompactIndex
+ 								and: [classIndex >= ClassMethodContextCompactIndex]])
+ 								ifTrue: [self fillInPointerObjectWithPC: targetObj from: sourceObj]
+ 								ifFalse: [self fillInPointerObject: targetObj from: sourceObj]]
+ 						ifFalse:
+ 							[(targetHeap isCompiledMethodFormat: format)
+ 								ifTrue: [self fillInCompiledMethod: targetObj from: sourceObj]
+ 								ifFalse: [self fillInBitsObject: targetObj from: sourceObj]]]]
+ 			ifNil: [self assert: (self isUnmappedObject: sourceObj)]]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInPointerObject:from: (in category 'bootstrap image') -----
+ fillInPointerObject: targetObj from: sourceObj 
+ 	0 to: (targetHeap numSlotsOf: targetObj) - 1 do:
+ 		[:i|
+ 		 targetHeap
+ 			storePointerUnchecked: i
+ 			ofObject: targetObj
+ 			withValue: (self mapSourceOop: (sourceHeap fetchPointer: i ofObject: sourceObj))]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>fillInPointerObjectWithPC:from: (in category 'bootstrap image') -----
+ fillInPointerObjectWithPC: targetObj from: sourceObj
+ 	| method |
+ 	self fillInPointerObject: targetObj from: sourceObj.
+ 	(targetHeap classIndexOf: targetObj) = ClassBlockClosureCompactIndex ifTrue:
+ 		[method := sourceHeap
+ 						fetchPointer: MethodIndex
+ 						ofObject: (sourceHeap
+ 									fetchPointer: ClosureOuterContextIndex
+ 									ofObject: sourceObj).
+ 		self mapPCField: ClosureStartPCIndex ofObject: targetObj for: method].
+ 	(targetHeap classIndexOf: targetObj) = ClassMethodContextCompactIndex ifTrue:
+ 		[method := sourceHeap
+ 						fetchPointer: MethodIndex
+ 						ofObject: sourceObj.
+ 		 self mapPCField: InstructionPointerIndex ofObject: targetObj for: method]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>findSymbol: (in category 'public access') -----
+ findSymbol: aString
+ 	"Find the Symbol equal to aString in oldHeap."
+ 	| symbolClass |
+ 	(literalMap at: aString ifAbsent: nil) ifNotNil:
+ 		[:oop| ^oop].
+ 	symbolClass := self symbolClass.
+ 	targetHeap allObjectsDo:
+ 		[:obj|
+ 		(symbolClass = (targetHeap fetchClassOfNonImm: obj)
+ 		 and: [(targetHeap numBytesOf: obj) = aString size
+ 		 and: [aString = (targetHeap stringOf: obj)]]) ifTrue:
+ 			[aString isSymbol ifTrue:
+ 				[literalMap at: aString asSymbol put: obj].
+ 			 ^obj]].
+ 	Transcript cr; nextPutAll: 'Warning, could not find '; store: aString; flush.
+ 	^nil!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>initMaps (in category 'initialize-release') -----
+ initMaps
+ 	map := Dictionary new: sourceHeap memory size // 32.
+ 	reverseMap := Dictionary new: sourceHeap memory size // 32.
+ 	literalMap := IdentityDictionary new!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>isUnmappedObject: (in category 'bootstrap image') -----
+ isUnmappedObject: sourceObj
+ 	"Answer if sourceObj is an object that is not cloned by the bootstrap."
+ 	^((sourceHeap classIndexOf: sourceObj)
+ 			between: ClassLargeNegativeIntegerCompactIndex
+ 			and: ClassFloatCompactIndex)
+ 	  or: [sourceObj = sourceHeap freeListsObject
+ 	  or: [(sourceHeap isValidObjStackPage: sourceObj)]]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>mapPCField:ofObject:for: (in category 'bootstrap image') -----
+ mapPCField: fieldIndex ofObject: targetObj for: sourceMethod
+ 	| value |
+ 	value := targetHeap fetchPointer: fieldIndex ofObject: targetObj.
+ 	(targetHeap isIntegerObject: value)
+ 		ifTrue:
+ 			[targetHeap
+ 				storePointerUnchecked: fieldIndex
+ 				ofObject: targetObj
+ 				withValue: (targetHeap integerObjectOf: (targetHeap integerValueOf: value) + (self pcDeltaForSourceMethod: sourceMethod))]
+ 		ifFalse:
+ 			[self assert: (reverseMap at: value) = sourceHeap nilObject]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>mapSourceOop: (in category 'bootstrap image') -----
+ mapSourceOop: sourceObj
+ 	"sourceInterpreter printOop: sourceObj"
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>nilWordSize (in category 'bootstrap image') -----
+ nilWordSize
+ 	| wordSizeSym |
+ 	wordSizeSym := self findSymbol: #WordSize.
+ 	targetHeap allOldSpaceObjectsDo:
+ 		[:o|
+ 		((targetHeap numSlotsOf: o) > ValueIndex
+ 		and: [(targetHeap isPointersNonImm: o)
+ 		and: [(targetHeap fetchPointer: KeyIndex ofObject: o) = wordSizeSym
+ 		and: [(targetHeap fetchPointer: ValueIndex ofObject: o) = (targetHeap integerObjectOf: 4)]]]) ifTrue:
+ 			[targetHeap storePointer: ValueIndex ofObject: o withValue: targetHeap nilObject]]!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>on: (in category 'public access') -----
+ on: imageName
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>pcDeltaForSourceMethod: (in category 'bootstrap image') -----
+ pcDeltaForSourceMethod: sourceMethod
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>shouldClone: (in category 'bootstrap image') -----
+ shouldClone: sourceObj
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>smallFloatClass (in category 'bootstrap image') -----
+ smallFloatClass
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>symbolClass (in category 'public access') -----
+ symbolClass
+ 	^targetHeap fetchClassOfNonImm: (targetHeap splObj: SelectorDoesNotUnderstand)!

Item was added:
+ ----- Method: SpurMtoNBitImageConverter>>writeSnapshot:headerFlags:screenSize: (in category 'snapshot') -----
+ writeSnapshot: imageFileName headerFlags: headerFlags screenSize: screenSizeInteger
+ 	targetHeap
+ 		checkFreeSpace;
+ 		runLeakCheckerForFullGC.
+ 	targetInterpreter
+ 		setImageHeaderFlagsFrom: headerFlags;
+ 		setDisplayForm: nil;
+ 		setSavedWindowSize: savedWindowSize;
+ 		imageName: imageFileName;
+ 		writeImageFileIO.
+ 	Transcript cr; show: 'Done!!'!




More information about the Vm-dev mailing list