VM Maker: VMMaker-dtl.406.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-dtl.406.mcz

commits-2
 
David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.406.mcz

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

Name: VMMaker-dtl.406
Author: dtl
Time: 30 November 2019, 1:21:00.992 pm
UUID: 050fa60d-0841-4d79-9ccd-80a600f8d2ba
Ancestors: VMMaker-dtl.405

VMMaker 4.16.9

Minor refactorings to prepare for  a primitive to resume from a snapshot object.

Move allocateMemory:heapSize: from ContextInterpreter to ObjectMemory

Move fullScreenFlag up to InterpreterPrimitives

=============== Diff against VMMaker-dtl.405 ===============

Item was changed:
  Interpreter subclass: #ContextInterpreter
+ instanceVariableNames: 'activeContext theHomeContext method receiver instructionPointer stackPointer localIP localSP localHomeContext localReturnContext localReturnValue messageSelector currentBytecode primitiveIndex primitiveFunctionPointer methodCache atCache lkupClass reclaimableContextCount nextPollTick nextWakeupTick lastTick interruptPending savedWindowSize deferDisplayUpdates pendingFinalizationSignals compilerInitialized compilerHooks newNativeMethod methodClass receiverClass interpreterVersion imageFormatVersionNumber interpreterProxy showSurfaceFn interruptCheckCounter interruptCheckCounterFeedBackReset interruptChecksEveryNms externalPrimitiveTable globalSessionID jmpBuf jmpDepth jmpMax suspendedCallbacks suspendedMethods imageFormatInitialVersion allowAccessBeyondSP'
- instanceVariableNames: 'activeContext theHomeContext method receiver instructionPointer stackPointer localIP localSP localHomeContext localReturnContext localReturnValue messageSelector currentBytecode primitiveIndex primitiveFunctionPointer methodCache atCache lkupClass reclaimableContextCount nextPollTick nextWakeupTick lastTick interruptPending savedWindowSize fullScreenFlag deferDisplayUpdates pendingFinalizationSignals compilerInitialized compilerHooks newNativeMethod methodClass receiverClass interpreterVersion imageFormatVersionNumber interpreterProxy showSurfaceFn interruptCheckCounter interruptCheckCounterFeedBackReset interruptChecksEveryNms externalPrimitiveTable globalSessionID jmpBuf jmpDepth jmpMax suspendedCallbacks suspendedMethods imageFormatInitialVersion allowAccessBeyondSP'
  classVariableNames: 'BlockArgumentCountIndex BytecodeTable CacheProbeMax CallerIndex CompilerHooksSize DirBadPath DirEntryFound DirNoMoreEntries DoBalanceChecks HomeIndex InitialIPIndex MaxJumpBuf MessageDictionaryIndex MethodCacheNative TempFrameStart'
  poolDictionaries: 'VMMethodCacheConstants VMSqueakV3BytecodeConstants'
  category: 'VMMaker-Interpreter'!
 
  !ContextInterpreter commentStamp: '<historical>' prior: 0!
  This class is a complete implementation of the Smalltalk-80 virtual machine, derived originally from the Blue Book specification but quite different in some areas.
 
  It has been modernized with 32-bit pointers, better management of Contexts, and attention to variable use that allows the CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer in registers as well as keeping most simple variables in a global array that seems to improve performance for most platforms.
 
  In addition to SmallInteger arithmetic and Floats, it supports logic on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much more effectively than would otherwise be the case.
 
  NOTE:  Here follows a list of things to be borne in mind when working on this code, or when making changes for the future.
 
  1.  There are a number of things that should be done the next time we plan to release a copletely incompatible image format.  These include unifying the instanceSize field of the class format word -- see instantiateClass:indexableSize:, and unifying the bits of the method primitive index (if we decide we need more than 512, after all) -- see primitiveIndexOf:.  Also, contexts should be given a special format code (see next item).
 
  2.  There are several fast checks for contexts (see isContextHeader: and isMethodContextHeader:) which will fail if the compact class indices of BlockContext or MethodContext change.  This is necessary because the oops may change during a compaction when the oops are being adjusted.  It's important to be aware of this when writing a new image using the systemTracer.  A better solution would be to reserve one of the format codes for Contexts only.
 
  3.  We have made normal files tolerant to size and positions up to 32 bits.  This has not been done for async files, since they are still experimental.  The code in size, at: and at:put: should work with sizes and indices up to 31 bits, although I have not tested it (di 12/98); it might or might not work with 32-bit sizes.
 
  4.  Note that 0 is used in a couple of places as an impossible oop.  This should be changed to a constant that really is impossible (or perhaps there is code somewhere that guarantees it --if so it should be put in this comment).  The places include the method cache and the at cache. !

