VM Maker Inbox: VMMaker.oscog-dtl.2910.mcz

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

VM Maker Inbox: VMMaker.oscog-dtl.2910.mcz

commits-2
 
A new version of VMMaker was added to project VM Maker Inbox:
http://source.squeak.org/VMMakerInbox/VMMaker.oscog-dtl.2910.mcz

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

Name: VMMaker.oscog-dtl.2910
Author: dtl
Time: 24 December 2020, 10:10:19.306764 pm
UUID: eecad252-d9d1-4e76-ae46-d7e9ef61ac29
Ancestors: VMMaker.oscog-nice.2909

Let the image inform the interpreter that alternate bytecodes either are or are not in use, and remember the setting when writing or reading the image format number in a shapshot file header. Also support testing the current value of multipleBytecodeSetsActive, and listing the encoder names of supported bytecode sets. Add helper methods for string creation borrowed from OSPP.

Adds two primitives:

primitiveMultipleBytecodeSetsActive
        "Given one boolean parameter, set multipleBytecodeSetsActive to inform
         the VM that alternate bytecode sets such as SistaV1 are now in use and
        that the image format number should be updated accordingly. With zero
        parameters, answer the current value of multipleBytecodeSetsActive."

primitiveBytecodeSetsAvailable
        "Answer the encoder names for the supported bytecode sets."

=============== Diff against VMMaker.oscog-nice.2909 ===============

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn ffiExceptionResponse eventTraceMask multipleBytecodeSetsActive'
- instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn ffiExceptionResponse eventTraceMask'
  classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
  poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
  category: 'VMMaker-Interpreter'!
 
  !InterpreterPrimitives commentStamp: 'eem 8/24/2018 11:05' prior: 0!
  InterpreterPrimitives implements most of the VM's core primitives.  It is the root of the interpreter hierarchy so as to share the core primitives amongst the varioius interpreters.
 
  Instance Variables
  argumentCount <Integer>
  ffiExceptionResponse <Integer>
  inFFIFlags <Integer>
  messageSelector <Integer>
  newMethod <Integer>
  nextProfileTick <Integer>
  objectMemory <ObjectMemory> (simulation only)
  preemptionYields <Boolean>
  primFailCode <Integer>
  osErrorCode <Integer>
  profileMethod <Integer>
  profileProcess <Integer>
  profileSemaphore <Integer>
  secHasEnvironmentAccess <Integer>
 
  argumentCount
  - the number of arguments of the current message
 
  ffiExceptionResponse
  - controls system response to exceptions during FFI calls.  See primitiveFailForFFIException:at:
 
  inFFIFlags
  - flags recording currently only whether the system is in an FFI call
 
  messageSelector
  - the oop of the selector of the current message
 
  newMethod
  - the oop of the result of looking up the current message
 
  nextProfileTick
  - the millisecond clock value of the next profile tick (if profiling is in effect)
 
  objectMemory
  - the memory manager and garbage collector that manages the heap
 
  preemptionYields
  - a boolean controlling the process primitives.  If true (old, incorrect, blue-book semantics) a preempted process is sent to the back of its run-queue.  If false, a process preempted by a higher-priority process is put back at the head of its run queue, hence preserving cooperative scheduling within priorities.
 
  primFailCode
  - primitive success/failure flag, 0 for success, otherwise the reason code for failure
 
  osErrorCode
  - a 64-bit value settable by external primitives conveying arbitrary error codes from the operating system and/or system libraries
 
  profileMethod
  - the oop of the method at the time nextProfileTick was reached
 
  profileProcess
  - the oop of the activeProcess at the time nextProfileTick was reached
 
  profileSemaphore
  - the oop of the semaphore to signal when nextProfileTick is reached
 
  secHasEnvironmentAccess
  - the function to call to check if access to the envronment should be granted to primitiveGetenv
  !

