<div id="__MailbirdStyleContent" style="font-size: 10pt;font-family: Arial;color: #000000">
                                        
                                        
                                            
                                        
                                        
                                        Well, that bit is not a "Sista bit" in the long term. <div><br></div><div>What is now "secondary" could become virtually "primary" when somebody designs SistaV2 etc. So, while you can find out, whether "primary" or "secondary" is used, you cannot find out whether or not SistaV1 is used in some method. Following that bit in a method will only give you a hint on whether to look in the classVar PrimaryBytecodeSetEncoderClass or SecondaryBytecodeSetEncoderClass ... which could be set to anything in the future.<div><br></div><div><span style="font-size: 10pt">Best,</span><br></div><div>Marcel</div><div class="mb_sig"></div>
                                        
                                        </div><blockquote class="history_container" type="cite" style="border-left-style: solid;border-width: 1px;margin-top: 20px;margin-left: 0px;padding-left: 10px;min-width: 500px">
                        <p style="color: #AAAAAA; margin-top: 10px;">Am 19.07.2020 21:56:42 schrieb David T. Lewis <lewis@mail.msen.com>:</p><div style="font-family:Arial,Helvetica,sans-serif"> <br>On Sun, Jul 19, 2020 at 08:50:19PM +0200, Fabio Niephaus wrote:<br>>  <br>> On Sun, 19 Jul 2020 at 7:51 pm, David T. Lewis <lewis@mail.msen.com> wrote:<br>> <br>> ><br>> > I should add that my underlying assumption in proposing the primitive is that<br>> > the VM has no easy or efficient way of knowing whether alternate bytecode sets<br>> > are currently in use, hence the "helper" primitive to permit the image to<br>> > pass a hint to the VM that alternate bytecodes are now active.<br>> ><br>> > But I note that CompiledMethod is in the special object array, so maybe<br>> > there is some way to scan object memory for compiled methods that use<br>> > the alternate bytecode set.<br>> <br>> <br>> IIRC the sign bit of a method header defines whether the primary or<br>> secondary bytecode set is in use. So I believe we can use different sets<br>> per method, not just per image. The sign bit is used to make the check as<br>> cheap as possible.<br>> <br>> Fabio<br>> <br><br>Yes, that's right. For example:<br><br>Spur64BitMemoryManager>>headerIndicatesAlternateBytecodeSet: methodHeader<br>   "A negative header selects the alternate bytecode set."<br>     <api><br>   <inline: true=""><br>     ^methodHeader signedIntFromLong64 <><br><br>So if it is possible to scan object memory for compiled methods that<br>answer true to this test, it would indicate that an alternate bytecode<br>set is currently in use. I'm not sure how to implement that scan, but<br>ideally it would be done prior to image snapshot, and if and only if<br>the "Sista bit" had not previously been set in the image format number.<br><br>Dave<br><br><br>> <br>> ><br>> > Dave<br>> ><br>> > On Sun, Jul 19, 2020 at 12:26:21PM -0400, David T. Lewis wrote:<br>> > > <bump><br>> > ><br>> > > Background:<br>> > ><br>> > > Sista bytecodes have been supported in the VM (opensmalltalk-vm) for<br>> > quite<br>> > > some time. Shortly after the Squeak 5.3 release Sista became the default<br>> > > bytecode set in the trunk image.<br>> > ><br>> > > In Squeak trunk, Sista bytecodes can be activated (or deactivated) with<br>> > > CompiledCode class>>useSista: aBoolean, which also calls the hook to<br>> > inform<br>> > > the VM of Sista bytecode usage:<br>> > ><br>> > >       <primitive: 'primitivemultiplebytecodesetsactive'=""><br>> > ><br>> > > This optional primitive is intended to inform the VM that an alternate<br>> > > bytecode set is (or is not) being used by the image, and the VM can use<br>> > > this information to update the image format number (first few bytes of<br>> > > the saved image file) to a new number that indicates that Sista or other<br>> > > enhanced bytecode set support is required for that image. A proposed<br>> > > implementation of the primitive for opensmalltalk-vm is in the VMMaker<br>> > > inbox (VMMaker.oscog-dtl.2711).<br>> > ><br>> > > An earlier follow-up discussion in this thread included the suggestion<br>> > > of e.g.  a #primitiveAvailableBytecodeSets that would provide a list of<br>> > > available bytecode sets to the image. This is also a good idea, but it is<br>> > > not directly related to the intended use of<br>> > #primitiveMultipleBytecodeSetsActive.<br>> > > Perhaps it could be implemented as a zero-argument call to a single<br>> > primitive,<br>> > > such that a boolean argument informs the VM of multiple bytecodes active,<br>> > > and calling primitiveMultipleBytecodeSetsActive without arguments would<br>> > ask<br>> > > the VM to tell the image what bytecode sets can be supported by that VM.<br>> > ><br>> > > @eliot - are you still on board with this concept, and if so could you<br>> > > please take a look at the inbox proposal? We discussed this in the last<br>> > > Squeak board meeting, and the board remains supportive of the idea of<br>> > > updating the image format number for the next Squeak release.<br>> > ><br>> > > Thanks,<br>> > > Dave<br>> > ><br>> > ><br>> > > On Mon, Jan 13, 2020 at 09:33:34AM -0500, David T. Lewis wrote:<br>> > > > Hi Eliot,<br>> > > ><br>> > > > This is a belated follow up on earlier private discussion during a<br>> > Squeak<br>> > > > board meeting a few months ago, in which we agreed that identifying<br>> > > > "Sista in use" in the image format number would be a useful thing to<br>> > do.<br>> > > > I previously added the documentation for this in ImageFormat-dtl.39.mcz<br>> > > > (as well as the updated ckformat.c program to match).<br>> > > ><br>> > > > Attached here is a change set that can be loaded into a VMMaker image<br>> > to<br>> > > > add VM support for setting and reading the updated image format<br>> > numbers.<br>> > > > Here I used a primitive to initially set or clear the "sista bit".<br>> > There<br>> > > > are other ways this could be done, but this at least gets us started<br>> > > > with a working implementation.<br>> > > ><br>> > > > By way of explanation, I am copying below both the change set preamble<br>> > > > and the earlier ImageFormat commit notice:<br>> > > ><br>> > > > ===<br>> > > ><br>> > > >   Change Set:               VMM-Sista-bit-dtl<br>> > > >   Date:                     12 January 2020<br>> > > >   Author:                   David T. Lewis<br>> > > ><br>> > > >   Let the image inform the interpreter that alternate bytecodes either<br>> > are<br>> > > >   or are not in use, and remember that setting when writing or reading<br>> > the<br>> > > >   image format number in a shapshot file header.<br>> > > ><br>> > > >   Provide primitiveMultipleBytecodesActive to allow the setting to be<br>> > updated<br>> > > >   from the image. Expected usage is that the image can call this<br>> > primitive<br>> > > >   after recompiling with Systa bytecodes, or after reverting back.<br>> > Note that<br>> > > >   an alternative implemenation would be to use a VM parameter. The<br>> > primitive<br>> > > >   was chosen here because it can perform parameter checking and does<br>> > not<br>> > > >   require coordinated update the the VM parameter usage.<br>> > > ><br>> > > >   Expected usage is that this feature will remain unused for some<br>> > grace period<br>> > > >   (perhaps a few months) during which an updated VM can be widely<br>> > circulated.<br>> > > >   After that period, images using Sista bytecodes may be safely saved<br>> > with the<br>> > > >   updated image format number indicating that multiple bytecodes are<br>> > in use.<br>> > > ><br>> > > >   This change set includes helper methods in SmalltalkImage for<br>> > testing or<br>> > > >   setting the multipleBytecodeSetsActive setting in the VM.<br>> > > ><br>> > > >   Note the change set postscript which is necessary for initializing a<br>> > class<br>> > > >   variable prior to code generation.<br>> > > ><br>> > > > ===<br>> > > ><br>> > > >   Name: ImageFormat-dtl.37<br>> > > >   Author: dtl<br>> > > >   Time: 20 July 2019, 5:23:59.004 pm<br>> > > >   UUID: 52b464d5-0bf7-4326-bde3-4f18ad70b239<br>> > > >   Ancestors: ImageFormat-dtl.36<br>> > > ><br>> > > >   Identify extended bytecodes for Sista in the image format number.<br>> > Bit 10<br>> > > >   identifies an image that contains extended bytecodes. Thus a 32 bit<br>> > Spur<br>> > > >   image is 6521, with Sista it is 7033, and a 64 bit Spur image is<br>> > 68021,<br>> > > >   with Sista it is 68533.<br>> > > ><br>> > > >   It is expected that additional bytecode sets can be identified by an<br>> > > >   additional field in the image header, probably 32 bits containing two<br>> > > >   16 bit fields,  if both zero then Sista.<br>> > > ><br>> > > >   Per discussion with Eliot and Bert in a Squeak oversight board<br>> > meeting<br>> > > >   2019-05-15.<br>> > > ><br>> > > ><br>> > > > Dave<br>> > > ><br>> > ><br>> > > > 'From Squeak5.3beta of 4 January 2020 [latest update: #19304] on 12<br>> > January 2020 at 2:10:55 pm'!"Change Set:<br>> > VMM-Sista-bit-dtlDate:                  12 January 2020Author:<br>> >     David T. LewisLet the image inform the interpreter that alternate<br>> > bytecodes either are or are not in use, and remember that setting when<br>> > writing or reading the image format number in a shapshot file<br>> > header.Provide primitiveMultipleBytecodesActive to allow the setting to be<br>> > updated from the image. Expected usage is that the image can call this<br>> > primitive after recompiling with Systa bytecodes, or after reverting back.<br>> > Note that an alternative implemenation would be to use a VM parameter. The<br>> > primitive was chosen here because it can perform parameter checking and<br>> > does not require coordinated update the the VM parameter usage.Expected<br>> > usage is that this feature will remain unused for some grace period<br>> > (perhaps a few months) during which an updated VM can be widely circulated.<br>> > After that period, images using Sista bytecodes may be safely saved with<br>> > the updated image format number indicating that multiple bytecodes are in<br>> > use.This change set includes helper methods in SmalltalkImage for testing<br>> > or setting the multipleBytecodeSetsActive setting in the VM.Note the change<br>> > set postscript which is necessary for initializing a class variable prior<br>> > to code generation."!VMClass subclass: #InterpreterPrimitives<br>> > instanceVariableNames: 'objectMemory messageSelector argumentCount<br>> > newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod<br>> > profileProcess profileSemaphore nextProfileTick preemptionYields<br>> > newFinalization sHEAFn ffiExceptionResponse multipleBytecodeSetsActive'<br>> >  classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'<br>> > poolDictionaries: 'VMBasicConstants VMBytecodeConstants<br>> > VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices<br>> > VMStackFrameOffsets'        category:<br>> > 'VMMaker-Interpreter'!InterpreterPrimitives subclass: #StackInterpreter<br>> >    instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP<br>> > localIP localSP stackLimit stackPage stackPages method instructionPointer<br>> > stackPointer framePointer localReturnValue localAbsentReceiver<br>> > localAbsentReceiverOrZero extA extB numExtB primitiveFunctionPointer<br>> > methodCache nsMethodCache atCache lkupClassTag lkupClass<br>> > methodDictLinearSearchLimit highestRunnableProcessPriority<br>> > reenterInterpreter nextWakeupUsecs nextPollUsecs inIOProcessEvents<br>> > interruptKeycode interruptPending savedWindowSize imageHeaderFlags<br>> > fullScreenFlag sendWheelEvents deferDisplayUpdates<br>> > pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn<br>> > primitiveTable primitiveAccessorDepthTable externalPrimitiveTable<br>> > externalPrimitiveTableFirstFreeIndex overflowedPage<br>> > extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth<br>> > suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages<br>> > desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots<br>> > interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength<br>> > breakLookupClassTag longRunningPrimitiveCheckMethod<br>> > longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs<br>> > longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs<br>> > longRunningPrimitiveCheckSequenceNumber<br>> > longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2<br>> > metaAccessorDepth theUnknownShort the2ndUnknownShort imageFloatsBigEndian<br>> > maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex<br>> > classByteArrayCompactIndex checkedPluginName nativeSP nativeStackPointer<br>> > lowcodeCalloutState shadowCallStackPointer displayBits displayWidth<br>> > displayHeight displayDepth statForceInterruptCheck statStackOverflow<br>> > statStackPageDivorce statCheckForEvents statProcessSwitch<br>> > statIOProcessEvents statPendingFinalizationSignals statIdleUsecs<br>> > debugCallbackPath debugCallbackReturns debugCallbackInvokes<br>> > primitiveDoMixedArithmetic'      classVariableNames: 'AccessModifierPrivate<br>> > AccessModifierProtected AccessModifierPublic AltBytecodeEncoderClassName<br>> > AltLongStoreBytecode AlternateHeaderHasPrimFlag<br>> > AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask<br>> > AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize<br>> > AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable<br>> > CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace<br>> > EnclosingMixinIndex EnclosingObjectIndex EnforceAccessControl<br>> > FailImbalancedPrimitives LongStoreBytecode MaxExternalPrimitiveTableSize<br>> > MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex<br>> > MethodHeaderArgCountShift MethodHeaderFlagBitPosition<br>> > MethodHeaderTempCountShift MixinIndex MultipleBytecodeSetsBitmask<br>> > PrimNumberDoExternalCall PrimNumberDoPrimitive PrimNumberExternalCall<br>> > PrimNumberFFICall PrimitiveTable ReturnToInterpreter<br>> > StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced<br>> > StackPageUnreached V3PrimitiveBitsMask'        poolDictionaries:<br>> > 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants<br>> > VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices<br>> > VMStackFrameOffsets'    category:<br>> > 'VMMaker-Interpreter'!!InterpreterPrimitives methodsFor: 'other primitives'<br>> > stamp: 'dtl 1/12/2020 13:47'!primitiveMultipleBytecodeSetsActive  "Set the<br>> > value of multipleBytecodeSetsActive based on the boolean       argument if<br>> > supplied. Fail if multiple bytecode sets are not supported. Answer the<br>> > current value of multipleBytecodeSetsActive."        <export: true=""><br>> > argumentCount >1 ifTrue:                [^self primitiveFailFor:<br>> > PrimErrBadNumArgs].    argumentCount = 1               ifTrue: [self<br>> > stackTop = objectMemory trueObject                        ifTrue: [self<br>> > cppIf: MULTIPLEBYTECODESETS                               ifTrue:<br>> > [multipleBytecodeSetsActive := true]                            ifFalse:<br>> > [^self primitiveFailFor: PrimErrUnsupported]]                  ifFalse:<br>> > [self stackTop = objectMemory falseObject<br>> > ifTrue: [multipleBytecodeSetsActive := false]<br>> >  ifFalse:[^self primitiveFailFor: PrimErrBadArgument]]].<br>> > multipleBytecodeSetsActive              ifTrue: [self pop: argumentCount +<br>> > 1 thenPush: objectMemory trueObject]         ifFalse: [self pop:<br>> > argumentCount + 1 thenPush: objectMemory falseObject].! !!SmalltalkImage<br>> > methodsFor: 'system attributes' stamp: 'dtl 1/12/2020<br>> > 11:55'!multipleBytecodeSetsActive    "Answer true if the VM is assuming<br>> > that multiple bytecode sets such as  Sista are active in this image."<br>> >   <primitive: 'primitivemultiplebytecodesetsactive'="">.     self<br>> > primitiveFailed! !!SmalltalkImage methodsFor: 'system attributes' stamp:<br>> > 'dtl 1/12/2020 11:52'!multipleBytecodeSetsActive: aBoolean        "Inform<br>> > the VM that an alternate bytecode set such as EncoderForSistaV1 is or is<br>> > not currently in use by this image. The VM may use this to update      the<br>> > image format number when saving the image." <><br>> > 'primitiveMultipleBytecodeSetsActive'>.     self primitiveFailed!<br>> > !!StackInterpreter methodsFor: 'image save/restore' stamp: 'dtl 1/12/2020<br>> > 11:19'!readableFormat: imageVersion     "Anwer true if images of the given<br>> > format are readable by this interpreter.      Allows a virtual machine to<br>> > accept selected older image formats."      <api>   |<br>> > imageVersionWithoutSistaBit | imageVersionWithoutSistaBit := imageVersion<br>> > bitAnd: ( -1 - MultipleBytecodeSetsBitmask). "Ignore multiple bytecode<br>> > support identifier"  [imageVersionWithoutSistaBit = self imageFormatVersion<br>> > "Float words in platform-order"     or: [objectMemory<br>> > hasSpurMemoryManagerAPI not "No compatibility version for Spur as yet"<br>> >                and: [imageVersionWithoutSistaBit = self<br>> > imageFormatCompatibilityVersion]]] "Float words in BigEndian order"<br>> >     ifTrue: [multipleBytecodeSetsActive := imageVersion bitAnd:<br>> > MultipleBytecodeSetsBitmask. "Remember the Sista bit"<br>> >  ^ true].        ^ false! !!StackInterpreter methodsFor: 'image<br>> > save/restore' stamp: 'dtl 1/12/2020 11:18'!writeImageFileIO      "Write the<br>> > image header and heap contents to imageFile for snapshot. c.f.<br>> > writeImageFileIOSimulation.    The game below is to maintain 64-bit<br>> > alignment for all putLong:toFile: occurrences."   <inline: #never="">        |<br>> > imageName headerStart headerSize f imageBytes bytesWritten sCWIfn okToWrite<br>> > | <var: #f="" type:="" #sqimagefile="">    <var: #headerstart=""></var:><br>> > #squeakFileOffsetType> <var: #scwifn="" type:="" #'void="" *'="">  <var:></var:><br>> > declareC: 'extern char imageName[]'>   self cCode: [] inSmalltalk:<br>> > [imageName := 'sooth compiler'. ^self writeImageFileIOSimulation].  "If the<br>> > security plugin can be loaded, use it to check for write permission.     If<br>> > not, assume it's ok"        sCWIfn := self ioLoadFunction:<br>> > 'secCanWriteImage' From: 'SecurityPlugin'.       sCWIfn ~= 0 ifTrue:<br>> >      [okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.<br>> >    okToWrite ifFalse:[^self primitiveFail]].              "local<br>> > constants"       headerStart := 0.       headerSize := objectMemory<br>> > wordSize = 4 ifTrue: [64] ifFalse: [128].  "header size in bytes; do not<br>> > change!!"   f := self sqImageFile: imageName Open: 'wb'.    f = nil ifTrue:<br>> > "could not open the image file for writing"             [^self<br>> > primitiveFail].  imageBytes := objectMemory imageSizeToWrite.<br>> > headerStart := self sqImage: f File: imageName StartLocation: headerSize +<br>> > imageBytes.  self cCode: '/* Note: on Unix systems one could put an exec<br>> > command here, padded to 512 bytes */'.      "position file to start of<br>> > header"      self sqImageFile: f Seek: headerStart.<br>> > multipleBytecodeSetsActive              ifTrue: [self putWord32: (self<br>> > imageFormatVersion bitOr: MultipleBytecodeSetsBitmask) toFile: f]<br>> >       ifFalse: [self putWord32: self imageFormatVersion toFile: f].   self<br>> > putWord32: headerSize toFile: f.   self putLong: imageBytes toFile: f.<br>> >  self putLong: objectMemory baseAddressOfImage toFile: f.        self<br>> > putLong: objectMemory specialObjectsOop toFile: f. self putLong:<br>> > objectMemory newObjectHash toFile: f.     self putLong: self<br>> > getSnapshotScreenSize toFile: f.     self putLong: self getImageHeaderFlags<br>> > toFile: f.       self putWord32: extraVMMemory toFile: f.        self<br>> > putShort: desiredNumStackPages toFile: f.  self putShort: self<br>> > unknownShortOrCodeSizeInKs toFile: f.       self putWord32:<br>> > desiredEdenBytes toFile: f.     self putShort: (maxExtSemTabSizeSet ifTrue:<br>> > [self ioGetMaxExtSemTableSize] ifFalse: [0]) toFile: f.     self putShort:<br>> > the2ndUnknownShort toFile: f.    objectMemory hasSpurMemoryManagerAPI<br>> >       ifTrue:                 [self putLong: objectMemory firstSegmentBytes<br>> > toFile: f.                         self putLong: objectMemory<br>> > bytesLeftInOldSpace toFile: f.                       2 timesRepeat: [self<br>> > putLong: 0 toFile: f]     "Pad the rest of the header."]          ifFalse:<br>> >                       [4 timesRepeat: [self putLong: 0 toFile: f]].  "Pad<br>> > the rest of the header."     objectMemory wordSize = 8 ifTrue:<br>> > [3 timesRepeat: [self putLong: 0 toFile: f]]. "Pad the rest of the<br>> > header."     self assert: headerStart + headerSize = (self<br>> > sqImageFilePosition: f).  "position file after the header"        self<br>> > sqImageFile: f Seek: headerStart + headerSize.     self successful ifFalse:<br>> > "file write or seek failure"           [self sqImageFileClose: f.<br>> >      ^nil]. "write the image data"  objectMemory hasSpurMemoryManagerAPI<br>> >         ifTrue:                 [bytesWritten := objectMemory<br>> > writeImageSegmentsToFile: f]              ifFalse:<br>> > [bytesWritten := self sq: (self pointerForOop: objectMemory<br>> > baseAddressOfImage)<br>> >  Image: (self sizeof: #char)<br>> >              File: imageBytes<br>> >                   Write: f].      self success: bytesWritten = imageBytes.<br>> >       self sqImageFileClose: f! !!StackInterpreter class methodsFor:<br>> > 'initialization' stamp: 'dtl 1/12/2020 11:19'!initializeMiscConstants<br>> > super initializeMiscConstants.  STACKVM := true.        "These flags<br>> > function to identify a GC operation, or     to specify what operations the<br>> > leak checker should be run for."        GCModeFull := 1.<br>> >             "stop-the-world global GC"      GCModeNewSpace := 2.<br>> > "Spur's scavenge, or V3's incremental"  GCModeIncremental := 4.<br>> >  "incremental global gc (Dijkstra tri-colour marking); as yet<br>> > unimplemented"     GCModeBecome := 8.                      "v3 post-become<br>> > sweeping/Spur forwarding"       GCModeImageSegment := 16.       "just a<br>> > flag for leak checking image segments"  GCModeFreeSpace := 32.<br>> > "just a flag for leak checking free space; Spur only"   GCCheckPrimCall :=<br>> > 64.          "just a flag for leak checking external primitive calls"<br>> >   StackPageTraceInvalid := -1.    StackPageUnreached := 0.<br>> > StackPageReachedButUntraced := 1.       StackPageTraced := 2.<br>> >  DumpStackOnLowSpace := 0.       MillisecondClockMask := 16r1FFFFFFF.<br>> > "Note: The external primitive table should actually be dynamically sized<br>> > but for the sake of inferior platforms (e.g., Mac :-) who cannot allocate<br>> > memory in any reasonable way, we keep it static (and cross our<br>> > fingers...)"  MaxExternalPrimitiveTableSize := 4096. "entries"<br>> > MaxJumpBuf := 32. "max. callback depth" FailImbalancedPrimitives :=<br>> > InitializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].<br>> > EnforceAccessControl := InitializationOptions at: #EnforceAccessControl<br>> > ifAbsent: [true].       ReturnToInterpreter := 1. "setjmp/longjmp code."<br>> >     "N.B. some of these DisownFlags are replicated in<br>> > platforms/Cross/vm/sqVirtualMachine.h.         Hence they should always be<br>> > initialized.  Because of a hack with callbacks in the non-threaded  VM they<br>> > must not conflct with the VM's tag bits."      DisownVMLockOutFullGC := 8.<br>> >    DisownVMForFFICall := 16.       DisownVMForThreading := 32.<br>> >  "The Sista bit in the interpreter image format version number"<br>> > MultipleBytecodeSetsBitmask := 512.! !"Postscript:Initialize<br>> > MultipleByteCodeSets class variable."StackInterpreter<br>> > initializeMiscConstants.!<br>> > > ><br>> > ><br>> > ><br>> ><br><br></var:></var:></inline:></api></primitive:></export:></primitive:></bump></inline:></api></lewis@mail.msen.com></div></blockquote></div>