Item was removed:
- ----- Method: ContextInterpreter>>allocateMemory:heapSize: (in category 'snapshot resume') -----
- allocateMemory: dataSize heapSize: desiredHeapSize
- "Allocate memory space sufficient to contain object memory data from an image snapshot."
-
- | unusedHeaderSize minimumMemory memStart heapSize unusedFileReference savedOldMemoryAddress |
- <returnTypeC: 'usqInt'>
- <var: #unusedFileReference type: 'sqImageFile '>
- <var: #desiredHeapSize type: 'usqInt'>
- <var: #dataSize type: 'size_t '>
- <var: #savedOldMemoryAddress type: 'usqInt'>
-
- unusedFileReference := nil. self flag: #FIXME. "remove unused"
- unusedHeaderSize := nil. self flag: #FIXME. "remove unused"
-
- "decrease Squeak object heap to leave extra memory for the VM"
- heapSize := self cCode: 'reserveExtraCHeapBytes(desiredHeapSize, extraVMMemory)'.
-
- "compare memory requirements with availability".
- minimumMemory := dataSize + 100000.  "need at least 100K of breathing room"
- heapSize < minimumMemory ifTrue: [
- self insufficientMemorySpecifiedError].
-
- "allocate a contiguous block of memory for the Squeak heap"
- "below calls a macro that does sqAllocateMemory(minimumMemory, heapSize)"
- "so save prior value of memory so it can be freed at the end of this method, and
- call the below to create new memory here"
- savedOldMemoryAddress := self cCode: 'sqMemoryBase'. self flag: #FIXME. "see package MemoryAccess sqMemoryBaseAddress"
- "allocate new here"
- (objectMemory allocateMemory: heapSize
- minimum: minimumMemory
- imageFile: unusedFileReference
- headerSize: unusedHeaderSize) = nil ifTrue: [self insufficientMemoryAvailableError].
-
- memStart := objectMemory startOfMemory.
- objectMemory setMemoryLimit: (memStart + heapSize) - 24.  "decrease memoryLimit a tad for safety"
- objectMemory setEndOfMemory: memStart + dataSize.
- ^savedOldMemoryAddress.
-  !

Item was removed:
- ----- Method: ContextInterpreter>>getFullScreenFlag (in category 'plugin primitive support') -----
- getFullScreenFlag
- ^fullScreenFlag!

Item was changed:
  ----- Method: ContextInterpreter>>memoryHeaderState: (in category 'primitive support') -----
  memoryHeaderState: dataSize
  "Answer current interpreter and object memory state information."
 
  | splObjsOop oopStart headerSize results hash displayExtent |
 
  "seee ContextInterpreter>>writeImageFileIO:"
 
  "self putLong: (self imageFormatVersion) toFile: f.
  self putLong: headerSize toFile: f.
  self putLong: imageBytes toFile: f.
  self putLong: (objectMemory startOfMemory) toFile: f.
  self putLong: objectMemory getSpecialObjectsOop toFile: f.
  self putLong: objectMemory getLastHash toFile: f.
  self putLong: (self ioScreenSize) toFile: f.
  self putLong: fullScreenFlag toFile: f.
  self putLong: extraVMMemory toFile: f.
  1 to: 7 do: [:i | self putLong: 0 toFile: f]."  "fill remaining header words with zeros"
 
  headerSize := 16 * objectMemory bytesPerWord.  "header size in bytes; do not change!!"
  oopStart := objectMemory startOfMemory.
  splObjsOop := objectMemory getSpecialObjectsOop.
  hash := objectMemory integerObjectOf: objectMemory getLastHash.
  "self ioScreenSize."
  "fullScreenFlag"
  "extraVMMemory"
  "Pad the rest of the header."
  "7 timesRepeat: [self putLong: 0 toFile: file]."
 
  InterpreterProxy pushRemappableOop: (objectMemory
  instantiateClass: (objectMemory classArray)
  indexableSize: 16). "results array"
  displayExtent := self displayExtent: self ioScreenSize. "may trigger GC"
  results := interpreterProxy popRemappableOop.
  objectMemory
  storePointer: 0
  ofObject: results
  withValue: (objectMemory integerObjectOf: self imageFormatVersion).
  objectMemory
  storePointer: 1
  ofObject: results
  withValue: (objectMemory integerObjectOf: headerSize).
  objectMemory
  storePointer: 2
  ofObject: results
  withValue: (self positive64BitIntegerFor: dataSize).
  objectMemory
  storePointer: 3
  ofObject: results
  withValue: (objectMemory integerObjectOf: oopStart).
  objectMemory
  storePointer: 4
  ofObject: results
  withValue: (objectMemory integerObjectOf: splObjsOop).
  objectMemory
  storePointer: 5
  ofObject: results
  withValue: (objectMemory integerObjectOf: hash).
  objectMemory
  storePointer: 6
  ofObject: results
  withValue: displayExtent.
  objectMemory
  storePointer: 7
  ofObject: results
