VM Maker: VMMaker.oscog-eem.2428.mcz

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

VM Maker: VMMaker.oscog-eem.2428.mcz

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

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

Name: VMMaker.oscog-eem.2428
Author: eem
Time: 13 August 2018, 3:27:58.198059 pm
UUID: a41e2021-d5fb-46f3-870f-2f3f866c5631
Ancestors: VMMaker.oscog-AlistairGrant.2427

Work around some Squeak specificities.
Update the VMMakerDecompilerTests decompilerFailures

=============== Diff against VMMaker.oscog-AlistairGrant.2427 ===============

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  "CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
 
  | f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
   headerFlags firstSegSize heapSize
   hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
   hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
  "open image file and read the header"
 
  f := FileStream readOnlyFileNamed: fileName.
  f ifNil: [^self error: 'no image found'].
 
  "Set the image name and the first argument; there are
  no arguments during simulation unless set explicitly."
  systemAttributes at: 1 put: fileName; at: 2 put: nil.
 
  ["begin ensure block..."
  imageName := f fullName.
  f binary.
 
  version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  (self readableFormat: version)
  ifTrue: [swapBytes := false]
  ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  ifTrue: [swapBytes := true]
  ifFalse: [self error: 'incomaptible image format']].
  headerSize := self getWord32FromFile: f swap: swapBytes.
  dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
 
  savedWindowSize := self getLongFromFile: f swap: swapBytes.
  headerFlags := self getLongFromFile: f swap: swapBytes.
  self setImageHeaderFlagsFrom: headerFlags.
  extraVMMemory := self getWord32FromFile: f swap: swapBytes.
  hdrNumStackPages := self getShortFromFile: f swap: swapBytes.
  "4 stack pages is small.  Should be able to run with as few as
  three. 4 should be comfortable but slow.  8 is a reasonable
  default. Can be changed via vmParameterAt: 43 put: n"
  numStackPages := desiredNumStackPages ~= 0
  ifTrue: [desiredNumStackPages]
  ifFalse: [hdrNumStackPages = 0
  ifTrue: [self defaultNumStackPages]
  ifFalse: [hdrNumStackPages]].
  desiredNumStackPages := hdrNumStackPages.
  stackZoneSize := self computeStackZoneSize.
  "This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  cogCodeSize := desiredCogCodeSize ~= 0
  ifTrue: [desiredCogCodeSize]
  ifFalse:
  [hdrCogCodeSize = 0
  ifTrue: [cogit defaultCogCodeSize]
  ifFalse: [hdrCogCodeSize]].
  desiredCogCodeSize := hdrCogCodeSize.
  self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  hdrEdenBytes := self getWord32FromFile: f swap: swapBytes.
  objectMemory edenBytes: (desiredEdenBytes ~= 0
  ifTrue: [desiredEdenBytes]
  ifFalse:
  [hdrEdenBytes = 0
  ifTrue: [objectMemory defaultEdenBytes]
  ifFalse: [hdrEdenBytes]]).
  desiredEdenBytes := hdrEdenBytes.
  hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  hdrMaxExtSemTabSize ~= 0 ifTrue:
  [self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  "pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  Preserve it to be polite to other VMs."
  the2ndUnknownShort := self getShortFromFile: f swap: swapBytes.
  self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  firstSegSize := self getLongFromFile: f swap: swapBytes.
  objectMemory firstSegmentSize: firstSegSize.
  "For Open PICs to be able to probe the method cache during
  simulation the methodCache must be relocated to memory."
  methodCacheSize := methodCache size * objectMemory wordSize.
  primTraceLogSize := primTraceLog size * objectMemory wordSize.
  "allocate interpreter memory. This list is in address order, low to high.
  In the actual VM the stack zone exists on the C stack."
  heapBase := (Cogit guardPageSize
  + cogCodeSize
  + stackZoneSize
  + methodCacheSize
  + primTraceLogSize
  + self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  "compare memory requirements with availability"
  allocationReserve := self interpreterAllocationReserveBytes.
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [| freeOldSpaceInImage headroom |
  freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  headroom := objectMemory
  initialHeadroom: extraVMMemory
  givenFreeOldSpaceInImage: freeOldSpaceInImage.
  heapSize := objectMemory roundUpHeapSize:
    dataSize
  + headroom
  + objectMemory newSpaceBytes
  + (headroom > allocationReserve
  ifTrue: [0]
  ifFalse: [allocationReserve])]
  ifFalse:
  [heapSize :=  dataSize
  + extraBytes
  + objectMemory newSpaceBytes
  + (extraBytes > allocationReserve
  ifTrue: [0]
  ifFalse: [allocationReserve])].
  heapBase := objectMemory
  setHeapBase: heapBase
  memoryLimit:  heapBase + heapSize
  endOfMemory: heapBase + dataSize.
 
  self assert: cogCodeSize \\ 4 = 0.
  self assert: objectMemory memoryLimit \\ 4 = 0.
  self assert: self rumpCStackSize \\ 4 = 0.
  objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  "read in the image in bulk, then swap the bytes if necessary"
  f position: headerSize.
  count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  count ~= dataSize ifTrue: [self halt]]
  ensure: [f close].
  self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
  self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
 
  self ensureImageFormatIsUpToDate: swapBytes.
 
  bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
+ UIManager default
- Utilities
  informUser: 'Relocating object pointers...'
  during: [self initializeInterpreter: bytesToShift].
  self initializeCodeGenerator!

Item was changed:
  ----- Method: CogVMSimulator>>reverseBytesInImage (in category 'image save/restore') -----
  reverseBytesInImage
+ UIManager default
- Utilities
  informUser: 'Swapping bytes of foreign image...'
  during: [super reverseBytesInImage]!

Item was changed:
  ----- Method: InterpreterSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  "InterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
 
  | f version headerSize count oldBaseAddr bytesToShift swapBytes |
  "open image file and read the header"
 
  ["begin ensure block..."
  f := FileStream readOnlyFileNamed: fileName.
  imageName := f fullName.
  f binary.
  version := self nextLongFrom: f.  "current version: 16r1968 (=6504) vive la revolucion!!"
  (self readableFormat: version)
  ifTrue: [swapBytes := false]
  ifFalse: [(version := self byteSwapped: version) = self imageFormatVersion
  ifTrue: [swapBytes := true]
  ifFalse: [self error: 'incomaptible image format']].
  headerSize := self nextLongFrom: f swap: swapBytes.
  self setEndOfMemory: (self nextLongFrom: f swap: swapBytes).  "first unused location in heap"
  oldBaseAddr := self nextLongFrom: f swap: swapBytes.  "object memory base address of image"
  specialObjectsOop := self nextLongFrom: f swap: swapBytes.
  lastHash := self nextLongFrom: f swap: swapBytes.  "Should be loaded from, and saved to the image header"
  lastHash = 0 ifTrue: [lastHash := 999].
 
  savedWindowSize := self nextLongFrom: f swap: swapBytes.
  fullScreenFlag := self nextLongFrom: f swap: swapBytes.
  extraVMMemory := self nextLongFrom: f swap: swapBytes.
 
  "allocate interpreter memory"
  self setMemoryLimit: endOfMemory + extraBytes.
 
  "read in the image in bulk, then swap the bytes if necessary"
  f position: headerSize.
  memory := Bitmap new: memoryLimit // 4.
  count := f readInto: memory startingAt: 1 count: endOfMemory // 4.
  count ~= (endOfMemory // 4) ifTrue: [self halt].
  ]
  ensure: [f close].
 
+ swapBytes ifTrue:
+ [UIManager default
+ informUser: 'Swapping bytes of foreign image...'
+ during: [self reverseBytesInImage]].
- swapBytes ifTrue: [Utilities informUser: 'Swapping bytes of foreign image...'
- during: [self reverseBytesInImage]].
 
  self initialize.
  bytesToShift := self startOfMemory - oldBaseAddr.  "adjust pointers for zero base address"
  Utilities informUser: 'Relocating object pointers...'
  during: [self initializeInterpreter: bytesToShift].
  !

Item was changed:
  ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  "StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
 
  | f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
   headerFlags heapBase firstSegSize heapSize
   hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize allocationReserve |
  "open image file and read the header"
 
  f := FileStream readOnlyFileNamed: fileName.
  f ifNil: [^self error: 'no image found'].
 
  "Set the image name and the first argument; there are
  no arguments during simulation unless set explicitly."
  systemAttributes at: 1 put: fileName; at: 2 put: nil.
 
  ["begin ensure block..."
  imageName := f fullName.
  f binary.
 
  version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  (self readableFormat: version)
  ifTrue: [swapBytes := false]
  ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  ifTrue: [swapBytes := true]
  ifFalse: [self error: 'incomaptible image format']].
  headerSize := self getWord32FromFile: f swap: swapBytes.
  dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
 
  savedWindowSize := self getLongFromFile: f swap: swapBytes.
  headerFlags := self getLongFromFile: f swap: swapBytes.
  self setImageHeaderFlagsFrom: headerFlags.
  extraVMMemory := self getWord32FromFile: f swap: swapBytes.
  hdrNumStackPages := self getShortFromFile: f swap: swapBytes.
  "4 stack pages is small.  Should be able to run with as few as
  three. 4 should be comfortable but slow.  8 is a reasonable
  default. Can be changed via vmParameterAt: 43 put: n"
  numStackPages := desiredNumStackPages ~= 0
  ifTrue: [desiredNumStackPages]
  ifFalse: [hdrNumStackPages = 0
  ifTrue: [self defaultNumStackPages]
  ifFalse: [hdrNumStackPages]].
  desiredNumStackPages := hdrNumStackPages.
  "pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  theUnknownShort := self getShortFromFile: f swap: swapBytes.
  self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  hdrEdenBytes := self getWord32FromFile: f swap: swapBytes.
  objectMemory edenBytes: (hdrEdenBytes = 0
  ifTrue: [objectMemory defaultEdenBytes]
  ifFalse: [hdrEdenBytes]).
  desiredEdenBytes := hdrEdenBytes.
  hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  hdrMaxExtSemTabSize ~= 0 ifTrue:
  [self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  "pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  Preserve it to be polite to other VMs."
  the2ndUnknownShort := self getShortFromFile: f swap: swapBytes.
  self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  firstSegSize := self getLongFromFile: f swap: swapBytes.
  objectMemory firstSegmentSize: firstSegSize.
  "compare memory requirements with availability"
  allocationReserve := self interpreterAllocationReserveBytes.
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [| freeOldSpaceInImage headroom |
  freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  headroom := objectMemory
  initialHeadroom: extraVMMemory
  givenFreeOldSpaceInImage: freeOldSpaceInImage.
  heapSize := objectMemory roundUpHeapSize:
    dataSize
  + headroom
  + objectMemory newSpaceBytes
  + (headroom > allocationReserve
  ifTrue: [0]
  ifFalse: [allocationReserve])]
  ifFalse:
  [heapSize :=  dataSize
  + extraBytes
  + objectMemory newSpaceBytes
  + (extraBytes > allocationReserve
  ifTrue: [0]
  ifFalse: [allocationReserve])].
  "allocate interpreter memory"
  heapBase := objectMemory startOfMemory.
  objectMemory
  setHeapBase: heapBase
  memoryLimit: heapBase + heapSize
  endOfMemory: heapBase + dataSize. "bogus for Spur"
  objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  "read in the image in bulk, then swap the bytes if necessary"
  f position: headerSize.
  count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  count ~= dataSize ifTrue: [self halt]]
  ensure: [f close].
 
  self ensureImageFormatIsUpToDate: swapBytes.
 
  bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
+ UIManager default
- Utilities
  informUser: 'Relocating object pointers...'
  during: [self initializeInterpreter: bytesToShift]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>reverseBytesInImage (in category 'image save/restore') -----
  reverseBytesInImage
+ UIManager default
- Utilities
  informUser: 'Swapping bytes of foreign image...'
  during: [super reverseBytesInImage]!

Item was changed:
  ----- Method: VMClass class>>initialize (in category 'initialization') -----
  initialize
  InitializationOptions ifNil: [InitializationOptions := Dictionary new].
+ ExpensiveAsserts := false.
+ (Smalltalk classNamed: #Utilities) ifNotNil:
+ [:utilitiesClass|
+ (utilitiesClass classPool at: #CommonRequestStrings ifAbsent: []) ifNotNil:
+ [:commonRequestStringHolder|
+ (commonRequestStringHolder contents asString includesSubstring: 'VMClass open') ifFalse:
+ [Utilities appendToCommonRequests: '-\VMMaker generateConfiguration\VMMaker generateAllConfigurationsUnderVersionControl\VMMaker generateAllSpurConfigurations\VMClass openCogMultiWindowBrowser\VMClass openObjectMemoriesInterpretersBrowser\VMClass openSpurMultiWindowBrowser\VMClass openCogSpurMultiWindowBrowser\VMClass openCogitMultiWindowBrowser' withCRs]]]!
- (Utilities classPool at: #CommonRequestStrings ifAbsent: []) ifNotNil:
- [:commonRequestStringHolder|
- (commonRequestStringHolder contents asString includesSubstring: 'VMClass open') ifFalse:
- [Utilities appendToCommonRequests: '-\VMMaker generateConfiguration\VMMaker generateAllConfigurationsUnderVersionControl\VMMaker generateAllSpurConfigurations\VMClass openCogMultiWindowBrowser\VMClass openObjectMemoriesInterpretersBrowser\VMClass openSpurMultiWindowBrowser\VMClass openCogSpurMultiWindowBrowser\VMClass openCogitMultiWindowBrowser' withCRs]].
- ExpensiveAsserts := false!

Item was changed:
  ----- Method: VMMaker class>>initialize (in category 'initialisation') -----
  initialize
  "VMMaker initialize"
  DirNames := Dictionary new.
  DirNames
  at: #coreVMDir put: 'vm';
  at: #platformsDir put: 'platforms';
  at: #pluginsDir put: 'plugins';
  at: #sourceDir put: 'src'.
 
  "Try and decide where the Cog source tree is.  Two configurations are likely.
  One is that the VMMaker image is running in the image directory in the
  source tree and hence everything will be at '..'.
  Another is where the source tree is at the same level as the VMMaker image,
  in which case it is likely called oscogvm or Cog."
  #('../platforms' 'oscogvm/platforms' 'Cog/platforms' '../oscogvm/platforms')
  with: #('..' 'oscogvm' 'Cog' '../oscogvm')
+ do: ((Smalltalk classNamed: #FileSystem)
+ ifNotNil:
+ [[:dir :path|
+  (FileLocator cwd / dir) isDirectory ifTrue:
+ [DirNames at: #sourceTree put: path.
+ ^self]]]
+ ifNil:
+ [[:dir :path|
+  (FileDirectory default directoryExists: dir) ifTrue:
+ [DirNames at: #sourceTree put: path.
+ ^self]]])!
- do: [:dir :path|
- (FileDirectory default directoryExists: dir) ifTrue:
- [DirNames at: #sourceTree put: path.
- ^self]]!

Item was added:
+ ----- Method: VMMakerDecompilerTests>>decompilerFailures (in category 'utilities') -----
+ decompilerFailures
+ "Here is the list of failures: either a syntax error, a hard error or some failure to decompile correctly.
+ Collected via
+ DecompilerTestFailuresCollector new computeFailures."
+
+ "class name, selector, error class name or nil"
+ ^  #(
+ #(BitBltSimulator primitive:parameters:receiver: ResumableTestFailure)  "expr ifTrue: [^foo] ifFalse: [bar] => expr ifTrue: [^foo]. bar"
+ )
+
+ !

Item was removed:
- ----- Method: VMMakerTool>>findPlatformsPathFrom: (in category 'path access') -----
- findPlatformsPathFrom: fd
- | path |
- Utilities informUserDuring:[:bar|
- path := self findPlatformsPathFrom: fd informing: bar.
- ].
- ^path!