VM Maker: Cog-eem.214.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: Cog-eem.214.mcz

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

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

Name: Cog-eem.214
Author: eem
Time: 17 November 2014, 8:51:07.822 pm
UUID: 294b9ee9-efaf-47a0-9a55-a46d75e9c338
Ancestors: Cog-eem.213

Implement the 32-bit to 64-bit Spur bootstrap at least
as far as cloning, but not yet saving the image.  Still to
do are:
- saving the image
- mapping relevant Floats to SmallFloats.

Requres VMMaker.oscog-eem.936.

=============== Diff against Cog-eem.213 ===============

Item was added:
+ ----- Method: SimulatorHarness>>deny: (in category 'testing') -----
+ deny: aBooleanOrBlock
+ aBooleanOrBlock value ifTrue: [AssertionFailure signal: 'Assertion failed']!

Item was added:
+ SimulatorHarness subclass: #SpurBootstrap32to64
+ instanceVariableNames: 'heap32 heap64 map reverseMap interpreter32 interpreter64 imageHeaderFlags savedWindowSize'
+ classVariableNames: ''
+ poolDictionaries: 'VMSqueakClassIndices'
+ category: 'Cog-Bootstrapping'!

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

Item was added:
+ ----- Method: SpurBootstrap32to64>>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: SpurBootstrap32to64>>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')
+ ofTransformedImage: heap32
+ headerFlags: imageHeaderFlags
+ screenSize: savedWindowSize.
+ dir deleteFileNamed: baseName, '-64.changes';
+ copyFileNamed: baseName, '.changes' toFileNamed: baseName, '-64.changes'!

Item was added:
+ ----- Method: SpurBootstrap32to64>>clone: (in category 'bootstrap image') -----
+ clone: obj32
+ | obj64 format numSlots numBytes |
+ 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).
+ reverseMap at: obj64 put: obj32.
+ ^map at: obj32 put: obj64!

Item was added:
+ ----- Method: SpurBootstrap32to64>>cloneObjects (in category 'bootstrap image') -----
+ cloneObjects
+ heap32 allObjectsDo:
+ [:obj32| | classIndex value |
+ classIndex := heap32 classIndexOf: obj32.
+ ((classIndex between: ClassLargeNegativeIntegerCompactIndex and: ClassLargePositiveIntegerCompactIndex)
+ and: [interpreter32 initPrimCall.
+ value := heap32 positive64BitValueOf: obj32.
+ interpreter32 failed not
+ and: [heap64 isIntegerValue: value]]) ifFalse:
+ [self clone: obj32]]!

Item was added:
+ ----- Method: SpurBootstrap32to64>>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 added:
+ ----- Method: SpurBootstrap32to64>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
+ fillInCompiledMethod: obj64 from: obj32
+ | offset |
+ 0 to: (heap32 numPointerSlotsOf: obj32) - 1 do:
+ [:i|
+ heap64
+ storePointerUnchecked: i
+ ofObject: obj64
+ withValue: (self map32BitOop: (heap32 fetchPointer: i ofObject: obj32))].
+ offset := (interpreter64
+ initialPCForHeader: (heap64 methodHeaderOf: obj64)
+ method: obj64)
+ - (interpreter32
+ initialPCForHeader: (heap32 methodHeaderOf: obj32)
+ method: obj32).
+ (interpreter32
+ initialPCForHeader: (heap32 methodHeaderOf: obj32)
+ method: obj32)
+ to: (heap32 numBytesOf: obj32) - 1
+ do: [:i|
+ heap64
+ storeByte: offset + i
+ ofObject: obj64
+ withValue: (heap32 fetchByte: i ofObject: obj32)]!

Item was added:
+ ----- Method: SpurBootstrap32to64>>fillInObjects (in category 'bootstrap image') -----
+ fillInObjects
+ heap32 allObjectsDo:
+ [:obj32|
+ (map at: obj32 ifAbsent: nil)
+ ifNotNil:
+ [:obj64| | format classIndex |
+ 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: ((heap32 classIndexOf: obj32)
+ between: ClassLargeNegativeIntegerCompactIndex
+ and: ClassLargePositiveIntegerCompactIndex)]]!

Item was added:
+ ----- Method: SpurBootstrap32to64>>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 added:
+ ----- Method: SpurBootstrap32to64>>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 added:
+ ----- Method: SpurBootstrap32to64>>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 added:
+ ----- Method: SpurBootstrap32to64>>initMaps (in category 'initialize-release') -----
+ initMaps
+ map := Dictionary new: heap32 memory size // 32.
+ reverseMap := Dictionary new: heap32 memory size // 32!

Item was added:
+ ----- Method: SpurBootstrap32to64>>map32BitOop: (in category 'bootstrap image') -----
+ map32BitOop: oop32
+ ^map
+ at: oop32
+ ifAbsent:
+ [(heap32 isImmediate: oop32)
+ ifTrue:
+ [(heap32 isImmediateCharacter: oop32)
+ ifTrue: [heap64 characterObjectOf: (heap32 characterValueOf: oop32)]
+ ifFalse: [heap64 integerObjectOf: (heap32 integerValueOf: oop32)]]
+ ifFalse:
+ [| value |
+ self assert: ((heap32 classIndexOf: oop32)
+ between: ClassLargeNegativeIntegerCompactIndex
+ and: ClassLargePositiveIntegerCompactIndex).
+ interpreter32 initPrimCall.
+ value := heap32 positive64BitValueOf: oop32.
+ self deny: interpreter32 failed.
+ heap64 integerObjectOf: value]]!

Item was added:
+ ----- Method: SpurBootstrap32to64>>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 changed:
  SimulatorHarness subclass: #SpurOldToNewMethodFormatMunger
  instanceVariableNames: 'interpreter heap prototypes replacements symbolOops'
  classVariableNames: ''
  poolDictionaries: 'VMObjectIndices'
  category: 'Cog-Bootstrapping'!
+
+ !SpurOldToNewMethodFormatMunger commentStamp: 'eem 11/17/2014 10:36' prior: 0!
+ A SpurOldToNewMethodFormatMunger is a one-off for mirating a Spur image prior to the two formats to single format CompiledMethod header putsch.
+ !