+ withValue: (objectMemory integerObjectOf: fullScreenFlag)..
- withValue: (objectMemory integerObjectOf: 0)..
  objectMemory
  storePointer: 8
  ofObject: results
  withValue: (objectMemory integerObjectOf: extraVMMemory)..
  objectMemory
  storePointer: 9
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 10
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 11
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 12
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 13
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 14
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  objectMemory
  storePointer: 15
  ofObject: results
  withValue: (objectMemory integerObjectOf: 0).
  ^ results.!

Item was changed:
  ----- Method: ContextInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'snapshot resume') -----
  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 |
  <var: #f type: 'sqImageFile '>
  <var: #desiredHeapSize type: 'usqInt'>
  <var: #headerStart type: 'squeakFileOffsetType '>
  <var: #dataSize type: 'size_t '>
  <var: #imageOffset type: 'squeakFileOffsetType '>
 
  swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  headerStart := (self sqImageFilePosition: f) - objectMemory bytesPerWord.  "record header start position"
 
  headerSize := self getLongFromFile: f swap: swapBytes.
  dataSize := self getLongFromFile: f swap: swapBytes.
  oldBaseAddr := self getLongFromFile: f swap: swapBytes.
  objectMemory setSpecialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  objectMemory setLastHash: (self getLongFromFile: f swap: swapBytes).
  savedWindowSize := self getLongFromFile: f swap: swapBytes.
  fullScreenFlag := self oldFormatFullScreenFlag: (self getLongFromFile: f swap: swapBytes).
  extraVMMemory := self getLongFromFile: f swap: swapBytes.
 
  objectMemory getLastHash = 0 ifTrue: [
  "lastHash wasn't stored (e.g. by the cloner); use 999 as the seed"
  objectMemory setLastHash: 999].
 
+ objectMemory allocateMemory: dataSize heapSize: desiredHeapSize.
- self allocateMemory: dataSize heapSize: desiredHeapSize.
  self sqImageFile: f Seek: headerStart + headerSize. "position file after the header"
  self snapshotMemoryRead: f size: dataSize. "read object memory data"
  self swapBytesAndPrepareToInterpret: swapBytes oldBaseAddr: oldBaseAddr.
  ^ dataSize
  !

