VM Maker: VMMaker.oscog-eem.938.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.938.mcz

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

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

Name: VMMaker.oscog-eem.938
Author: eem
Time: 18 November 2014, 2:32:10.076 pm
UUID: 6b72ed8b-d485-4ffe-a710-f207bd7141f0
Ancestors: VMMaker.oscog-eem.937

Rewrite image save to match the recent 64-bit image
load changes.
Nuke obsolete storeHeaderOnFile:bytesPerWord: and
assorted detritus.

=============== Diff against VMMaker.oscog-eem.937 ===============

Item was removed:
- ----- Method: CCodeGenerator>>storeHeaderOnFile:bytesPerWord: (in category 'public') -----
- storeHeaderOnFile: fileName bytesPerWord: bytesPerWord
- "Store C header code for this interpreter on the given file."
-
- | aStream |
- aStream := VMMaker forceNewFileNamed: fileName.
- aStream ifNil: [Error signal: 'Could not open C header file: ', fileName].
- aStream
- nextPutAll: '/* ';
- nextPutAll: VMMaker headerNotice;
- nextPutAll: ' */'; cr; cr.
- self writeDefineBytesPerWord: bytesPerWord on: aStream.
- self writeDefineMemoryAccessInImageOn: aStream.
- self writeDefaultMacrosOn: aStream.
- aStream close!

Item was removed:
- ----- Method: CCodeGenerator>>writeDefaultMacrosOn: (in category 'public') -----
- writeDefaultMacrosOn: aStream
- "Write macros to provide default implementations of certain functions used by
- the interpreter. If not previously defined in config.h they will be defined here.
- The definitions will be available to any module that includes sqMemoryAccess.h.
- The default macros are chosen for backward compatibility with existing platform
- support code."
-
- aStream cr;
- nextPutAll: '#ifndef allocateMemoryMinimumImageFileHeaderSize'; cr;
- nextPutAll: ' /* Called by Interpreter>>allocateMemory:minimum:imageFile:headerSize: */'; cr;
- nextPutAll: ' #define allocateMemoryMinimumImageFileHeaderSize(',
- 'heapSize, minimumMemory, fileStream, headerSize) \'; cr;
- nextPutAll: '    sqAllocateMemory(minimumMemory, heapSize)'; cr;
- nextPutAll: '#endif'; cr; cr;
- nextPutAll: '#ifndef sqImageFileReadEntireImage'; cr;
- nextPutAll: ' /* Called by Interpreter>>sqImage:read:size:length: */'; cr;
- nextPutAll: ' #define sqImageFileReadEntireImage(memoryAddress, fileStream, ',
- 'elementSize,  length) \'; cr;
- nextPutAll: '    sqImageFileRead(memoryAddress, fileStream, elementSize,  length)'; cr;
- nextPutAll: '#endif'; cr; cr
- !

Item was removed:
- ----- Method: CCodeGenerator>>writeDefineBytesPerWord:on: (in category 'public') -----
- writeDefineBytesPerWord: bytesPerWord on: aStream
- aStream
- nextPutAll: '#define SQ_VI_BYTES_PER_WORD ';
- print: bytesPerWord;
- cr
- !

