VM Maker: Cog-eem.402.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.402.mcz

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

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

Name: Cog-eem.402
Author: eem
Time: 12 March 2020, 1:01:58.130173 pm
UUID: 37e10bd3-aae4-4dfa-9f4b-d0a4ed0caa3d
Ancestors: Cog-eem.401

Spur 32<->64 bit conversion.
Fix a bug in testing formats in fillInObjects (how did this ever work??).

Fix a bug with conversion and SistaV1/FullBlocks; the method header integer was not correctly mapped on 64->32 bit conversion.

Update conversion to mark literals expanded from large immediates on 64->32 bit conversion as immutable, if it appears that literals are immutable in the source image.

Do a better job of renaming, avoiding e.g. trunk6-64-32.

=============== Diff against Cog-eem.401 ===============

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

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>mapMethodHeaderOop: (in category 'bootstrap image') -----
+ mapMethodHeaderOop: sourceSmallInteger
+ ^targetHeap integerObjectOf: (sourceHeap integerValueOf: sourceSmallInteger)!

Item was added:
+ ----- Method: Spur32to64BitImageConverter>>rename: (in category 'private-accessing') -----
+ rename: baseName
+ ^(baseName endsWith: '32')
+ ifTrue: [(baseName allButLast: 2), '64']
+ ifFalse: [baseName, '-64']!

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

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>alterSystem (in category 'bootstrap image') -----
+ alterSystem
+ super alterSystem.
+ self ensureAllLiteralsAreReadOnlyIfLiteralsAppearToBeReadOnly!

Item was changed:
  ----- 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:
+ [numCompiledCode := numCompiledCode + 1.
+ numSlots := numBytes + 3 // 4.
- [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:
+ [numReadOnly := numReadOnly + 1.
+ targetHeap setIsImmutableOf: targetObj to: true].
- [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>>ensureAllLiteralsAreReadOnlyIfLiteralsAppearToBeReadOnly (in category 'bootstrap image') -----
+ ensureAllLiteralsAreReadOnlyIfLiteralsAppearToBeReadOnly
+ numReadOnly <= (numCompiledCode // 4) ifTrue: [^self].
+ targetHeap allOldSpaceObjectsDo:
+ [:o|
+ (targetHeap isCompiledMethod: o) ifTrue:
+ [1 to: (targetHeap literalCountOf: o) do:
+ [:i| self recursivelySetReadOnlyIfLiteralNumber: (targetHeap fetchPointer: i ofObject: o)]]]!

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

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>mapMethodHeaderOop: (in category 'bootstrap image') -----
+ mapMethodHeaderOop: sourceSmallInteger
+ "This is tricky; the sign bit is a bytecocde set flag, and other than the sign bit
+ only the least significant 31 bits of a method header SmallInteger are significant."
+ | value |
+ value := sourceHeap integerValueOf: sourceSmallInteger.
+ self assert: (value noMask: 16rFFFFFFFC0000000).
+ ^targetHeap integerObjectOf: (value < 0
+ ifTrue: [(value bitAnd: targetHeap maxSmallInteger) + targetHeap minSmallInteger]
+ ifFalse: [value])!

Item was changed:
  ----- 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.
+ numCompiledCode := numReadOnly := 0. "these are used to guess if literals are read-only..."
+ self initMaps
+ !
- self initMaps!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>recursivelySetReadOnlyIfLiteralNumber: (in category 'bootstrap image') -----
+ recursivelySetReadOnlyIfLiteralNumber: aLiteral
+ (targetHeap isImmediate: aLiteral) ifTrue: [^self].
+ (targetHeap isArrayNonImm: aLiteral) ifTrue:
+ [^0 to: (targetHeap numSlotsOf: aLiteral) - 1 do:
+ [:i| self recursivelySetReadOnlyIfLiteralNumber: (targetHeap fetchPointer: i ofObject: aLiteral)]].
+ ((targetHeap isPureBitsNonImm: aLiteral) "could be ByteString, ByteArray, Large[Posi|Nega]tiveInteger, BoxedFloat64"
+ and: [(targetHeap isImmutable: aLiteral) not]) ifTrue: "could only be Large[Posi|Nega]tiveInteger, BoxedFloat64 expanded from SmallInteger, SmallFloat64..."
+ [targetHeap setIsImmutableOf: aLiteral to: true]!

Item was added:
+ ----- Method: Spur64to32BitImageConverter>>rename: (in category 'private-accessing') -----
+ rename: baseName
+ ^(baseName endsWith: '64')
+ ifTrue: [(baseName allButLast: 2), '32']
+ ifFalse: [baseName, '-32']!

Item was changed:
  ----- 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: (self rename: baseName), '.image')
- self writeSnapshot: (dir fullNameFor: baseName, self fileNameExtension, '.image')
  headerFlags: imageHeaderFlags
  screenSize: savedWindowSize.
+ dir deleteFileNamed: (self rename: baseName), '.changes';
+ copyFileNamed: baseName, '.changes' toFileNamed: (self rename: baseName), '.changes'!
- dir deleteFileNamed: baseName,  self fileNameExtension, '.changes';
- copyFileNamed: baseName, '.changes' toFileNamed: baseName,  self fileNameExtension, '.changes'!

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

Item was changed:
  ----- Method: SpurMtoNBitImageConverter>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
  fillInCompiledMethod: targetObj from: sourceObj
+ | sourceOop targetOop offset |
- | offset |
  "sourceInterpreter printOop: sourceOop"
  "targetInterpreter printOop: targetOop"
+ targetHeap
+ storePointerUnchecked: 0
+ ofObject: targetObj
+ withValue: (self mapMethodHeaderOop: (sourceHeap fetchPointer: 0 ofObject: sourceObj)).
+ 1 to: (sourceHeap numPointerSlotsOf: sourceObj) - 1 do:
+ [:i|
- 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 changed:
  ----- Method: SpurMtoNBitImageConverter>>fillInObjects (in category 'bootstrap image') -----
  fillInObjects
  "sourceInterpreter printOop: sourceObj"
  | i freeListsObject |
  {sourceHeap markStack. sourceHeap weaklingStack. sourceHeap mournQueue} do:
  [:obj|
  obj ~= sourceHeap nilObject ifTrue:
  [map at: obj put: (map at: sourceHeap nilObject)]].
  i := 0.
  freeListsObject := sourceHeap freeListsObject.
  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.
+ (sourceHeap isPointersFormat: format)
- (targetHeap isPointersFormat: format)
  ifTrue:
+ [((sourceHeap isIndexableFormat: format)
- [((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:
+ [(sourceHeap isCompiledMethodFormat: format)
- [(targetHeap isCompiledMethodFormat: format)
  ifTrue: [self fillInCompiledMethod: targetObj from: sourceObj]
  ifFalse:
  [sourceObj ~= freeListsObject ifTrue:
  [self fillInBitsObject: targetObj from: sourceObj]]]]]
  ifNil: [self assert: (self isUnmappedObject: sourceObj)]]!

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

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