Item was removed:
- ----- Method: ContextInterpreter>>setFullScreenFlag: (in category 'plugin primitive support') -----
- setFullScreenFlag: value
- fullScreenFlag := value!

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ instanceVariableNames: 'objectMemory primitiveTable primFailCode argumentCount interruptKeycode newMethod preemptionYields fullScreenFlag'
- instanceVariableNames: 'objectMemory primitiveTable primFailCode argumentCount interruptKeycode newMethod preemptionYields'
  classVariableNames: 'CrossedX EndOfRun InterpreterSourceVersion MillisecondClockMask PrimitiveExternalCallIndex PrimitiveTable'
  poolDictionaries: 'VMObjectIndices VMSqueakV3ObjectRepresentationConstants'
  category: 'VMMaker-Interpreter'!
 
  !InterpreterPrimitives commentStamp: 'dtl 4/14/2013 23:16' 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 various interpreters.
 
  Instance Variables
  argumentCount: <Integer>
  messageSelector: <Integer>
  newMethod: <Integer>
  nextProfileTick: <Integer>
  objectMemory: <ObjectMemory> (simulation only)
  preemptionYields: <Boolean>
  primFailCode: <Integer>
  profileMethod: <Integer>
  profileProcess: <Integer>
  profileSemaphore: <Integer>
 
  argumentCount
  - the number of arguments of the current message
 
  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
  - primtiive success/failure flag, 0 for success, otherwise the reason code for failure
 
  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
  !

Item was added:
+ ----- Method: InterpreterPrimitives>>getFullScreenFlag (in category 'plugin primitive support') -----
+ getFullScreenFlag
+ ^fullScreenFlag!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetFullScreen (in category 'I/O primitives') -----
  primitiveSetFullScreen
  "On platforms that support it, set full-screen mode to the value of the boolean argument."
 
  | argOop |
  argOop := self stackTop.
  argOop = objectMemory getTrueObj
+ ifTrue: [self ioSetFullScreen: true.
+ fullScreenFlag := true]
- ifTrue: [self ioSetFullScreen: true]
  ifFalse: [ argOop = objectMemory getFalseObj
+ ifTrue: [self ioSetFullScreen: false.
+ fullScreenFlag := false]
- ifTrue: [self ioSetFullScreen: false]
  ifFalse: [self primitiveFail]].
  self successful ifTrue: [self pop: 1].
  !

Item was added:
+ ----- Method: InterpreterPrimitives>>setFullScreenFlag: (in category 'plugin primitive support') -----
+ setFullScreenFlag: value
+ fullScreenFlag := value!

Item was added:
+ ----- Method: ObjectMemory>>allocateMemory:heapSize: (in category 'image save/restore') -----
+ allocateMemory: dataSize heapSize: desiredHeapSize
+ "Allocate memory space sufficient to contain object memory data from an image snapshot."
+
+ | unusedHeaderSize minimumMemory heapSize unusedFileReference |
+ <returnTypeC: 'usqInt'>
+ <var: #desiredHeapSize type: 'usqInt'>
+ <var: #dataSize type: 'size_t '>
+
+ unusedFileReference := nil. self flag: #FIXME. "remove unused"
+ unusedHeaderSize := nil. self flag: #FIXME. "remove unused"
+
+ "decrease Squeak object heap to leave extra memory for the VM"
+ heapSize := self cCode: 'reserveExtraCHeapBytes(desiredHeapSize, extraVMMemory)'.
+
+ "compare memory requirements with availability".
+ minimumMemory := dataSize + 100000.  "need at least 100K of breathing room"
+ heapSize < minimumMemory ifTrue: [
+ interpreter insufficientMemorySpecifiedError].
+
+ "allocate a contiguous block of memory for the Squeak heap"
+ (self allocateMemory: heapSize
+ minimum: minimumMemory
+ imageFile: unusedFileReference
+ headerSize: unusedHeaderSize) = nil ifTrue: [self insufficientMemoryAvailableError].
+
+ self setMemoryLimit: (memory + heapSize) - 24.  "decrease memoryLimit a tad for safety"
+ self setEndOfMemory: memory + dataSize.
+  !

Item was changed:
  Interpreter subclass: #StackInterpreter
+ instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptPending savedWindowSize imageHeaderFlags deferDisplayUpdates pendingFinalizationSignals interpreterProxy showSurfaceFn externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSign
 alUndelivered tempOop statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite statPendingFinalizationSignals classByteArrayCompactIndex messageSelector profileProcess nextProfileTick profileMethod profileSemaphore'
- instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals interpreterProxy showSurfaceFn externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunni
 ngPrimitiveSignalUndelivered tempOop statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite statPendingFinalizationSignals classByteArrayCompactIndex messageSelector profileProcess nextProfileTick profileMethod profileSemaphore'
  classVariableNames: 'BytecodeTable BytesPerWord COGMTVM COGVM CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives HeaderFlagBitPosition IMMUTABILITY MULTIPLEBYTECODESETS MaxJumpBuf MaxQuickPrimitiveIndex MixinIndex NewspeakVM STACKVM VMBIGENDIAN'
  poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSqueakV3BytecodeConstants VMSqueakV3ObjectRepresentationConstants VMStackFrameOffsets'
  category: 'VMMaker-Interpreter'!
 
  !StackInterpreter commentStamp: '<historical>' prior: 0!
  This class is a complete implementation of the Smalltalk-80 virtual machine, derived originally from the Blue Book specification but quite different in some areas.  This VM supports Closures but *not* old-style BlockContexts.
 
  It has been modernized with 32-bit pointers, better management of Contexts (see next item), and attention to variable use that allows the CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer in registers as well as keeping most simple variables in a global array that seems to improve performance for most platforms.
 
  The VM does not use Contexts directly.  Instead Contexts serve as proxies for a more conventional stack format that is invisible to the image.  There is considerable explanation at http://www.mirandabanda.org/cogblog/2009/01/14/under-cover-contexts-and-the-big-frame-up.  The VM maintains a fixed-size stack zone divided into pages, each page being capable of holding several method/block activations.  A send establishes a new frame in the current stack page, a return returns to the previous frame.  This eliminates allocation/deallocation of contexts and the moving of receiver and arguments from caller to callee on each send/return.  Contexts are created lazily when an activation needs a context (creating a block, explicit use of thisContext, access to sender when sender is a frame, or linking of stack pages together).  Contexts are either conventional and heap-resident ("single") or "married" and serve as proxies for their corresponding frame or "widowed", meaning that their spouse f
 rame has been returned from (died).  A married context is specially marked (more details in the code) and refers to its frame.  Likewise a married frame is specially marked and refers to its context.
 
  In addition to SmallInteger arithmetic and Floats, the VM supports logic on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much more effectively than would otherwise be the case.
 
  NOTE:  Here follows a list of things to be borne in mind when working on this code, or when making changes for the future.
 
  1.  There are a number of things that should be done the next time we plan to release a completely incompatible image format.  These include unifying the instanceSize field of the class format word -- see instantiateClass:indexableSize:, and unifying the bits of the method primitive index (if we decide we need more than 512, after all) -- see primitiveIndexOf:.  Also, contexts should be given a special format code (see next item).
 
  2.  There are several fast checks for contexts (see isContextHeader: and isMethodContextHeader:) which will fail if the compact class indices of BlockContext or MethodContext change.  This is necessary because the oops may change during a compaction when the oops are being adjusted.  It's important to be aware of this when writing a new image using the SystemTracer.  A better solution would be to reserve one of the format codes for Contexts only.
 
  3.  We have made normal files tolerant to size and positions up to 32 bits.  This has not been done for async files, since they are still experimental.  The code in size, at: and at:put: should work with sizes and indices up to 31 bits, although I have not tested it (di 12/98); it might or might not work with 32-bit sizes.
 
  4.  Note that 0 is used in a couple of places as an impossible oop.  This should be changed to a constant that really is impossible (or perhaps there is code somewhere that guarantees it --if so it should be put in this comment).  The places include the method cache and the at cache.
 
  5. Moving to a 2 bit immediate tag and having immediate Characters is a good choice for Unicode and the JIT
 
  6.  If Eliot Miranda's 2 word header scheme is acceptable in terms of footprint (we estimate about a 10% increase in image size with about 35 reclaimed by better representation of CompiledMethod - loss of MethodProperties) then the in-line cache for the JIT is simplified, class access is faster and header access is the same in 32-bit and full 64-bit images.!

Item was removed:
- ----- Method: StackInterpreter>>getFullScreenFlag (in category 'plugin primitive support') -----
- getFullScreenFlag
- ^fullScreenFlag!

Item was removed:
- ----- Method: StackInterpreter>>setFullScreenFlag: (in category 'plugin primitive support') -----
- setFullScreenFlag: value
- fullScreenFlag := value!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
 
  "VMMaker versionString"
 
+ ^'4.16.9'!
- ^'4.16.8'!