Item was removed:
- ----- Method: CCodeGenerator>>writeDefineMemoryAccessInImageOn: (in category 'public') -----
- writeDefineMemoryAccessInImageOn: aStream
- "If MemoryAccess is present in the image, then define MEMORY_ACCESS_IN_IMAGE as
- a C preprocessor macro. When MEMORY_ACCESS_IN_IMAGE is defined, the traditional
- C preprocessor macros for low level memory access are ignored and will be replaced
- by directly translated (and inlined) SLANG versions of the same. This enables visibility
- of the memory access functions for debuggers and profilers."
-
- (Smalltalk classNamed: #MemoryAccess)
- ifNotNilDo: [:ma | ma isEnabled
- ifTrue: [aStream nextPutAll: '#define MEMORY_ACCESS_IN_IMAGE 1'; cr]]
- !

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  "Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  "Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  "This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
 
  | swapBytes headerStart headerSize dataSize oldBaseAddr
   minimumMemory heapSize bytesRead bytesToShift firstSegSize
   hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize |
  <var: #f type: #sqImageFile>
  <var: #heapSize type: #usqInt>
  <var: #dataSize type: #'size_t'>
  <var: #minimumMemory type: #usqInt>
  <var: #desiredHeapSize type: #usqInt>
  <var: #headerStart type: #squeakFileOffsetType>
  <var: #imageOffset type: #squeakFileOffsetType>
 
  metaclassNumSlots := 6. "guess Metaclass instSize"
  classNameIndex := 6. "guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
+ headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
- headerStart := (self sqImageFilePosition: f) - objectMemory wordSize.  "record header start position"
 
+ headerSize := self getWord32FromFile: f swap: swapBytes.
- headerSize := self getLongFromFile: f swap: swapBytes.
  dataSize := self getLongFromFile: f swap: swapBytes.
  oldBaseAddr := self getLongFromFile: f swap: swapBytes.
  objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  savedWindowSize := self getLongFromFile: f swap: swapBytes.
+ headerFlags := self getLongFromFile: f swap: swapBytes.
- headerFlags := self getLongFromFile: f swap: swapBytes.
  self setImageHeaderFlagsFrom: headerFlags.
+ extraVMMemory := self getWord32FromFile: f swap: swapBytes. "N.B.  not used."
- extraVMMemory := self getLongFromFile: f swap: swapBytes. "N.B.  not used."
  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.
  Can be set as a preference (Info.plist, VM.ini, command line etc).
  If desiredNumStackPages is already non-zero then it has been
  set as a preference.  Ignore (but preserve) the header's default."
  numStackPages := desiredNumStackPages ~= 0
  ifTrue: [desiredNumStackPages]
  ifFalse: [hdrNumStackPages = 0
  ifTrue: [self defaultNumStackPages]
  ifFalse: [hdrNumStackPages]].
  desiredNumStackPages := hdrNumStackPages.
  "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: [self defaultCogCodeSize]
  ifFalse: [hdrCogCodeSize]].
+ hdrEdenBytes := self getWord32FromFile: f swap: swapBytes.
- hdrEdenBytes := self getLongFromFile: 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.
  firstSegSize := self getLongFromFile: f swap: swapBytes.
  objectMemory firstSegmentSize: firstSegSize.
 
  "compare memory requirements with availability"
  minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  + dataSize
  + objectMemory newSpaceBytes
  + self interpreterAllocationReserveBytes.
  heapSize             :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
  + desiredHeapSize
  + objectMemory newSpaceBytes
  + self interpreterAllocationReserveBytes.
  heapSize < minimumMemory ifTrue:
  [self insufficientMemorySpecifiedError].
 
  "allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  objectMemory memory: (self
  allocateMemory: heapSize
  minimum: minimumMemory
  imageFile: f
  headerSize: headerSize) asUnsignedInteger.
  objectMemory memory ifNil: [self insufficientMemoryAvailableError].
 
  heapBase := objectMemory
  setHeapBase: objectMemory memory + cogCodeSize
  memoryLimit: objectMemory memory + heapSize
  endOfMemory: objectMemory memory + cogCodeSize + dataSize.
 
  "position file after the header"
  self sqImageFile: f Seek: headerStart + headerSize.
 
  "read in the image in bulk, then swap the bytes if necessary"
  bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
 
  self ensureImageFormatIsUpToDate: swapBytes.
 
  "compute difference between old and new memory base addresses"
  bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  self initializeCodeGenerator.
  ^dataSize!

Item was removed:
- ----- Method: CogVMSimulator>>getLongFromFile:swap: (in category 'initialization') -----
- getLongFromFile: aStream swap: swapFlag
- ^swapFlag
- ifTrue: [objectMemory byteSwapped: (self nextLongFrom: aStream)]
- ifFalse: [self nextLongFrom: aStream]!

Item was removed:
- ----- Method: CogVMSimulator>>nextLongFrom: (in category 'initialization') -----
- nextLongFrom: aStream
- "Read a 32-bit quantity from the given (binary) stream."
- ^self subclassResponsibility!

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 |
  "open image file and read the header"
 
  f := FileStream readOnlyFileNamed: fileName.
  f ifNil: [^self error: 'no image found'].
 
  ["begin ensure block..."
  imageName := f fullName.
  f binary.
 
+ version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
- version := self nextLongFrom: f.  "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.
- headerSize := self getLongFromFile: 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.
- extraVMMemory := self getLongFromFile: 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: [self defaultCogCodeSize]
  ifFalse: [hdrCogCodeSize]].
  desiredCogCodeSize := hdrCogCodeSize.
