Support an updated image format number for Sista

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

Support an updated image format number for Sista

David T. Lewis
Hi Eliot,

This is a belated follow up on earlier private discussion during a Squeak
board meeting a few months ago, in which we agreed that identifying
"Sista in use" in the image format number would be a useful thing to do.
I previously added the documentation for this in ImageFormat-dtl.39.mcz
(as well as the updated ckformat.c program to match).

Attached here is a change set that can be loaded into a VMMaker image to
add VM support for setting and reading the updated image format numbers.
Here I used a primitive to initially set or clear the "sista bit". There
are other ways this could be done, but this at least gets us started
with a working implementation.

By way of explanation, I am copying below both the change set preamble
and the earlier ImageFormat commit notice:

===

  Change Set: VMM-Sista-bit-dtl
  Date: 12 January 2020
  Author: David T. Lewis
 
  Let the image inform the interpreter that alternate bytecodes either are
  or are not in use, and remember that setting when writing or reading the
  image format number in a shapshot file header.
 
  Provide primitiveMultipleBytecodesActive to allow the setting to be updated
  from the image. Expected usage is that the image can call this primitive
  after recompiling with Systa bytecodes, or after reverting back. Note that
  an alternative implemenation would be to use a VM parameter. The primitive
  was chosen here because it can perform parameter checking and does not
  require coordinated update the the VM parameter usage.
 
  Expected usage is that this feature will remain unused for some grace period
  (perhaps a few months) during which an updated VM can be widely circulated.
  After that period, images using Sista bytecodes may be safely saved with the
  updated image format number indicating that multiple bytecodes are in use.
 
  This change set includes helper methods in SmalltalkImage for testing or
  setting the multipleBytecodeSetsActive setting in the VM.
 
  Note the change set postscript which is necessary for initializing a class
  variable prior to code generation.

===

  Name: ImageFormat-dtl.37
  Author: dtl
  Time: 20 July 2019, 5:23:59.004 pm
  UUID: 52b464d5-0bf7-4326-bde3-4f18ad70b239
  Ancestors: ImageFormat-dtl.36
 
  Identify extended bytecodes for Sista in the image format number. Bit 10
  identifies an image that contains extended bytecodes. Thus a 32 bit Spur
  image is 6521, with Sista it is 7033, and a 64 bit Spur image is 68021,
  with Sista it is 68533.
 
  It is expected that additional bytecode sets can be identified by an
  additional field in the image header, probably 32 bits containing two
  16 bit fields,  if both zero then Sista.
 
  Per discussion with Eliot and Bert in a Squeak oversight board meeting
  2019-05-15.


Dave