Item was added:
+ ----- Method: InterpreterPrimitives>>cString:asCollection: (in category 'primitive support') -----
+ cString: aCString asCollection: classIdentifier
+ "Answer a new collection, usually of type ByteArray or ByteString copied from
+ a null-terminated C string."
+
+ | len newString |
+ <var: 'aCString' type: 'const char *'>
+ len := self strlen: aCString.
+ newString := self
+ instantiateClass: classIdentifier
+ indexableSize: len.
+ self strncpy: (self arrayValueOf: newString)
+ _: aCString
+ _: len. "(char *)strncpy()"
+ ^ newString
+ !

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveBytecodeSetsAvailable (in category 'other primitives') -----
+ primitiveBytecodeSetsAvailable
+ "Answer the encoder names for the supported bytecode sets."
+ <export: true>
+ | encoderNames |
+ argumentCount >0 ifTrue:
+ [^self primitiveFailFor: PrimErrBadNumArgs].
+ encoderNames := self instantiateClass: self classArray indexableSize: 3.
+ self storePointer: 0 ofObject: encoderNames withValue: (self stringFromCString: 'EncoderForV3').
+ self storePointer: 1 ofObject: encoderNames withValue: (self stringFromCString: 'EncoderForV3PlusClosures').
+ self storePointer: 2 ofObject: encoderNames withValue: (self stringFromCString: 'EncoderForSistaV1').
+ self pop: 1 thenPush: encoderNames.
+ !

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveMultipleBytecodeSetsActive (in category 'other primitives') -----
+ primitiveMultipleBytecodeSetsActive
+ "Given one boolean parameter, set multipleBytecodeSetsActive to inform
+ the VM that alternate bytecode sets such as SistaV1 are now in use and
+ that the image format number should be updated accordingly. With zero
+ parameters, answer the current value of multipleBytecodeSetsActive."
+
+ <export: true>
+ argumentCount >1 ifTrue:
+ [^self primitiveFailFor: PrimErrBadNumArgs].
+ argumentCount = 1
+ ifTrue: [self stackTop = objectMemory trueObject
+ ifTrue: [self cppIf: MULTIPLEBYTECODESETS
+ ifTrue: [multipleBytecodeSetsActive := true]
+ ifFalse: [^self primitiveFailFor: PrimErrUnsupported]]
+ ifFalse: [self stackTop = objectMemory falseObject
+ ifTrue: [multipleBytecodeSetsActive := false]
+ ifFalse:[^self primitiveFailFor: PrimErrBadArgument]]].
+ multipleBytecodeSetsActive
+ ifTrue: [self pop: argumentCount + 1 thenPush: objectMemory trueObject]
+ ifFalse: [self pop: argumentCount + 1 thenPush: objectMemory falseObject].
+ !

Item was added:
+ ----- Method: InterpreterPrimitives>>stringFromCString: (in category 'primitive support') -----
+ stringFromCString: aCString
+ "Answer a new ByteString copied from a null-terminated C string."
+
+ <var: 'aCString' type: 'const char *'>
+ ^ self cString: aCString asCollection: self classString
+ !

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
 
  super initializeMiscConstants.
  STACKVM := true.
 
  "These flags function to identify a GC operation, or
  to specify what operations the leak checker should be run for."
  GCModeFull := 1. "stop-the-world global GC"
  GCModeNewSpace := 2. "Spur's scavenge, or V3's incremental"
  GCModeIncremental := 4. "incremental global gc (Dijkstra tri-colour marking); as yet unimplemented"
  GCModeBecome := 8. "v3 post-become sweeping/Spur forwarding"
  GCModeImageSegment := 16. "just a flag for leak checking image segments"
  GCModeFreeSpace := 32. "just a flag for leak checking free space; Spur only"
  GCCheckPrimCall := 64. "just a flag for leak checking external primitive calls"
 
  StackPageTraceInvalid := -1.
  StackPageUnreached := 0.
  StackPageReachedButUntraced := 1.
  StackPageTraced := 2.
 
  DumpStackOnLowSpace := 0.
  MillisecondClockMask := 16r1FFFFFFF.
  "Note: The external primitive table should actually be dynamically sized but for the sake of inferior platforms (e.g., Mac :-) who cannot allocate memory in any reasonable way, we keep it static (and cross our fingers...)"
  MaxExternalPrimitiveTableSize := 4096. "entries"
 
  MaxJumpBuf := 32. "max. callback depth"
  FailImbalancedPrimitives := InitializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].
  EnforceAccessControl := InitializationOptions at: #EnforceAccessControl ifAbsent: [true].
 
  ReturnToInterpreter := 1. "setjmp/longjmp code."
 
  "Because of a hack with callbacks in the non-threaded VM they must not conflct with the VM's tag bits."
  DisownVMForFFICall := 16.
+ DisownVMForThreading := 32.
+
+ "The multiple bytecodes active bit in the image format number"
+ MultipleBytecodeSetsBitmask := 512.
+
- DisownVMForThreading := 32
  !

Item was changed:
  ----- Method: StackInterpreter>>readableFormat: (in category 'image save/restore') -----
  readableFormat: imageVersion
  "Anwer true if images of the given format are readable by this interpreter.
  Allows a virtual machine to accept selected older image formats."
  <api>