+ self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
+ hdrEdenBytes := self getWord32FromFile: f swap: swapBytes.
- self assert: f position = 40.
- hdrEdenBytes := self getLongFromFile: 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]).
- self assert: f position = 48.
  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.
  heapSize := dataSize
  + extraBytes
  + objectMemory newSpaceBytes
  + self interpreterAllocationReserveBytes
  + (objectMemory hasSpurMemoryManagerAPI
  ifTrue: [headerSize]
  ifFalse: [0]).
  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.
  "read in the image in bulk, then swap the bytes if necessary"
  f position: headerSize.
  objectMemory memory: ((cogit processor endianness == #little
  ifTrue: [LittleEndianBitmap]
  ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  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"
  Utilities
  informUser: 'Relocating object pointers...'
  during: [self initializeInterpreter: bytesToShift].
  self initializeCodeGenerator!

Item was removed:
- ----- Method: CogVMSimulatorLSB>>nextLongFrom: (in category 'initialization') -----
- nextLongFrom: aStream
- "Read a 32- or 64-bit quantity from the given (binary) stream."
-
- ^ aStream nextLittleEndianNumber: objectMemory wordSize!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator>>nextLongFrom:swap: (in category 'image save/restore') -----
- nextLongFrom: aStream swap: swapFlag
- ^swapFlag
- ifTrue: [self byteSwapped: (self nextLongFrom: aStream)]
- ifFalse: [self nextLongFrom: aStream]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator>>nextShortFrom:swap: (in category 'initialization') -----
- nextShortFrom: aStream swap: swapFlag
- | aShort |
- aShort := self nextShortFrom: aStream.
- ^swapFlag
- ifTrue: [(aShort bitShift: -8) + ((aShort bitAnd: 16rFF) bitShift: 8)]
- ifFalse: [aShort]!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorLSB>>nextWord32From: (in category 'initialization') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: 4!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorMSB>>nextWord32From: (in category 'image save/restore') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextNumber: 4!

Item was removed:
- ----- Method: NewObjectMemorySimulator>>nextLongFrom:swap: (in category 'image save/restore') -----
- nextLongFrom: aStream swap: swapFlag
- ^swapFlag
- ifTrue: [self byteSwapped: (self nextLongFrom: aStream)]
- ifFalse: [self nextLongFrom: aStream]!

Item was removed:
- ----- Method: NewObjectMemorySimulator>>nextShortFrom:swap: (in category 'initialization') -----
- nextShortFrom: aStream swap: swapFlag
- | aShort |
- aShort := self nextShortFrom: aStream.
- ^swapFlag
- ifTrue: [(aShort bitShift: -8) + ((aShort bitAnd: 16rFF) bitShift: 8)]
- ifFalse: [aShort]!

Item was added:
+ ----- Method: NewObjectMemorySimulatorLSB>>nextWord32From: (in category 'initialization') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: 4!

Item was added:
+ ----- Method: NewObjectMemorySimulatorMSB>>nextWord32From: (in category 'image save/restore') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextNumber: 4!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>nextLongFrom: (in category 'initialization') -----
+ nextLongFrom: aStream
+ "Read a 32- or 64-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: self wordSize!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>nextWord32From: (in category 'initialization') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: 4!

Item was added:
+ ----- Method: Spur64BitMMLESimulator>>nextLongFrom: (in category 'initialization') -----
+ nextLongFrom: aStream
+ "Read a 32- or 64-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: self wordSize!

Item was added:
+ ----- Method: Spur64BitMMLESimulator>>nextWord32From: (in category 'initialization') -----
+ nextWord32From: aStream
+ "Read a 32-bit quantity from the given (binary) stream."
+
+ ^aStream nextLittleEndianNumber: 4!

Item was changed:
  ----- Method: StackInterpreter>>checkImageVersionFrom:startingAt: (in category 'image save/restore') -----
  checkImageVersionFrom: f startingAt: imageOffset
  "Read and verify the image file version number and return true if the the given image file needs to be byte-swapped. As a side effect, position the file stream just after the version number of the image header. This code prints a warning and does a hard-exit if it cannot find a valid version number."
  "This code is based on C code by Ian Piumarta."
 
  <inline: false>
  | version firstVersion |
+ <var: #f type: #sqImageFile>
+ <var: #imageOffset type: #squeakFileOffsetType>
- <var: #f type: 'sqImageFile '>
- <var: #imageOffset type: 'squeakFileOffsetType '>
 
  "check the version number"
  self sqImageFile: f Seek: imageOffset.
+ version := firstVersion := self getWord32FromFile: f swap: false.
- version := firstVersion := self getLongFromFile: f swap: false.
  (self readableFormat: version) ifTrue: [^ false].
 
  "try with bytes reversed"
  self sqImageFile: f Seek: imageOffset.
+ version := self getWord32FromFile: f swap: true.
- version := self getLongFromFile: f swap: true.
  (self readableFormat: version) ifTrue: [^ true].
 
  "Note: The following is only meaningful if not reading an embedded image"
  imageOffset = 0 ifTrue:[
  "try skipping the first 512 bytes (prepended by certain Mac file transfer utilities)"
  self sqImageFile: f Seek: 512.
+ version := self getWord32FromFile: f swap: false.
- version := self getLongFromFile: f swap: false.
  (self readableFormat: version) ifTrue: [^ false].
 
  "try skipping the first 512 bytes with bytes reversed"
  self sqImageFile: f Seek: 512.
+ version := self getWord32FromFile: f swap: true.
- version := self getLongFromFile: f swap: true.
  (self readableFormat: version) ifTrue: [^ true]].
 
  "hard failure; abort"
  self print: 'This interpreter (vers. '.
  self printNum: self imageFormatVersion.
  self print: ') cannot read image file (vers. '.
  self printNum: firstVersion.
  self print: ').'.
  self cr.
  self print: 'Press CR to quit...'.
  self getchar.
  self ioExitWithErrorCode: 1.
  ^false!

Item was changed:
  ----- Method: StackInterpreter>>getLongFromFile:swap: (in category 'image save/restore') -----
  getLongFromFile: aFile swap: swapFlag
+ "Answer the next 32 or 64 bit word read from aFile, byte-swapped according to the swapFlag."
- "Answer the next word read from aFile, byte-swapped according to the swapFlag."
 
+ <var: #aFile type: #sqImageFile>
  | w |
+ <var: #w type: #long>
- <var: #aFile type: 'sqImageFile '>
  w := 0.
+ self cCode: [self
+ sq: (self addressOf: w)
+ Image: (self sizeof: #long)
+ File: 1
+ Read: aFile]
+ inSmalltalk: [w := objectMemory nextLongFrom: aFile].
+ ^swapFlag
+ ifTrue: [objectMemory byteSwapped: w]
+ ifFalse: [w]!
- self cCode: 'sqImageFileRead(&w, sizeof(w), 1, aFile)'.
- swapFlag
- ifTrue: [^ objectMemory byteSwapped: w]
- ifFalse: [^ w].
- !

Item was changed:
  ----- Method: StackInterpreter>>getShortFromFile:swap: (in category 'image save/restore') -----
  getShortFromFile: aFile swap: swapFlag
+ "Answer the next 16 bit word read from aFile, byte-swapped according to the swapFlag."
- "Answer the next half-word read from aFile, byte-swapped according to the swapFlag."
 
+ <var: #aFile type: #sqImageFile>
  | w |
+ <var: #w type: #short>
- <var: #aFile type: #'sqImageFile'>
  w := 0.
+ self cCode: [self
+ sq: (self addressOf: w)
+ Image: (self sizeof: #short)
+ File: 1
+ Read: aFile]
+ inSmalltalk: [w := objectMemory nextShortFrom: aFile].
- self cCode: 'sqImageFileRead(&w, sizeof(unsigned short), 1, aFile)'.
  ^swapFlag
+ ifTrue: [objectMemory byteSwapped: w]
- ifTrue: [(w bitShift: -8) + ((w bitAnd: 16rFF) bitShift: 8)]
  ifFalse: [w]!

Item was added:
+ ----- Method: StackInterpreter>>getWord32FromFile:swap: (in category 'image save/restore') -----
+ getWord32FromFile: aFile swap: swapFlag
+ "Answer the next 32 bit word read from aFile, byte-swapped according to the swapFlag."
+
+ <var: #aFile type: #sqImageFile>
+ | w |
+ <var: #w type: #int>
+ w := 0.
+ self cCode: [self
+ sq: (self addressOf: w)
+ Image: (self sizeof: #int)
+ File: 1
+ Read: aFile]
+ inSmalltalk: [w := objectMemory nextWord32From: aFile].
+ ^swapFlag
+ ifTrue: [objectMemory byteSwapped: w]
+ ifFalse: [w]!

Item was changed:
  ----- Method: StackInterpreter>>putLong:toFile: (in category 'image save/restore') -----
  putLong: aLong toFile: aFile
  "Append aLong to aFile in this platform's 'natural' byte order.  aLong is either 32 or 64 bits,
  depending on ObjectMemory.  (Bytes will be swapped, if necessary, when the image is read
  on a different platform.) Set successFlag to false if the write fails."
 
  <var: #aLong type: #long>
- | objectsWritten |
  <var: #aFile type: #sqImageFile>
+ <inline: false>
+ | objectsWritten |
-
  objectsWritten := self
  cCode: [self sq: (self addressOf: aLong) Image: (self sizeof: #long) File: 1 Write: aFile]
  inSmalltalk:
  [| value |
  value := aLong.
  objectMemory wordSize timesRepeat:
  [aFile nextPut: (value bitAnd: 16rFF).
  value := value >> 8].
  1].
  self success: objectsWritten = 1!

Item was changed:
  ----- Method: StackInterpreter>>putShort:toFile: (in category 'image save/restore') -----
  putShort: aShort toFile: aFile
  "Append the 16-bit aShort to aFile in this platform's 'natural' byte order.
  (Bytes will be swapped, if necessary, when the image is read on a
  different platform.) Set successFlag to false if the write fails."
 
+ <var: #aShort type: #short>
- | objectsWritten |
  <var: #aFile type: #sqImageFile>
+ <inline: false>
+ | objectsWritten |
-
  objectsWritten := self
  cCode: [self sq: (self addressOf: aShort) Image: (self sizeof: #short) File: 1 Write: aFile]
  inSmalltalk:
  [aFile
  nextPut: (aShort bitAnd: 16rFF);
  nextPut: (aShort >> 8 bitAnd: 16rFF).
  1].
  self success: objectsWritten = 1!

Item was changed:
  ----- Method: StackInterpreter>>putWord32:toFile: (in category 'image save/restore') -----
  putWord32: aWord32 toFile: aFile
  "Append aWord32 to aFile in this platform's 'natural' byte order.  aWord32 is 32 bits,
  depending on ObjectMemory.  (Bytes will be swapped, if necessary, when the image is read
  on a different platform.) Set successFlag to false if the write fails."
 
  <var: #aWord32 type: #int>
- | objectsWritten |
  <var: #aFile type: #sqImageFile>
+ <inline: false>
+ | objectsWritten |
-
  objectsWritten := self
  cCode: [self sq: (self addressOf: aWord32) Image: 4 File: 1 Write: aFile]
  inSmalltalk:
  [| value |
  value := aWord32.
  4 timesRepeat:
  [aFile nextPut: (value bitAnd: 16rFF).
  value := value >> 8].
  1].
  self success: objectsWritten = 1!

Item was changed:
  ----- Method: StackInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  "Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  "Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  "This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
 
  | headerStart headerSize headerFlags dataSize oldBaseAddr swapBytes
   minimumMemory bytesRead bytesToShift heapSize firstSegSize
   hdrEdenBytes hdrMaxExtSemTabSize hdrNumStackPages |
  <var: #f type: #sqImageFile>
  <var: #heapSize type: #usqInt>
  <var: #dataSize type: #'size_t'>
  <var: #minimumMemory type: #usqInt>
  <var: #desiredHeapSize type: #usqInt>
  <var: #headerStart type: #squeakFileOffsetType>
  <var: #imageOffset type: #squeakFileOffsetType>
 
  metaclassNumSlots := 6. "guess Metaclass instSize"
  classNameIndex := 6. "guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
+ headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
- headerStart := (self sqImageFilePosition: f) - objectMemory wordSize.  "record header start position"
 
+ headerSize := self getWord32FromFile: f swap: swapBytes.
- headerSize := self getLongFromFile: f swap: swapBytes.
  dataSize := self getLongFromFile: f swap: swapBytes.
  oldBaseAddr := self getLongFromFile: f swap: swapBytes.
  objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  savedWindowSize := self getLongFromFile: f swap: swapBytes.
  headerFlags := self getLongFromFile: f swap: swapBytes.
  self setImageHeaderFlagsFrom: headerFlags.
+ extraVMMemory := self getWord32FromFile: f swap: swapBytes.
- extraVMMemory := self getLongFromFile: 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.
  Can be set as a preference (Info.plist, VM.ini, command line etc).
  If desiredNumStackPages is already non-zero then it has been
  set as a preference.  Ignore (but preserve) the header's default."
  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.
+ hdrEdenBytes := self getWord32FromFile: f swap: swapBytes.
- hdrEdenBytes := self getLongFromFile: 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.
  firstSegSize := self getLongFromFile: f swap: swapBytes.
  objectMemory firstSegmentSize: firstSegSize.
  "decrease Squeak object heap to leave extra memory for the VM"
  heapSize := desiredHeapSize
  + objectMemory newSpaceBytes
  + self interpreterAllocationReserveBytes.
  heapSize := self reserveExtraCHeap: heapSize Bytes: extraVMMemory.
 
  "compare memory requirements with availability".
  minimumMemory := dataSize + objectMemory newSpaceBytes + self interpreterAllocationReserveBytes.
  heapSize < minimumMemory ifTrue:
  [self insufficientMemorySpecifiedError].
 
  "allocate a contiguous block of memory for the Squeak heap"
  objectMemory memory: (self
  allocateMemory: heapSize
  minimum: minimumMemory
  imageFile: f
  headerSize: headerSize) asUnsignedInteger.
  objectMemory memory ifNil: [self insufficientMemoryAvailableError].
 
  objectMemory
  setHeapBase: objectMemory memory
  memoryLimit: objectMemory memory + heapSize
  endOfMemory: objectMemory memory + dataSize.
 
  "position file after the header"
  self sqImageFile: f Seek: headerStart + headerSize.
 
  "read in the image in bulk, then swap the bytes if necessary"
  bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
 
  self ensureImageFormatIsUpToDate: swapBytes.
 
  "compute difference between old and new memory base addresses"
  bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  ^dataSize!

Item was removed:
- ----- Method: StackInterpreterSimulator>>getLongFromFile:swap: (in category 'initialization') -----
- getLongFromFile: aStream swap: swapFlag
- ^swapFlag
- ifTrue: [objectMemory byteSwapped: (self nextLongFrom: aStream)]
- ifFalse: [self nextLongFrom: aStream]!

Item was removed:
- ----- Method: StackInterpreterSimulator>>nextLongFrom: (in category 'initialization') -----
- nextLongFrom: aStream
- "Read a 32-bit quantity from the given (binary) stream."
- ^self subclassResponsibility!

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 |
  "open image file and read the header"
 
  f := FileStream readOnlyFileNamed: fileName.
  f ifNil: [^self error: 'no image found'].
 
  ["begin ensure block..."
  imageName := f fullName.
  f binary.
 
+ version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
- version := self nextLongFrom: f.  "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.
- headerSize := self getLongFromFile: 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.
- extraVMMemory := self getLongFromFile: 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.
- self assert: f position = 40.
- hdrEdenBytes := self getLongFromFile: 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]).
- self assert: f position = 48.
  firstSegSize := self getLongFromFile: f swap: swapBytes.
  objectMemory firstSegmentSize: firstSegSize.
  "allocate interpreter memory"
  heapBase := objectMemory startOfMemory.
  heapSize := dataSize
  + extraBytes
  + objectMemory newSpaceBytes
  + self interpreterAllocationReserveBytes
  + (objectMemory hasSpurMemoryManagerAPI
  ifTrue: [headerSize]
  ifFalse: [0]).
  objectMemory
  setHeapBase: heapBase
  memoryLimit: heapBase + heapSize
  endOfMemory: heapBase + dataSize. "bogus for Spur"
  objectMemory memory: (Bitmap new: objectMemory memoryLimit // 4).
 
  "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"
+ Utilities
+ informUser: 'Relocating object pointers...'
+ during: [self initializeInterpreter: bytesToShift]!
- Utilities informUser: 'Relocating object pointers...'
- during: [self initializeInterpreter: bytesToShift].
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorLSB>>nextLongFrom: (in category 'initialization') -----
- nextLongFrom: aStream
- "Read a 32- or 64-bit quantity from the given (binary) stream."
-
- ^ aStream nextLittleEndianNumber: objectMemory wordSize!