VMM-Sista-Imageformat-dtl.6.cs (13K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Support an updated image format number for Sista

David T. Lewis
<bump>

Background:

Sista bytecodes have been supported in the VM (opensmalltalk-vm) for quite
some time. Shortly after the Squeak 5.3 release Sista became the default
bytecode set in the trunk image.

In Squeak trunk, Sista bytecodes can be activated (or deactivated) with
CompiledCode class>>useSista: aBoolean, which also calls the hook to inform
the VM of Sista bytecode usage:

        <primitive: 'primitiveMultipleBytecodeSetsActive'>
       
This optional primitive is intended to inform the VM that an alternate
bytecode set is (or is not) being used by the image, and the VM can use
this information to update the image format number (first few bytes of
the saved image file) to a new number that indicates that Sista or other
enhanced bytecode set support is required for that image. A proposed
implementation of the primitive for opensmalltalk-vm is in the VMMaker
inbox (VMMaker.oscog-dtl.2711).

An earlier follow-up discussion in this thread included the suggestion
of e.g.  a #primitiveAvailableBytecodeSets that would provide a list of
available bytecode sets to the image. This is also a good idea, but it is
not directly related to the intended use of #primitiveMultipleBytecodeSetsActive.
Perhaps it could be implemented as a zero-argument call to a single primitive,
such that a boolean argument informs the VM of multiple bytecodes active,
and calling primitiveMultipleBytecodeSetsActive without arguments would ask
the VM to tell the image what bytecode sets can be supported by that VM.

@eliot - are you still on board with this concept, and if so could you
please take a look at the inbox proposal? We discussed this in the last
Squeak board meeting, and the board remains supportive of the idea of
updating the image format number for the next Squeak release.

Thanks,
Dave


On Mon, Jan 13, 2020 at 09:33:34AM -0500, David T. Lewis wrote:

> Hi Eliot,
>
> This is a belated follow up on earlier private discussion during a Squeak
> board meeting a few months ago, in which we agreed that identifying
> "Sista in use" in the image format number would be a useful thing to do.
> I previously added the documentation for this in ImageFormat-dtl.39.mcz
> (as well as the updated ckformat.c program to match).
>
> Attached here is a change set that can be loaded into a VMMaker image to
> add VM support for setting and reading the updated image format numbers.
> Here I used a primitive to initially set or clear the "sista bit". There
> are other ways this could be done, but this at least gets us started
> with a working implementation.
>
> By way of explanation, I am copying below both the change set preamble
> and the earlier ImageFormat commit notice:
>
> ===
>
>   Change Set: VMM-Sista-bit-dtl
>   Date: 12 January 2020
>   Author: David T. Lewis
>  
>   Let the image inform the interpreter that alternate bytecodes either are
>   or are not in use, and remember that setting when writing or reading the
>   image format number in a shapshot file header.
>  
>   Provide primitiveMultipleBytecodesActive to allow the setting to be updated
>   from the image. Expected usage is that the image can call this primitive
>   after recompiling with Systa bytecodes, or after reverting back. Note that
>   an alternative implemenation would be to use a VM parameter. The primitive
>   was chosen here because it can perform parameter checking and does not
>   require coordinated update the the VM parameter usage.
>  
>   Expected usage is that this feature will remain unused for some grace period
>   (perhaps a few months) during which an updated VM can be widely circulated.
>   After that period, images using Sista bytecodes may be safely saved with the
>   updated image format number indicating that multiple bytecodes are in use.
>  
>   This change set includes helper methods in SmalltalkImage for testing or
>   setting the multipleBytecodeSetsActive setting in the VM.
>  
>   Note the change set postscript which is necessary for initializing a class
>   variable prior to code generation.
>
> ===
>
>   Name: ImageFormat-dtl.37
>   Author: dtl
>   Time: 20 July 2019, 5:23:59.004 pm
>   UUID: 52b464d5-0bf7-4326-bde3-4f18ad70b239
>   Ancestors: ImageFormat-dtl.36
>  
>   Identify extended bytecodes for Sista in the image format number. Bit 10
>   identifies an image that contains extended bytecodes. Thus a 32 bit Spur
>   image is 6521, with Sista it is 7033, and a 64 bit Spur image is 68021,
>   with Sista it is 68533.
>  
>   It is expected that additional bytecode sets can be identified by an
>   additional field in the image header, probably 32 bits containing two
>   16 bit fields,  if both zero then Sista.
>  
>   Per discussion with Eliot and Bert in a Squeak oversight board meeting
>   2019-05-15.
>
>
> Dave
>

> 'From Squeak5.3beta of 4 January 2020 [latest update: #19304] on 12 January 2020 at 2:10:55 pm'! "Change Set: VMM-Sista-bit-dtl Date: 12 January 2020 Author: David T. Lewis Let the image inform the interpreter that alternate bytecodes either are or are not in use, and remember that setting when writing or reading the image format number in a shapshot file header. Provide primitiveMultipleBytecodesActive to allow the setting to be updated from the image. Expected usage is that the image can call this primitive after recompiling with Systa bytecodes, or after reverting back. Note that an alternative implemenation would be to use a VM parameter. The primitive was chosen here because it can perform parameter checking and does not require coordinated update the the VM parameter usage. Expected usage is that this feature will remain unused for some grace period (perhaps a few months) during which an updated VM can be widely circulated. After that period, images using Sista bytecodes may be safely saved with the updated image format number indicating that multiple bytecodes are in use. This change set includes helper methods in SmalltalkImage for testing or setting the multipleBytecodeSetsActive setting in the VM. Note the change set postscript which is necessary for initializing a class variable prior to code generation."! VMClass subclass: #InterpreterPrimitives instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn ffiExceptionResponse multipleBytecodeSetsActive' classVariableNames: 'CrossedX EndOfRun MillisecondClockMask' poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets' category: 'VMMaker-Interpreter'! InterpreterPrimitives subclass: #StackInterpreter instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue localAbsentReceiver localAbsentReceiverOrZero extA extB numExtB primitiveFunctionPointer methodCache nsMethodCache atCache lkupClassTag lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority reenterInterpreter nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag sendWheelEvents deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength breakLookupClassTag longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2 metaAccessorDepth theUnknownShort the2ndUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex classByteArrayCompactIndex checkedPluginName nativeSP nativeStackPointer lowcodeCalloutState shadowCallStackPointer displayBits displayWidth displayHeight displayDepth statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents statPendingFinalizationSignals statIdleUsecs debugCallbackPath debugCallbackReturns debugCallbackInvokes primitiveDoMixedArithmetic' classVariableNames: 'AccessModifierPrivate AccessModifierProtected AccessModifierPublic AltBytecodeEncoderClassName AltLongStoreBytecode AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex EnforceAccessControl FailImbalancedPrimitives LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex MultipleBytecodeSetsBitmask PrimNumberDoExternalCall PrimNumberDoPrimitive PrimNumberExternalCall PrimNumberFFICall PrimitiveTable ReturnToInterpreter StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached V3PrimitiveBitsMask' poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMStackFrameOffsets' category: 'VMMaker-Interpreter'! !InterpreterPrimitives methodsFor: 'other primitives' stamp: 'dtl 1/12/2020 13:47'! primitiveMultipleBytecodeSetsActive "Set the value of multipleBytecodeSetsActive based on the boolean argument if supplied. Fail if multiple bytecode sets are not supported. 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]. ! ! !SmalltalkImage methodsFor: 'system attributes' stamp: 'dtl 1/12/2020 11:55'! multipleBytecodeSetsActive "Answer true if the VM is assuming that multiple bytecode sets such as Sista are active in this image." <primitive: 'primitiveMultipleBytecodeSetsActive'>. self primitiveFailed! ! !SmalltalkImage methodsFor: 'system attributes' stamp: 'dtl 1/12/2020 11:52'! multipleBytecodeSetsActive: aBoolean "Inform the VM that an alternate bytecode set such as EncoderForSistaV1 is or is not currently in use by this image. The VM may use this to update the image format number when saving the image." <primitive: 'primitiveMultipleBytecodeSetsActive'>. self primitiveFailed! ! !StackInterpreter methodsFor: 'image save/restore' stamp: 'dtl 1/12/2020 11:19'! 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"   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 ! ! !StackInterpreter methodsFor: 'image save/restore' stamp: 'dtl 1/12/2020 11:18'! 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: 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! ! !StackInterpreter class methodsFor: 'initialization' stamp: 'dtl 1/12/2020 11:19'! 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." "N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h. Hence they should always be initialized.  Because of a hack with callbacks in the non-threaded VM they must not conflct with the VM's tag bits." DisownVMLockOutFullGC := 8. DisownVMForFFICall := 16. DisownVMForThreading := 32. "The Sista bit in the interpreter image format version number" MultipleBytecodeSetsBitmask := 512. ! ! "Postscript: Initialize MultipleByteCodeSets class variable." StackInterpreter initializeMiscConstants.!
>