+ | imageVersionWithoutSistaBit |
+ imageVersionWithoutSistaBit := imageVersion bitAnd: ( -1 - MultipleBytecodeSetsBitmask). "Ignore multiple bytecode support identifier"
+ [imageVersionWithoutSistaBit = self imageFormatVersion "Float words in platform-order"
- ^imageVersion = self imageFormatVersion "Float words in platform-order"
    or: [objectMemory hasSpurMemoryManagerAPI not "No compatibility version for Spur as yet"
+ and: [imageVersionWithoutSistaBit = self imageFormatCompatibilityVersion]]] "Float words in BigEndian order"
+ ifTrue: [multipleBytecodeSetsActive := imageVersion bitAnd: MultipleBytecodeSetsBitmask. "Remember the Sista bit"
+ ^ true].
+ ^ false
+ !
- and: [imageVersion = self imageFormatCompatibilityVersion]] "Float words in BigEndian order"!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFileIO (in category 'image save/restore') -----
  writeImageFileIO
  "Write the image header and heap contents to imageFile for snapshot. c.f. writeImageFileIOSimulation.
  The game below is to maintain 64-bit alignment for all putLong:toFile: occurrences."
  <inline: #never>
  | imageName headerStart headerSize f imageBytes bytesWritten sCWIfn okToWrite |
  <var: #f type: #sqImageFile>
  <var: #headerStart type: #squeakFileOffsetType>
  <var: #sCWIfn type: #'void *'>
  <var: #imageName declareC: 'extern char imageName[]'>
 
  self cCode: [] inSmalltalk: [imageName := 'sooth compiler'. ^self writeImageFileIOSimulation].
 
  "If the security plugin can be loaded, use it to check for write permission.
  If not, assume it's ok"
  sCWIfn := self ioLoadFunction: 'secCanWriteImage' From: 'SecurityPlugin'.
  sCWIfn ~= 0 ifTrue:
  [okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.
  okToWrite ifFalse:[^self primitiveFail]].
 
  "local constants"
  headerStart := 0.  
  headerSize := objectMemory wordSize = 4 ifTrue: [64] ifFalse: [128].  "header size in bytes; do not change!!"
 
  f := self sqImageFile: imageName Open: 'wb'.
  f = nil ifTrue: "could not open the image file for writing"
  [^self primitiveFail].
 
  imageBytes := objectMemory imageSizeToWrite.
  headerStart := self sqImage: f File: imageName StartLocation: headerSize + imageBytes.
  self cCode: '/* Note: on Unix systems one could put an exec command here, padded to 512 bytes */'.
  "position file to start of header"
  self sqImageFile: f Seek: headerStart.
+ multipleBytecodeSetsActive
+ ifTrue: [self putWord32: (self imageFormatVersion bitOr: MultipleBytecodeSetsBitmask) toFile: f]
+ ifFalse: [self putWord32: self imageFormatVersion toFile: f].
-
- self putWord32: self imageFormatVersion toFile: f.
  self putWord32: headerSize toFile: f.
  self putLong: imageBytes toFile: f.
  self putLong: objectMemory baseAddressOfImage toFile: f.
  self putLong: objectMemory specialObjectsOop toFile: f.
  self putLong: objectMemory newObjectHash toFile: f.
  self putLong: self getSnapshotScreenSize toFile: f.
  self putLong: self getImageHeaderFlags toFile: f.
  self putWord32: extraVMMemory toFile: f.
  self putShort: desiredNumStackPages toFile: f.
  self putShort: self unknownShortOrCodeSizeInKs toFile: f.
  self putWord32: desiredEdenBytes toFile: f.
  self putShort: (maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]) toFile: f.
  self putShort: the2ndUnknownShort toFile: f.
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [self putLong: objectMemory firstSegmentBytes toFile: f.
  self putLong: objectMemory bytesLeftInOldSpace toFile: f.
  2 timesRepeat: [self putLong: 0 toFile: f] "Pad the rest of the header."]
  ifFalse:
  [4 timesRepeat: [self putLong: 0 toFile: f]].  "Pad the rest of the header."
 
  objectMemory wordSize = 8 ifTrue:
  [3 timesRepeat: [self putLong: 0 toFile: f]]. "Pad the rest of the header."
 
  self assert: headerStart + headerSize = (self sqImageFilePosition: f).
  "position file after the header"
  self sqImageFile: f Seek: headerStart + headerSize.
 
  self successful ifFalse: "file write or seek failure"
  [self sqImageFileClose: f.
  ^nil].
 
  "write the image data"
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [bytesWritten := objectMemory writeImageSegmentsToFile: f]
  ifFalse:
  [bytesWritten := self sq: (self pointerForOop: objectMemory baseAddressOfImage)
  Image: (self sizeof: #char)
  File: imageBytes
  Write: f].
  self success: bytesWritten = imageBytes.
  self sqImageFileClose: f!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker Inbox: VMMaker.oscog-dtl.2910.mcz

David T. Lewis
 
This replaces VMMaker.oscog-dtl.2711 from the VMMaker inbox (9 February 2020),
which I will move to treated.

I merged the original submission, made a few changes, and added one new
primitive based on earlier suggestions on vm-dev.

This provides primitive support to allow the image to inform the VM that it
can change the image format number from 68021 to 68533 after the image has
been recompiled with SistaV1.

It also provides a primitive for querying the VM for supported bytecode
sets, such that this will work:

  Smalltalk supportedEncoders ==> {EncoderForV3 . EncoderForV3PlusClosures . EncoderForSistaV1}

I am attaching a change set that illustrates the use of the two primitives.

Dave


DemonstrateMultipleByteCodePrimitives-dtl.1.cs (1K) Download Attachment