<div dir="ltr"><div>In VMPluginCodeGenerator&gt;&gt;emitCTypesOn: shouldn&#39;t it be<br>    (pluginClass shouldGenerateTypedefFor: structClass)<br>rather than<br>    (vmClass shouldGenerateTypedefFor: structClass) ?<br><br>
</div>I can&#39;t generate IA32ABIPlugin because vmClass isNil, nor ThreadedIA32FFIPlugin since that change<br><br>Nicolas<br></div><div class="gmail_extra"><br><br><div class="gmail_quote">2013/8/21  <span dir="ltr">&lt;<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>&gt;</span><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-eem.330.mcz" target="_blank">http://source.squeak.org/VMMaker/VMMaker.oscog-eem.330.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-eem.330<br>
Author: eem<br>
Time: 21 August 2013, 2:20:31.076 pm<br>
UUID: 836f976a-35fa-404c-aa5a-c4af1c58852f<br>
Ancestors: VMMaker.oscog-eem.329<br>
<br>
Refactor ancilliaryClasses and ancilliaryStructClasses to pass in<br>
options to allow selecting different classes as required.<br>
i.e. collapse ancilliaryClasses and ancilliaryStructClasses onto<br>
ancilliaryClasses: optionsDictionary.  This also requires changing<br>
requiredMethodNames and exportAPISelectors to take options too.<br>
(this is prior to adding a NewspeakCogMethod class for maintaining<br>
a list of anonymous methods).<br>
<br>
Simplify CoInterpreter class&gt;&gt;exportAPISelectors: by marking a few<br>
methods as &lt;api&gt;.<br>
<br>
Eliminate CogStackPage, collapsing it onto InterpreterStackPage<br>
(it only has a class side).<br>
<br>
Use temporaryCountOfMethodHader: instead of tempCountOf: in<br>
SimpleStackBasedCogit&gt;&gt;compileFrameBuild (header is in hand).<br>
<br>
Reimplement CCodeGenerator&gt;&gt;structClassesForTranslationClasses:<br>
to keep the sort stable (ChangeSet superclassOrder: is a stable sort<br>
but structClassesForTranslationClasses: used a set).<br>
<br>
=============== Diff against VMMaker.oscog-eem.329 ===============<br>
<br>
Item was removed:<br>
- ----- Method: BitBltSimulation class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       ^self opTable asSet!<br>
<br>
Item was added:<br>
+ ----- Method: BitBltSimulation class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       ^self opTable asSet!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;addClass: (in category &#39;public&#39;) -----<br>
  addClass: aClass<br>
        &quot;Add the variables and methods of the given class to the code base.&quot;<br>
<br>
        aClass prepareToBeAddedToCodeGenerator: self.<br>
        self checkClassForNameConflicts: aClass.<br>
        self addClassVarsFor: aClass.<br>
        &quot;ikp...&quot;<br>
        self addPoolVarsFor: aClass.<br>
        (aClass inheritsFrom: VMStructType) ifFalse:<br>
                [variables addAll: aClass instVarNames].<br>
+       self retainMethods: (aClass requiredMethodNames: self options).<br>
-       self retainMethods: aClass requiredMethodNames.<br>
<br>
        &#39;Adding Class &#39; , aClass name , &#39;...&#39;<br>
                displayProgressAt: Sensor cursorPoint<br>
                from: 0<br>
                to: aClass selectors size<br>
                during:<br>
                        [:bar |<br>
                         aClass selectors doWithIndex:<br>
                                [:sel :i | | source |<br>
                                bar value: i.<br>
                                self addMethodFor: aClass selector: sel]].<br>
        aClass declareCVarsIn: self!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;addStructClass: (in category &#39;public&#39;) -----<br>
  addStructClass: aClass<br>
        &quot;Add the non-accessor methods of the given struct class to the code base.&quot;<br>
<br>
        aClass prepareToBeAddedToCodeGenerator: self.<br>
        self addClassVarsFor: aClass.<br>
        self addPoolVarsFor: aClass.<br>
+       self retainMethods: (aClass requiredMethodNames: self options).<br>
-       self retainMethods: aClass requiredMethodNames.<br>
<br>
        &#39;Adding Class &#39; , aClass name , &#39;...&#39;<br>
                displayProgressAt: Sensor cursorPoint<br>
                from: 0<br>
                to: aClass selectors size<br>
                during:<br>
                        [:bar |<br>
                         aClass selectors doWithIndex:<br>
                                [:sel :i | | source |<br>
                                bar value: i.<br>
                                self addStructMethodFor: aClass selector: sel]].<br>
        aClass declareCVarsIn: self!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;checkClassForNameConflicts: (in category &#39;error notification&#39;) -----<br>
  checkClassForNameConflicts: aClass<br>
        &quot;Verify that the given class does not have constant, variable, or method names that conflict with<br>
         those of previously added classes. Raise an error if a conflict is found, otherwise just return.&quot;<br>
<br>
        &quot;check for constant name collisions in class pools&quot;<br>
        aClass classPool associationsDo:<br>
                [:assoc |<br>
                (constants includesKey: assoc key asString) ifTrue:<br>
                        [self error: &#39;Constant &#39;, assoc key, &#39; was defined in a previously added class&#39;]].<br>
<br>
        &quot;and in shared pools&quot;<br>
        (aClass sharedPools reject: [:pool| pools includes: pool]) do:<br>
                [:pool |<br>
                pool bindingsDo:<br>
                        [:assoc |<br>
                        (constants includesKey: assoc key asString) ifTrue:<br>
                                [self error: &#39;Constant &#39;, assoc key, &#39; was defined in a previously added class&#39;]]].<br>
<br>
        &quot;check for instance variable name collisions&quot;<br>
        (aClass inheritsFrom: VMStructType) ifFalse:<br>
                [aClass instVarNames do:<br>
                        [:varName |<br>
                        (variables includes: varName) ifTrue:<br>
                                [self error: &#39;Instance variable &#39;, varName, &#39; was defined in a previously added class&#39;]]].<br>
<br>
        &quot;check for method name collisions&quot;<br>
        aClass selectors do:<br>
                [:sel |<br>
                ((methods includesKey: sel)<br>
+               and: [(aClass isStructClass and: [(aClass isAccessor: sel)<br>
+                               and: [(methods at: sel) isStructAccessor]]) not<br>
+               and: [((aClass compiledMethodAt: sel) pragmaAt: #doNotGenerate) isNil]]) ifTrue:<br>
-               and: [((aClass compiledMethodAt: sel) pragmaAt: #doNotGenerate) isNil]) ifTrue:<br>
                        [self error: &#39;Method &#39;, sel, &#39; was defined in a previously added class.&#39;]]!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;emitCAPIExportHeaderOn: (in category &#39;C code generator&#39;) -----<br>
  emitCAPIExportHeaderOn: aStream<br>
        &quot;Store prototype declarations for all non-inlined methods on the given stream.&quot;<br>
        | api methodList |<br>
+       api := (vmClass translationClass exportAPISelectors: self options).<br>
-       api := vmClass translationClass exportAPISelectors.<br>
        methodList := api select: [:s| (methods includesKey: s) or: [(vmClass whichClassIncludesSelector: s) notNil]]<br>
                                          thenCollect:<br>
                                                [:s|<br>
                                                methods<br>
                                                        at: s<br>
                                                        ifAbsent: [self compileToTMethodSelector: s<br>
                                                                                   in: (vmClass whichClassIncludesSelector: s)]].<br>
        methodList := self sortMethods: methodList.<br>
        methodList do:<br>
                [:m|<br>
                m static ifTrue:<br>
                        [logger ensureCr; show: m selector, &#39; excluded from export API because it is static&#39;; cr]].<br>
        self emitCFunctionPrototypes: methodList on: aStream.<br>
        self emitGlobalCVariablesOn: aStream.<br>
        self emitCMacros: methodList on: aStream!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;emitCTypesOn: (in category &#39;C code generator&#39;) -----<br>
  emitCTypesOn: aStream<br>
        &quot;Store local type declarations on the given stream.&quot;<br>
        vmClass ifNotNil:<br>
+               [(self structClassesForTranslationClasses: { vmClass }) do:<br>
-               [vmClass ancilliaryStructClasses do:<br>
                        [:structClass|<br>
                        (structClass isAbstract not<br>
                         and: [vmClass shouldGenerateTypedefFor: structClass]) ifTrue:<br>
                                [structClass printTypedefOn: aStream.<br>
                                 aStream cr; cr]]]!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator&gt;&gt;structClassesForTranslationClasses: (in category &#39;utilities&#39;) -----<br>
  structClassesForTranslationClasses: classes<br>
+       &quot;Answer in superclass order (any superclass precedes any subclass)<br>
+        the ancilliaryClasses that are struct classes for all the given classes.&quot;<br>
-       &quot;Answer in superclass order (any superclass precedes any subclass) the ancilliaryStructClasses for all the given classes.&quot;<br>
        | structClasses |<br>
+       structClasses := OrderedCollection new.<br>
-<br>
-       structClasses := Set new.<br>
        classes do:<br>
                [:aTranslationClass|<br>
+               ([aTranslationClass ancilliaryClasses: self options]<br>
-               structClasses addAll:<br>
-                       ([aTranslationClass ancilliaryStructClasses]<br>
                                on: MessageNotUnderstood<br>
                                do: [:ex|<br>
+                                       ex message selector == #ancilliaryClasses:<br>
-                                       ex message selector == #ancilliaryStructClasses<br>
                                                ifTrue: [#()]<br>
+                                               ifFalse: [ex pass]]) do:<br>
+                       [:class|<br>
+                       (class isStructClass<br>
+                        and: [(structClasses includes: class) not]) ifTrue:<br>
+                               [structClasses addLast: class]]].<br>
+       ^ChangeSet superclassOrder: structClasses!<br>
-                                               ifFalse: [ex pass]])].<br>
-       ^ChangeSet superclassOrder: structClasses asArray!<br>
<br>
Item was removed:<br>
- ----- Method: CoInterpreter class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       &quot;Answer any extra classes to be included in the translation.&quot;<br>
-       ^super ancilliaryClasses<br>
-               copyReplaceAll: { InterpreterStackPages }<br>
-               with: { CoInterpreterStackPages }!<br>
<br>
Item was added:<br>
+ ----- Method: CoInterpreter class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       &quot;Answer any extra classes to be included in the translation.&quot;<br>
+       ^((super ancilliaryClasses: options) copyWithout: InterpreterStackPages),<br>
+          {    CoInterpreterStackPages.<br>
+               CogBlockMethod.<br>
+               CogMethod }!<br>
<br>
Item was removed:<br>
- ----- Method: CoInterpreter class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ CogStackPage.<br>
-               CogBlockMethod.<br>
-               CogMethod }!<br>
<br>
Item was removed:<br>
- ----- Method: CoInterpreter class&gt;&gt;exportAPISelectors (in category &#39;translation&#39;) -----<br>
- exportAPISelectors<br>
-       &quot;Yes this is a mess.  When all exportAPI methods are marked with the &lt;api&gt; pragma<br>
-        this can go away.&quot;<br>
-       | omExports |<br>
-       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)<br>
-                                       inject: Set new into: [:api :c| api addAll: c exportAPISelectors; yourself].<br>
-       ^((self withAllSuperclasses copyUpTo: VMClass),<br>
-               self ancilliaryClasses<br>
-                       inject: omExports<br>
-                       into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself])<br>
-               addAll: #(      classHeader:<br>
-                                       compactClassIndexOf:<br>
-                                       fetchByte:ofObject:<br>
-                                       functionPointerFor:inClass:<br>
-                                       isNonIntegerObject:<br>
-                                       lastPointerOf:<br>
-                                       literal:ofMethod:<br>
-                                       popStack<br>
-                                       primitiveClosureValueNoContextSwitch<br>
-                                       specialSelector:<br>
-                                       stackTop<br>
-                                       tempCountOf:);<br>
-               yourself!<br>
<br>
Item was added:<br>
+ ----- Method: CoInterpreter class&gt;&gt;exportAPISelectors: (in category &#39;translation&#39;) -----<br>
+ exportAPISelectors: options<br>
+       &quot;Yes this is a mess.  When all exportAPI methods are marked with the &lt;api&gt; pragma<br>
+        this can go away.&quot;<br>
+       | omExports |<br>
+       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)<br>
+                                       inject: Set new into: [:api :c| api addAll: (c exportAPISelectors: options); yourself].<br>
+       ^(self withAllSuperclasses copyUpTo: VMClass), (self ancilliaryClasses: options)<br>
+               inject: omExports<br>
+               into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself]!<br>
<br>
Item was changed:<br>
  ----- Method: CoInterpreter class&gt;&gt;shouldGenerateTypedefFor: (in category &#39;translation&#39;) -----<br>
  shouldGenerateTypedefFor: aStructClass<br>
        &quot;Hack to work-around multiple definitions.  Sometimes a type has been defined in an include.&quot;<br>
+       ^({ CogBlockMethod. CogMethod. SistaCogMethod. VMCallbackContext } includes: aStructClass) not!<br>
-       ^({ CogBlockMethod. CogMethod. SistaCogMethod } includes: aStructClass) not!<br>
<br>
Item was changed:<br>
  ----- Method: CoInterpreter&gt;&gt;computeStackZoneSize (in category &#39;initialization&#39;) -----<br>
  computeStackZoneSize<br>
+       ^numStackPages * ((self sizeof: InterpreterStackPage) + self stackPageByteSize)<br>
-       ^numStackPages * ((self sizeof: CogStackPage) + self stackPageByteSize)<br>
         + stackPages extraStackBytes!<br>
<br>
Item was removed:<br>
- ----- Method: CoInterpreterMT class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       ^super ancilliaryClasses, { CogThreadManager }!<br>
<br>
Item was added:<br>
+ ----- Method: CoInterpreterMT class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^(super ancilliaryClasses: options), { CogThreadManager. CogVMThread }!<br>
<br>
Item was removed:<br>
- ----- Method: CoInterpreterMT class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^super ancilliaryStructClasses, { CogVMThread }!<br>
<br>
Item was changed:<br>
  ----- Method: CoInterpreterStackPages&gt;&gt;initializeStack:numSlots:pageSize: (in category &#39;initialization&#39;) -----<br>
  initializeStack: theStackPages numSlots: stackSlots pageSize: slotsPerPage<br>
        &quot;Initialize the stack pages.  In the C VM theStackPages will be alloca&#39;ed memory to hold the<br>
         stack pages on the C stack.  In the simulator they are housed in the memory between the<br>
         cogMethodZone and the heap.&quot;<br>
<br>
        &lt;var: #theStackPages type: #&#39;char *&#39;&gt;<br>
        &lt;returnTypeC: #void&gt;<br>
        | numPages page structStackPageSize pageStructBase count |<br>
        &lt;var: #page type: #&#39;StackPage *&#39;&gt;<br>
        &lt;var: #pageStructBase type: #&#39;char *&#39;&gt;<br>
        self cCode: []<br>
                inSmalltalk:<br>
                        [self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize<br>
                                        = (stackSlots * BytesPerWord)].<br>
+       structStackPageSize := coInterpreter sizeof: InterpreterStackPage.<br>
-       structStackPageSize := coInterpreter sizeof: CogStackPage.<br>
        bytesPerPage := slotsPerPage * BytesPerWord.<br>
        numPages := coInterpreter numStkPages.<br>
<br>
        &quot;Because stack pages grow down baseAddress is at the top of a stack page and so to avoid<br>
         subtracting BytesPerWord from baseAddress and lastAddress in the init loop below we simply<br>
         push the stackPage array up one word to avoid the overlap.  This word is extraStackBytes.&quot;<br>
        pageStructBase := theStackPages + (numPages * bytesPerPage) + BytesPerWord.<br>
        pages := self cCode: [self cCoerceSimple: pageStructBase to: #&#39;StackPage *&#39;]<br>
                                  inSmalltalk:<br>
                                        [pageMap := Dictionary new.<br>
                                         ((0 to: numPages - 1) collect:<br>
                                                [:i|<br>
+                                                InterpreterStackPage surrogateClass new<br>
-                                                CogStackPage surrogateClass new<br>
                                                        address: pageStructBase + (i * structStackPageSize)<br>
                                                        simulator: coInterpreter<br>
                                                        zoneBase: coInterpreter stackZoneBase<br>
                                                        zoneLimit: objectMemory startOfMemory])<br>
                                                do: [:pageSurrogate|<br>
                                                        pageMap at: pageSurrogate address put: pageSurrogate];<br>
                                                yourself].<br>
        &quot;make sure there&#39;s enough headroom&quot;<br>
        self assert: coInterpreter stackPageByteSize - coInterpreter stackLimitBytes - coInterpreter stackLimitOffset<br>
                                &gt;= coInterpreter stackPageHeadroom.<br>
        0 to: numPages - 1 do:<br>
                [:index|<br>
                 page := self stackPageAt: index.<br>
                 page<br>
                        lastAddress: theStackPages + (index * bytesPerPage);<br>
                        baseAddress: page lastAddress + bytesPerPage;<br>
                        stackLimit: page baseAddress - coInterpreter stackLimitBytes;<br>
                        realStackLimit: page stackLimit;<br>
                        baseFP: 0;<br>
                        nextPage: (self stackPageAt: (index = (numPages - 1) ifTrue: [0] ifFalse: [index + 1]));<br>
                        prevPage: (self stackPageAt: (index = 0 ifTrue: [numPages - 1] ifFalse: [index - 1]))].<br>
<br>
        &quot;Now compute stackBasePlus1 so that the pageIndexFor: call maps all addresses from<br>
         aPage baseAddress to aBase limitAddress + 1 to the same index (stacks grow down)&quot;<br>
        stackBasePlus1 := (self cCoerceSimple: theStackPages to: #&#39;char *&#39;) + 1.<br>
        self cCode: []<br>
                inSmalltalk:<br>
                        [minStackAddress := theStackPages.<br>
                         maxStackAddress := theStackPages + (numPages * bytesPerPage) + BytesPerWord - 1].<br>
<br>
        &quot;The overflow limit is the amount of stack to retain when moving frames from an overflowing<br>
         stack to reduce thrashing.  See stackOverflowOrEvent:mayContextSwitch:&quot;<br>
        page := self stackPageAt: 0.<br>
        overflowLimit := page baseAddress - page realStackLimit * 3 // 5.<br>
        0 to: numPages - 1 do:<br>
                [:index|<br>
                 page := self stackPageAt: index.<br>
                 self assert: (self pageIndexFor: page baseAddress) == index.<br>
                 self assert: (self pageIndexFor: page baseAddress - (slotsPerPage - 1 * BytesPerWord)) == index.<br>
                 self assert: (self stackPageFor: page baseAddress) == page.<br>
                 self assert: (self stackPageFor: page stackLimit) == page.<br>
                 self cCode: []<br>
                        inSmalltalk:<br>
                                [| memIndex |<br>
                                 memIndex := index * slotsPerPage + 1. &quot;this is memIndex in the block above&quot;<br>
                                 self assert: (self memIndexFor: (self oopForPointer: page baseAddress))<br>
                                                        == (memIndex + slotsPerPage - 1).<br>
                                 index &lt; (numPages - 1) ifTrue:<br>
                                        [self assert: (self stackPageFor: page baseAddress + BytesPerWord) == (self stackPageAt: index + 1)]].<br>
                self assert: (page trace: -1) ~= 0 &quot;for assert checking of the page tracing flags. -1 == invalid state&quot;].<br>
<br>
        mostRecentlyUsedPage := self stackPageAt: 0.<br>
        page := mostRecentlyUsedPage.<br>
        count := 0.<br>
        [| theIndex |<br>
         count := count + 1.<br>
         theIndex := self pageIndexFor: page baseAddress.<br>
         self assert: (self stackPageAt: theIndex) == page.<br>
         self assert: (self pageIndexFor: page baseAddress) == theIndex.<br>
         self assert: (self pageIndexFor: page stackLimit) == theIndex.<br>
         self assert: (self pageIndexFor: page lastAddress + 1) == theIndex.<br>
         (page := page nextPage) ~= mostRecentlyUsedPage] whileTrue.<br>
        self assert: count == numPages.<br>
        self assert: self pageListIsWellFormed!<br>
<br>
Item was removed:<br>
- ----- Method: CogAbstractInstruction class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       ^self selectors reject:<br>
-               [:s|<br>
-               (self isAccessor: s)<br>
-               or: [((self compiledMethodAt: s) pragmaAt: #doNotGenerate) notNil]]!<br>
<br>
Item was added:<br>
+ ----- Method: CogAbstractInstruction class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       ^self selectors reject:<br>
+               [:s|<br>
+               (self isAccessor: s)<br>
+               or: [((self compiledMethodAt: s) pragmaAt: #doNotGenerate) notNil]]!<br>
<br>
Item was removed:<br>
- InterpreterStackPage subclass: #CogStackPage<br>
-       instanceVariableNames: &#39;&#39;<br>
-       classVariableNames: &#39;&#39;<br>
-       poolDictionaries: &#39;&#39;<br>
-       category: &#39;VMMaker-JIT&#39;!<br>
<br>
Item was removed:<br>
- ----- Method: CogStackPage class&gt;&gt;alignedByteSize (in category &#39;translation&#39;) -----<br>
- alignedByteSize<br>
-       ^self surrogateClass alignedByteSize!<br>
<br>
Item was removed:<br>
- ----- Method: CogStackPage class&gt;&gt;alignedByteSizeOf:forClient: (in category &#39;translation&#39;) -----<br>
- alignedByteSizeOf: anObject forClient: aVMClass<br>
-       ^self surrogateClass alignedByteSize!<br>
<br>
Item was removed:<br>
- ----- Method: CogStackPage class&gt;&gt;surrogateClass (in category &#39;simulation only&#39;) -----<br>
- surrogateClass<br>
-       ^BytesPerWord = 4<br>
-               ifTrue: [CogStackPageSurrogate32]<br>
-               ifFalse: [CogStackPageSurrogate64]!<br>
<br>
Item was removed:<br>
- ----- Method: Cogit class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       ^super ancilliaryClasses,<br>
-         { CogMethodZone }!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ProcessorClass ifNil: [thisContext methodClass theNonMetaClass initialize].<br>
+       ^{      CogMethodZone.<br>
+               CogAbstractInstruction.<br>
+               ProcessorClass basicNew abstractInstructionCompilerClass.<br>
+               CogBlockStart.<br>
+               CogBytecodeDescriptor.<br>
+               CogBytecodeFixup.<br>
+               CogInstructionAnnotation.<br>
+               CogPrimitiveDescriptor.<br>
+               CogBlockMethod.<br>
+               CogMethod<br>
+         }!<br>
<br>
Item was removed:<br>
- ----- Method: Cogit class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ProcessorClass ifNil: [thisContext methodClass theNonMetaClass initialize].<br>
-       ^{      CogAbstractInstruction.<br>
-               ProcessorClass basicNew abstractInstructionCompilerClass.<br>
-               CogBlockStart.<br>
-               CogBytecodeDescriptor.<br>
-               CogBytecodeFixup.<br>
-               CogInstructionAnnotation.<br>
-               CogPrimitiveDescriptor.<br>
-               CogBlockMethod.<br>
-               CogMethod       }!<br>
<br>
Item was removed:<br>
- ----- Method: Cogit class&gt;&gt;exportAPISelectors (in category &#39;translation&#39;) -----<br>
- exportAPISelectors<br>
-       ^((self withAllSuperclasses copyUpThrough: Cogit), self ancilliaryClasses collect:<br>
-               [:c| self exportAPISelectorsFor: c]) fold: [:a :b| a, b]!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit class&gt;&gt;exportAPISelectors: (in category &#39;translation&#39;) -----<br>
+ exportAPISelectors: options<br>
+       ^((self withAllSuperclasses copyUpThrough: Cogit), (self ancilliaryClasses: options) collect:<br>
+               [:c| self exportAPISelectorsFor: c]) fold: [:a :b| a, b]!<br>
<br>
Item was changed:<br>
  ----- Method: Cogit class&gt;&gt;preGenerationHook: (in category &#39;translation&#39;) -----<br>
  preGenerationHook: aCCodeGenerator<br>
        &quot;Perform any last-minute changes to the code generator immediately<br>
         before it performs code analysis and generation.  In this case, make<br>
         all non-exported methods private.&quot;<br>
        | exportAPISelectors |<br>
+       exportAPISelectors := self exportAPISelectors: aCCodeGenerator options.<br>
-       exportAPISelectors := self exportAPISelectors.<br>
        aCCodeGenerator selectorsAndMethodsDo:<br>
                [:s :m|<br>
                (exportAPISelectors includes: s)<br>
                        ifTrue: [m static: false]<br>
                        ifFalse:<br>
                                [m export ifFalse:<br>
                                        [m static: true]]]!<br>
<br>
Item was removed:<br>
- ----- Method: Cogit class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;self requiredMethodNames&quot;<br>
-       ^self exportAPISelectors<br>
-               addAll: self tableFunctions;<br>
-               yourself!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;self requiredMethodNames&quot;<br>
+       ^(self exportAPISelectors: options)<br>
+               addAll: self tableFunctions;<br>
+               yourself!<br>
<br>
Item was added:<br>
+ ----- Method: IA32ABIPlugin class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^{ VMCallbackContext. VMCallbackReturnValue }!<br>
<br>
Item was removed:<br>
- ----- Method: IA32ABIPlugin class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ VMCallbackContext. VMCallbackReturnValue }!<br>
<br>
Item was changed:<br>
  ----- Method: Interpreter class&gt;&gt;preGenerationHook: (in category &#39;translation&#39;) -----<br>
  preGenerationHook: aCCodeGenerator<br>
        &quot;Perform any last-minute changes to the code generator immediately<br>
         before it performs code analysis and generation.  In this case, make<br>
         all non-exported methods private.&quot;<br>
        | requiredMethodNames |<br>
+       requiredMethodNames := self requiredMethodNames: aCCodeGenerator options.<br>
-       requiredMethodNames := self requiredMethodNames.<br>
        aCCodeGenerator selectorsAndMethodsDo:<br>
                [:s :m|<br>
                (m export or: [requiredMethodNames includes: s]) ifTrue:<br>
                        [m static: false]]!<br>
<br>
Item was removed:<br>
- ----- Method: Interpreter class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
-       | requiredList |<br>
-       requiredList := Set new: 400.<br>
-       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
-       requiredList addAll: #(fullDisplayUpdate interpret printCallStack printAllStacks printOop: readImageFromFile:HeapSize:StartingAt: success: readableFormat: getCurrentBytecode characterForAscii: findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver: loadInitialContext nullCompilerHook primitiveFlushExternalPrimitives setCompilerInitialized: getFullScreenFlag getInterruptCheckCounter getInterruptKeycode getInterruptPending getNextWakeupTick getSavedWindowSize setFullScreenFlag: setInterruptCheckCounter: setInterruptKeycode: setInterruptPending: setNextWakeupTick: setSavedWindowSize: forceInterruptCheck getThisSessionID).<br>

-<br>
-       &quot;Nice to actually have all the primitives available&quot;<br>
-       requiredList addAll: self primitiveTable.<br>
-<br>
-       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
-       InterpreterProxy organization categories do: [:cat |<br>
-               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue: [<br>
-                       requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
-<br>
-       ^requiredList!<br>
<br>
Item was added:<br>
+ ----- Method: Interpreter class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
+       | requiredList |<br>
+       requiredList := Set new: 400.<br>
+       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
+       requiredList addAll: #(fullDisplayUpdate interpret printCallStack printAllStacks printOop: readImageFromFile:HeapSize:StartingAt: success: readableFormat: getCurrentBytecode characterForAscii: findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver: loadInitialContext nullCompilerHook primitiveFlushExternalPrimitives setCompilerInitialized: getFullScreenFlag getInterruptCheckCounter getInterruptKeycode getInterruptPending getNextWakeupTick getSavedWindowSize setFullScreenFlag: setInterruptCheckCounter: setInterruptKeycode: setInterruptPending: setNextWakeupTick: setSavedWindowSize: forceInterruptCheck getThisSessionID).<br>

+<br>
+       &quot;Nice to actually have all the primitives available&quot;<br>
+       requiredList addAll: self primitiveTable.<br>
+<br>
+       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
+       InterpreterProxy organization categories do: [:cat |<br>
+               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue: [<br>
+                       requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
+<br>
+       ^requiredList!<br>
<br>
Item was changed:<br>
  ----- Method: InterpreterPrimitives&gt;&gt;primitiveClosureValueNoContextSwitch (in category &#39;control primitives&#39;) -----<br>
  primitiveClosureValueNoContextSwitch<br>
        &quot;An exact clone of primitiveClosureValue except that this version will not<br>
         check for interrupts on stack overflow.  It may invoke the garbage collector<br>
         but will not switch processes.  See checkForInterruptsMayContextSwitch:&quot;<br>
+       &lt;api&gt;<br>
        | blockClosure numArgs closureMethod outerContext |<br>
        blockClosure := self stackValue: argumentCount.<br>
        numArgs := self argumentCountOfClosure: blockClosure.<br>
        argumentCount = numArgs ifFalse:<br>
                [^self primitiveFail].<br>
<br>
        &quot;Somewhat paranoiac checks we need while debugging that we may be able to discard<br>
         in a robust system.&quot;<br>
        outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.<br>
        (objectMemory isContext: outerContext) ifFalse:<br>
                [^self primitiveFail].<br>
        closureMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.<br>
        &quot;Check if the closure&#39;s method is actually a CompiledMethod.&quot;<br>
        (objectMemory isOopCompiledMethod: closureMethod) ifFalse:<br>
                [^self primitiveFail].<br>
<br>
        &quot;Note we use activateNewMethod, not executeNewMethod, to avoid<br>
         quickCheckForInterrupts.  Don&#39;t check until we have a full activation.&quot;<br>
        self activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: false!<br>
<br>
Item was changed:<br>
+ ----- Method: InterpreterStackPage class&gt;&gt;alignedByteSize (in category &#39;translation&#39;) -----<br>
- ----- Method: InterpreterStackPage class&gt;&gt;alignedByteSize (in category &#39;accessing&#39;) -----<br>
  alignedByteSize<br>
+       ^self surrogateClass alignedByteSize!<br>
-       &quot;Simulation only.  In the simulation stack pages are purely Smalltalk objects<br>
-        and don&#39;t exist in memory.&quot;<br>
-       ^0!<br>
<br>
Item was changed:<br>
  ----- Method: InterpreterStackPage class&gt;&gt;alignedByteSizeOf:forClient: (in category &#39;translation&#39;) -----<br>
  alignedByteSizeOf: anObject forClient: aVMClass<br>
+       ^self surrogateClass alignedByteSize!<br>
-       ^self alignedByteSize!<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterStackPage class&gt;&gt;surrogateClass (in category &#39;simulation only&#39;) -----<br>
+ surrogateClass<br>
+       ^BytesPerWord = 4<br>
+               ifTrue: [CogStackPageSurrogate32]<br>
+               ifFalse: [CogStackPageSurrogate64]!<br>
<br>
Item was changed:<br>
  ----- Method: NewObjectMemory&gt;&gt;lastPointerOf: (in category &#39;object enumeration&#39;) -----<br>
  lastPointerOf: oop<br>
        &quot;Return the byte offset of the last pointer field of the given object.<br>
         Can be used even when the type bits are not correct.<br>
         Works with CompiledMethods, as well as ordinary objects.&quot;<br>
+       &lt;api&gt;<br>
-       | fmt header contextSize numLiterals |<br>
        &lt;inline: true&gt;<br>
        &lt;asmLabel: false&gt;<br>
+       | fmt header contextSize numLiterals |<br>
        header := self baseHeader: oop.<br>
        fmt := self formatOfHeader: header.<br>
        fmt &lt;= 4 ifTrue:<br>
                [(fmt = 3<br>
                  and: [self isContextHeader: header]) ifTrue:<br>
                        [&quot;contexts end at the stack pointer&quot;<br>
                        contextSize := coInterpreter fetchStackPointerOf: oop.<br>
                        ^CtxtTempFrameStart + contextSize * BytesPerOop].<br>
                ^(self sizeBitsOfSafe: oop) - BaseHeaderSize  &quot;all pointers&quot;].<br>
        fmt &lt; 12 ifTrue: [^0]. &quot;no pointers&quot;<br>
<br>
        &quot;CompiledMethod: contains both pointers and bytes&quot;<br>
        numLiterals := coInterpreter literalCountOf: oop.<br>
        ^numLiterals + LiteralStart * BytesPerOop!<br>
<br>
Item was added:<br>
+ ----- Method: NewspeakInterpreter class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^{ VMCallbackContext }!<br>
<br>
Item was removed:<br>
- ----- Method: NewspeakInterpreter class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ VMCallbackContext }!<br>
<br>
Item was changed:<br>
  ----- Method: NewspeakInterpreter class&gt;&gt;preGenerationHook: (in category &#39;translation&#39;) -----<br>
  preGenerationHook: aCCodeGenerator<br>
        &quot;Perform any last-minute changes to the code generator immediately<br>
         before it performs code analysis and generation.  In this case, make<br>
         all non-exported methods private.&quot;<br>
        | publicMethodNames |<br>
+       publicMethodNames := (self requiredMethodNames: aCCodeGenerator options)<br>
-       publicMethodNames := self requiredMethodNames<br>
                                                                copyWithoutAll: (self primitiveTable<br>
                                                                                                                copyWithout: #primitiveFail).<br>
        aCCodeGenerator selectorsAndMethodsDo:<br>
                [:s :m|<br>
                (m export or: [publicMethodNames includes: s]) ifTrue:<br>
                        [m static: false]]!<br>
<br>
Item was removed:<br>
- ----- Method: NewspeakInterpreter class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
-       | requiredList |<br>
-       requiredList := self exportAPISelectors..<br>
-       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
-       requiredList addAll: #(fullDisplayUpdate interpret printCallStack printAllStacks printOop: readImageFromFile:HeapSize:StartingAt: success: readableFormat: getCurrentBytecode characterForAscii: findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver: loadInitialContext primitiveFlushExternalPrimitives getFullScreenFlag getInterruptCheckCounter getInterruptKeycode getInterruptPending getNextWakeupTick getSavedWindowSize setFullScreenFlag: setInterruptCheckCounter: setInterruptKeycode: setInterruptPending: setNextWakeupTick: setSavedWindowSize: forceInterruptCheck getThisSessionID getDeferDisplayUpdates validInstructionPointer:inMethod:).<br>

-<br>
-       &quot;Nice to actually have all the primitives available&quot;<br>
-       requiredList addAll: self primitiveTable.<br>
-<br>
-       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
-       InterpreterProxy organization categories do: [:cat |<br>
-               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue: [<br>
-                       requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
-<br>
-       ^requiredList!<br>
<br>
Item was added:<br>
+ ----- Method: NewspeakInterpreter class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
+       | requiredList |<br>
+       requiredList := self exportAPISelectors: options.<br>
+       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
+       requiredList addAll: #(fullDisplayUpdate interpret printCallStack printAllStacks printOop: readImageFromFile:HeapSize:StartingAt: success: readableFormat: getCurrentBytecode characterForAscii: findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver: loadInitialContext primitiveFlushExternalPrimitives getFullScreenFlag getInterruptCheckCounter getInterruptKeycode getInterruptPending getNextWakeupTick getSavedWindowSize setFullScreenFlag: setInterruptCheckCounter: setInterruptKeycode: setInterruptPending: setNextWakeupTick: setSavedWindowSize: forceInterruptCheck getThisSessionID getDeferDisplayUpdates validInstructionPointer:inMethod:).<br>

+<br>
+       &quot;Nice to actually have all the primitives available&quot;<br>
+       requiredList addAll: self primitiveTable.<br>
+<br>
+       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
+       InterpreterProxy organization categories do: [:cat |<br>
+               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue: [<br>
+                       requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
+<br>
+       ^requiredList!<br>
<br>
Item was added:<br>
+ ----- Method: NewsqueakIA32ABIPlugin class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^{ VMCallbackContext. VMCallbackReturnValue }!<br>
<br>
Item was removed:<br>
- ----- Method: NewsqueakIA32ABIPlugin class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ VMCallbackContext. VMCallbackReturnValue }!<br>
<br>
Item was removed:<br>
- ----- Method: ObjectMemory class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
-       ^self exportAPISelectors!<br>
<br>
Item was added:<br>
+ ----- Method: ObjectMemory class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
+       ^self exportAPISelectors: options!<br>
<br>
Item was changed:<br>
  ----- Method: ObjectMemory&gt;&gt;classHeader: (in category &#39;header access&#39;) -----<br>
  classHeader: oop<br>
+       &lt;api&gt;<br>
+       ^self longAt: oop - BaseHeaderSize!<br>
-<br>
-       ^ self longAt: oop - BaseHeaderSize!<br>
<br>
Item was changed:<br>
  ----- Method: ObjectMemory&gt;&gt;compactClassIndexOf: (in category &#39;header access&#39;) -----<br>
  compactClassIndexOf: oop<br>
+       &lt;api&gt;<br>
        &lt;inline: true&gt;<br>
        ^((self baseHeader: oop) &gt;&gt; 12) bitAnd: 16r1F!<br>
<br>
Item was changed:<br>
  ----- Method: ObjectMemory&gt;&gt;fetchByte:ofObject: (in category &#39;interpreter access&#39;) -----<br>
  fetchByte: byteIndex ofObject: oop<br>
+       &lt;api&gt;<br>
+       ^self byteAt: oop + BaseHeaderSize + byteIndex!<br>
-<br>
-       ^ self byteAt: oop + BaseHeaderSize + byteIndex!<br>
<br>
Item was changed:<br>
  ----- Method: ObjectMemory&gt;&gt;isNonIntegerObject: (in category &#39;interpreter access&#39;) -----<br>
  isNonIntegerObject: objectPointer<br>
+       &lt;api&gt;<br>
+       ^(objectPointer bitAnd: 1) = 0!<br>
-<br>
-       ^ (objectPointer bitAnd: 1) = 0!<br>
<br>
Item was changed:<br>
  ----- Method: ObjectMemory&gt;&gt;lastPointerOf: (in category &#39;object enumeration&#39;) -----<br>
  lastPointerOf: oop<br>
        &quot;Return the byte offset of the last pointer field of the given object.<br>
        Works with CompiledMethods, as well as ordinary objects.<br>
        Can be used even when the type bits are not correct.&quot;<br>
+       &lt;api&gt;<br>
-       | fmt sz methodHeader header contextSize |<br>
        &lt;inline: true&gt;<br>
        &lt;asmLabel: false&gt;<br>
+       | fmt sz methodHeader header contextSize |<br>
        header := self baseHeader: oop.<br>
        fmt := self formatOfHeader: header.<br>
        fmt &lt;= 4 ifTrue: [(fmt = 3 and: [self isContextHeader: header])<br>
                                        ifTrue: [&quot;contexts end at the stack pointer&quot;<br>
                                                contextSize := self fetchStackPointerOf: oop.<br>
                                                ^ CtxtTempFrameStart + contextSize * BytesPerWord].<br>
                                sz := self sizeBitsOfSafe: oop.<br>
                                ^ sz - BaseHeaderSize  &quot;all pointers&quot;].<br>
        fmt &lt; 12 ifTrue: [^ 0]. &quot;no pointers&quot;<br>
<br>
        &quot;CompiledMethod: contains both pointers and bytes:&quot;<br>
        methodHeader := self longAt: oop + BaseHeaderSize.<br>
        ^ (methodHeader &gt;&gt; 10 bitAnd: 255) + LiteralStart * BytesPerWord!<br>
<br>
Item was removed:<br>
- ----- Method: SimpleStackBasedCogit class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       ^super ancilliaryClasses, { CogObjectRepresentationForSqueakV3 }!<br>
<br>
Item was added:<br>
+ ----- Method: SimpleStackBasedCogit class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       &quot;hard-wired for now&quot;<br>
+       ^(super ancilliaryClasses: options), { CogObjectRepresentationForSqueakV3 }!<br>
<br>
Item was changed:<br>
  ----- Method: SimpleStackBasedCogit&gt;&gt;compileFrameBuild (in category &#39;compile abstract instructions&#39;) -----<br>
  compileFrameBuild<br>
        &quot;Build a frame for a CogMethod activation.  See CoInterpreter class&gt;&gt;initializeFrameIndices.<br>
                        receiver (in ReceiverResultReg)<br>
                        arg0<br>
                        ...<br>
                        argN<br>
                        caller&#39;s saved ip/this stackPage (for a base frame)<br>
        fp-&gt;    saved fp<br>
                        method<br>
                        context (uninitialized?)<br>
                        receiver<br>
                        first temp<br>
                        ...<br>
        sp-&gt;    Nth temp<br>
        If there is a primitive and an error code the Nth temp is the error code.<br>
        Ensure SendNumArgsReg is set early on (incidentally to nilObj) because<br>
        it is the flag determining whether context switch is allowed on stack-overflow.&quot;<br>
        | methodHeader jumpSkip |<br>
        &lt;inline: false&gt;<br>
        &lt;var: #jumpSkip type: #&#39;AbstractInstruction *&#39;&gt;<br>
        needsFrame ifFalse: [^0].<br>
        methodHeader := coInterpreter headerOf: methodObj.<br>
        backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].<br>
        self PushR: FPReg.<br>
        self MoveR: SPReg R: FPReg.<br>
        methodLabel addDependent: (self annotateAbsolutePCRef:<br>
                (self PushCw: methodLabel asInteger)). &quot;method&quot;<br>
        self annotate: (self MoveCw: objectMemory nilObject R: SendNumArgsReg)<br>
                objRef: objectMemory nilObject.<br>
        self PushR: SendNumArgsReg. &quot;context&quot;<br>
        self PushR: ReceiverResultReg.<br>
+       methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:<br>
-       methodOrBlockNumArgs + 1 to: (coInterpreter tempCountOf: methodObj) do:<br>
                [:i|<br>
                self PushR: SendNumArgsReg].<br>
        (primitiveIndex &gt; 0<br>
         and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)<br>
                        = (objectMemory<br>
                                fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)<br>
                                ofObject: methodObj)]) ifTrue:<br>
                [self compileGetErrorCode.<br>
                 initialPC := initialPC<br>
                                   + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)<br>
                                   + (coInterpreter sizeOfLongStoreTempBytecode: methodHeader)].<br>
        self MoveAw: coInterpreter stackLimitAddress R: TempReg.<br>
        self CmpR: TempReg R: SPReg. &quot;N.B. FLAGS := SPReg - TempReg&quot;<br>
        &quot;If we can&#39;t context switch for this method, use a slightly<br>
         slower overflow check that clears SendNumArgsReg.&quot;<br>
        (coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)<br>
                ifTrue:<br>
                        [self JumpBelow: stackOverflowCall.<br>
                         stackCheckLabel := self Label]<br>
                ifFalse:<br>
                        [jumpSkip := self JumpAboveOrEqual: 0.<br>
                         self MoveCq: 0 R: SendNumArgsReg.<br>
                         self Jump: stackOverflowCall.<br>
                         jumpSkip jmpTarget: (stackCheckLabel := self Label)].<br>
        self annotateBytecode: stackCheckLabel!<br>
<br>
Item was added:<br>
+ ----- Method: SistaStackToRegisterMappingCogit class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^(super ancilliaryClasses: options) copyWith: SistaCogMethod!<br>
<br>
Item was removed:<br>
- ----- Method: SistaStackToRegisterMappingCogit class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       &quot;self ancilliaryStructClasses&quot;<br>
-       ^super ancilliaryStructClasses copyWith: SistaCogMethod!<br>
<br>
Item was removed:<br>
- ----- Method: StackInterpreter class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       &quot;Answer any extra classes to be included in the translation.&quot;<br>
-       ^{ self objectMemoryClass. InterpreterStackPages }!<br>
<br>
Item was added:<br>
+ ----- Method: StackInterpreter class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       &quot;Answer any extra classes to be included in the translation.&quot;<br>
+       ^{      self objectMemoryClass.<br>
+               VMCallbackContext.<br>
+               InterpreterStackPages.<br>
+               InterpreterStackPage }!<br>
<br>
Item was removed:<br>
- ----- Method: StackInterpreter class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ InterpreterStackPage. VMCallbackContext }!<br>
<br>
Item was removed:<br>
- ----- Method: StackInterpreter class&gt;&gt;exportAPISelectors (in category &#39;translation&#39;) -----<br>
- exportAPISelectors<br>
-       | omExports |<br>
-       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)<br>
-                                       inject: Set new<br>
-                                       into: [:api :c| api addAll: c exportAPISelectors; yourself].<br>
-       ^(self withAllSuperclasses copyUpTo: VMClass), self ancilliaryClasses<br>
-               inject: omExports<br>
-               into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself]!<br>
<br>
Item was added:<br>
+ ----- Method: StackInterpreter class&gt;&gt;exportAPISelectors: (in category &#39;translation&#39;) -----<br>
+ exportAPISelectors: options<br>
+       | omExports |<br>
+       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)<br>
+                                       inject: Set new<br>
+                                       into: [:api :c| api addAll: (c exportAPISelectors: options); yourself].<br>
+       ^(self withAllSuperclasses copyUpTo: VMClass), (self ancilliaryClasses: options)<br>
+               inject: omExports<br>
+               into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself]!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter class&gt;&gt;preGenerationHook: (in category &#39;translation&#39;) -----<br>
  preGenerationHook: aCCodeGenerator<br>
        &quot;Perform any last-minute changes to the code generator immediately<br>
         before it performs code analysis and generation.  In this case, make<br>
         all non-exported methods private.&quot;<br>
        | publicMethodNames |<br>
+       publicMethodNames := (self requiredMethodNames: aCCodeGenerator options)<br>
-       publicMethodNames := self requiredMethodNames<br>
                                                                copyWithoutAll: (self primitiveTable<br>
                                                                                                                copyWithout: #primitiveFail).<br>
        aCCodeGenerator selectorsAndMethodsDo:<br>
                [:s :m|<br>
                (m export or: [publicMethodNames includes: s]) ifTrue:<br>
                        [m static: false]]!<br>
<br>
Item was removed:<br>
- ----- Method: StackInterpreter class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
-       | requiredList |<br>
-       requiredList := self exportAPISelectors.<br>
-       requiredList addAll: NewObjectMemory requiredMethodNames.<br>
-       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
-       requiredList addAll: #(<br>
-               assertValidExecutionPointe:r:s:<br>
-               characterForAscii: checkedLongAt:<br>
-               delayExpired<br>
-               findClassOfMethod:forReceiver: findSelectorOfMethod:<br>
-                       forceInterruptCheck forceInterruptCheckFromHeartbeat fullDisplayUpdate<br>
-               getCurrentBytecode getFullScreenFlag getInterruptKeycode getInterruptPending<br>
-                       getSavedWindowSize getThisSessionID<br>
-               highBit:<br>
-               interpret<br>
-               loadInitialContext<br>
-               oopFromChunk:<br>
-               primitiveFail primitiveFailFor: primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:<br>
-                       printExternalHeadFrame printFramesInPage: printFrame: printHeadFrame printMemory printOop:<br>
-                               printStackPages printStackPageList printStackPagesInUse printStackPageListInUse<br>
-               readableFormat: readImageFromFile:HeapSize:StartingAt:<br>
-               setFullScreenFlag: setInterruptKeycode: setInterruptPending: setInterruptCheckChain:<br>
-                       setSavedWindowSize: success:<br>
-               validInstructionPointer:inMethod:framePointer:).<br>
-<br>
-       &quot;Nice to actually have all the primitives available&quot;<br>
-       requiredList addAll: (self primitiveTable select: [:each| each isSymbol]).<br>
-<br>
-       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
-       InterpreterProxy organization categories do:<br>
-               [:cat |<br>
-               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue:<br>
-                       [requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
-<br>
-       ^requiredList!<br>
<br>
Item was added:<br>
+ ----- Method: StackInterpreter class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;return the list of method names that should be retained for export or other support reasons&quot;<br>
+       | requiredList |<br>
+       requiredList := self exportAPISelectors: options.<br>
+       requiredList addAll: (NewObjectMemory requiredMethodNames: options).<br>
+       &quot;A number of methods required by VM support code, jitter, specific platforms etc&quot;<br>
+       requiredList addAll: #(<br>
+               assertValidExecutionPointe:r:s:<br>
+               characterForAscii:<br>
+               findClassOfMethod:forReceiver: findSelectorOfMethod:<br>
+                       forceInterruptCheck forceInterruptCheckFromHeartbeat fullDisplayUpdate<br>
+               getCurrentBytecode getFullScreenFlag getInterruptKeycode getInterruptPending<br>
+                       getSavedWindowSize getThisSessionID<br>
+               interpret<br>
+               loadInitialContext<br>
+               oopFromChunk:<br>
+               primitiveFail primitiveFailFor: primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:<br>
+                       printExternalHeadFrame printFramesInPage: printFrame: printHeadFrame printMemory printOop:<br>
+                               printStackPages printStackPageList printStackPagesInUse printStackPageListInUse<br>
+               readableFormat: readImageFromFile:HeapSize:StartingAt:<br>
+               setFullScreenFlag: setInterruptKeycode: setInterruptPending: setInterruptCheckChain:<br>
+                       setSavedWindowSize: success:<br>
+               validInstructionPointer:inMethod:framePointer:).<br>
+<br>
+       &quot;Nice to actually have all the primitives available&quot;<br>
+       requiredList addAll: (self primitiveTable select: [:each| each isSymbol]).<br>
+<br>
+       &quot;InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those&quot;<br>
+       InterpreterProxy organization categories do:<br>
+               [:cat |<br>
+               ((cat ~= &#39;initialize&#39;) and: [cat ~= &#39;private&#39;]) ifTrue:<br>
+                       [requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].<br>
+<br>
+       ^requiredList!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;computeStackZoneSize (in category &#39;initialization&#39;) -----<br>
  computeStackZoneSize<br>
        &quot;In C the StackPage structs live next to the actual stack pages in the alloca&#39;ed stack<br>
         zone.  In simulation these live in some dictionary and don&#39;t exist in the memory.&quot;<br>
+       ^numStackPages * ((self cCode: [self sizeof: InterpreterStackPage] inSmalltalk: [0])<br>
-       ^numStackPages * ((self cCode: &#39;sizeof(StackPage)&#39; inSmalltalk: [0])<br>
                                                + self stackPageByteSize)<br>
         + stackPages extraStackBytes!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;functionPointerFor:inClass: (in category &#39;method lookup cache&#39;) -----<br>
  functionPointerFor: primIdx inClass: theClass<br>
        &quot;Find an actual function pointer for this primitiveIndex.  This is an<br>
        opportunity to specialise the prim for the relevant class (format for<br>
        example).  Default for now is simply the entry in the base primitiveTable.&quot;<br>
+       &lt;api&gt;<br>
-<br>
        &lt;returnTypeC: &#39;void (*functionPointerForinClass(sqInt primIdx,sqInt theClass))(void)&#39;&gt;<br>
        ^primIdx &gt; MaxPrimitiveIndex ifTrue: [0] ifFalse: [primitiveTable at: primIdx]!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;literal:ofMethod: (in category &#39;compiled methods&#39;) -----<br>
  literal: offset ofMethod: methodPointer<br>
+       &lt;api&gt;<br>
+       ^objectMemory fetchPointer: offset + LiteralStart ofObject: methodPointer<br>
-<br>
-       ^ objectMemory fetchPointer: offset + LiteralStart ofObject: methodPointer<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;popStack (in category &#39;internal interpreter access&#39;) -----<br>
  popStack<br>
        &quot;In the StackInterpreter stacks grow down.&quot;<br>
+       &lt;api&gt;<br>
        | top |<br>
        &lt;inline: true&gt;<br>
        top := stackPages longAt: stackPointer.<br>
        stackPointer := stackPointer + BytesPerWord.<br>
        ^top!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;specialSelector: (in category &#39;message sending&#39;) -----<br>
  specialSelector: index<br>
+       &lt;api&gt;<br>
+       ^objectMemory fetchPointer: (index * 2) ofObject: (objectMemory splObj: SpecialSelectors)!<br>
-<br>
-       ^ objectMemory fetchPointer: (index * 2) ofObject: (objectMemory splObj: SpecialSelectors)!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;stackTop (in category &#39;internal interpreter access&#39;) -----<br>
  stackTop<br>
+       &lt;api&gt;<br>
        ^stackPages longAt: stackPointer!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter&gt;&gt;tempCountOf: (in category &#39;compiled methods&#39;) -----<br>
  tempCountOf: methodPointer<br>
+       &lt;api&gt;<br>
        ^self temporaryCountOfMethodHeader: (self headerOf: methodPointer)!<br>
<br>
Item was added:<br>
+ ----- Method: StackToRegisterMappingCogit class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^((super ancilliaryClasses: options) copyWithout: CogBytecodeFixup),<br>
+         { CogSSBytecodeFixup. CogSimStackEntry. CogSSOptStatus }!<br>
<br>
Item was removed:<br>
- ----- Method: StackToRegisterMappingCogit class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       &quot;self ancilliaryStructClasses&quot;<br>
-       ^(super ancilliaryStructClasses copyWithout: CogBytecodeFixup),<br>
-         { CogSSBytecodeFixup. CogSimStackEntry. CogSSOptStatus }!<br>
<br>
Item was removed:<br>
- ----- Method: StackToRegisterMappingCogit class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;self requiredMethodNames&quot;<br>
-       ^super requiredMethodNames<br>
-               add: self isPushNilFunction;<br>
-               add: self pushNilSizeFunction;<br>
-               yourself!<br>
<br>
Item was added:<br>
+ ----- Method: StackToRegisterMappingCogit class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       ^(super requiredMethodNames: options)<br>
+               add: self isPushNilFunction;<br>
+               add: self pushNilSizeFunction;<br>
+               yourself!<br>
<br>
Item was added:<br>
+ ----- Method: ThreadedFFIPlugin class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: options<br>
+       ^{ self calloutStateClass }!<br>
<br>
Item was removed:<br>
- ----- Method: ThreadedFFIPlugin class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^{ self calloutStateClass }!<br>
<br>
Item was removed:<br>
- ----- Method: VMClass class&gt;&gt;ancilliaryClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryClasses<br>
-       &quot;Answer any extra classes to be included in the translation.&quot;<br>
-       ^#()!<br>
<br>
Item was added:<br>
+ ----- Method: VMClass class&gt;&gt;ancilliaryClasses: (in category &#39;translation&#39;) -----<br>
+ ancilliaryClasses: optionsDictionary<br>
+       &quot;Answer any extra classes to be included in the translation.&quot;<br>
+       ^{}!<br>
<br>
Item was removed:<br>
- ----- Method: VMClass class&gt;&gt;ancilliaryStructClasses (in category &#39;translation&#39;) -----<br>
- ancilliaryStructClasses<br>
-       ^#()!<br>
<br>
Item was removed:<br>
- ----- Method: VMClass class&gt;&gt;exportAPISelectors (in category &#39;translation&#39;) -----<br>
- exportAPISelectors<br>
-       ^self exportAPISelectorsFor: self!<br>
<br>
Item was added:<br>
+ ----- Method: VMClass class&gt;&gt;exportAPISelectors: (in category &#39;translation&#39;) -----<br>
+ exportAPISelectors: options<br>
+       ^self exportAPISelectorsFor: self!<br>
<br>
Item was removed:<br>
- ----- Method: VMClass class&gt;&gt;requiredMethodNames (in category &#39;translation&#39;) -----<br>
- requiredMethodNames<br>
-       &quot;Answer a list of method names that should be retained for export or other<br>
-        support reasons.  These are typically entry-points that unless explicitly noted<br>
-        will be deleted by the code generator since it will assume these are not used.&quot;<br>
-       ^#()!<br>
<br>
Item was added:<br>
+ ----- Method: VMClass class&gt;&gt;requiredMethodNames: (in category &#39;translation&#39;) -----<br>
+ requiredMethodNames: options<br>
+       &quot;Answer a list of method names that should be retained for export or other<br>
+        support reasons.  These are typically entry-points that unless explicitly noted<br>
+        will be deleted by the code generator since it will assume these are not used.&quot;<br>
+       ^#()!<br>
<br>
Item was changed:<br>
  ----- Method: VMMaker&gt;&gt;buildCodeGeneratorForCogit: (in category &#39;generate sources&#39;) -----<br>
  buildCodeGeneratorForCogit: getAPIMethods<br>
        &quot;Answer the code generator for translating the cogit.&quot;<br>
<br>
        | cg cogitClass cogitClasses apicg |<br>
        cg := self createCogitCodeGenerator.<br>
<br>
        cg vmClass: (cogitClass := self cogitClass).<br>
        { cogitClass. self interpreterClass } do:<br>
                [:cgc|<br>
                (cgc respondsTo: #initializeWithOptions:)<br>
                        ifTrue: [cgc initializeWithOptions: optionsDictionary]<br>
                        ifFalse: [cgc initialize]].<br>
<br>
        cogitClasses := OrderedCollection new.<br>
        [cogitClasses addFirst: cogitClass.<br>
         cogitClass ~~ Cogit<br>
         and: [cogitClass inheritsFrom: Cogit]] whileTrue:<br>
                [cogitClass := cogitClass superclass].<br>
        cogitClasses addFirst: VMClass.<br>
+       cogitClasses addAllLast: ((self cogitClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]).<br>
-       cogitClasses addAllLast: self cogitClass ancilliaryClasses.<br>
        cogitClasses do: [:cgc| cg addClass: cgc].<br>
        (cg structClassesForTranslationClasses: cogitClasses) do:<br>
                [:structClass| cg addStructClass: structClass].<br>
<br>
        getAPIMethods ifTrue:<br>
                [apicg := self buildCodeGeneratorForInterpreter: false.<br>
                 cg apiMethods: apicg selectAPIMethods].<br>
<br>
        ^cg!<br>
<br>
Item was changed:<br>
  ----- Method: VMMaker&gt;&gt;buildCodeGeneratorForInterpreter: (in category &#39;generate sources&#39;) -----<br>
  buildCodeGeneratorForInterpreter: getAPIMethods<br>
        &quot;Answer the code generator for translating the interpreter.&quot;<br>
<br>
+       | cg interpreterClass interpreterClasses apicg |<br>
-       | cg interpreterClass interpreterClasses structClasses apicg |<br>
        interpreterClasses := OrderedCollection new.<br>
<br>
        (cg := self createCodeGenerator) vmClass: (interpreterClass := self interpreterClass).<br>
<br>
        [interpreterClass ~~ VMClass] whileTrue:<br>
                [interpreterClasses addFirst: interpreterClass.<br>
                 interpreterClass := interpreterClass superclass].<br>
<br>
        cg vmClass objectMemoryClass ifNotNil:<br>
                [:objectMemoryClass|<br>
                interpreterClass := objectMemoryClass.<br>
                [interpreterClass ~~ VMClass] whileTrue:<br>
                        [interpreterClasses addFirst: interpreterClass.<br>
                         interpreterClass := interpreterClass superclass]].<br>
<br>
        interpreterClasses addFirst: VMClass.<br>
+       interpreterClasses addAllLast: (((self interpreterClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]) copyWithout: cg vmClass objectMemoryClass).<br>
+       (cg structClassesForTranslationClasses: interpreterClasses) do:<br>
-       interpreterClasses addAllLast: (self interpreterClass ancilliaryClasses copyWithout: cg vmClass objectMemoryClass).<br>
-       structClasses := Set new.<br>
-       interpreterClasses do: [:class| structClasses addAll: class ancilliaryStructClasses].<br>
-       (ChangeSet superclassOrder: structClasses asArray) do:<br>
                [:structClass|<br>
                structClass initialize.<br>
                cg addStructClass: structClass].<br>
<br>
        interpreterClasses do:<br>
                [:ic|<br>
                (ic respondsTo: #initializeWithOptions:)<br>
                        ifTrue: [ic initializeWithOptions: optionsDictionary]<br>
                        ifFalse: [ic initialize]].<br>
<br>
        interpreterClasses do: [:ic| cg addClass: ic].<br>
<br>
        (getAPIMethods<br>
        and: [self interpreterClass needsCogit]) ifTrue:<br>
                [apicg := self buildCodeGeneratorForCogit: false.<br>
                 cg apiMethods: apicg selectAPIMethods].<br>
<br>
        ^cg!<br>
<br>
Item was changed:<br>
  ----- Method: VMMaker&gt;&gt;needsToRegenerateCogitFile (in category &#39;generate sources&#39;) -----<br>
  needsToRegenerateCogitFile<br>
+       &quot;Check the timestamp for the relevant classes and then the timestamp for the main source file (e.g. interp.c)<br>
+        file if it already exists. Answer if the file needs regenerating.&quot;<br>
- &quot;check the timestamp for the relevant classes and then the timestamp for the interp.c file if it already exists. Return true if the file needs regenerating, false if not&quot;<br>
<br>
+       | cogitClass cogitClasses tStamp |<br>
+       cogitClasses := (cogitClass := self cogitClass) withAllSuperclasses copyUpThrough: Cogit.<br>
+       cogitClasses addAllLast: (cogitClass ancilliaryClasses: self options).<br>
-       | cogitClass cogitClasses tStamp fstat |<br>
-       cogitClass := self cogitClass.<br>
-       cogitClasses := cogitClass withAllSuperclasses copyUpThrough: Cogit.<br>
-       cogitClasses addAllLast: cogitClass ancilliaryClasses.<br>
        tStamp := cogitClasses inject: 0 into: [:tS :cl| tS max: cl timeStamp].<br>
-       cogitClasses do:<br>
-               [:c|<br>
-               tStamp := c ancilliaryStructClasses inject: tStamp into: [:tS :cl| tS max: cl timeStamp]].<br>
<br>
        &quot;don&#39;t translate if the file is newer than my timeStamp&quot;<br>
+       (self coreVMDirectory entryAt: cogitClass sourceFileName ifAbsent: [nil]) ifNotNil:<br>
+               [:fstat|<br>
+               tStamp &lt; fstat modificationTime ifTrue:<br>
+                       [^self confirm: &#39;The &#39;, cogitClass printString, &#39; classes have not been modified since\ the source file was last generated.\Do you still want to regenerate it?&#39; withCRs]].<br>
-       fstat := self coreVMDirectory entryAt: cogitClass sourceFileName ifAbsent:[nil].<br>
-       fstat ifNotNil:[tStamp &lt; fstat modificationTime ifTrue:<br>
-               [^self confirm: &#39;The &#39;, cogitClass printString, &#39; classes have not been modified since\ the source file was last generated.\Do you still want to regenerate it?&#39; withCRs]].<br>
        ^true<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: VMMaker&gt;&gt;needsToRegenerateInterpreterFile (in category &#39;initialize&#39;) -----<br>
  needsToRegenerateInterpreterFile<br>
+       &quot;Check the timestamp for the relevant classes and then the timestamp for the main<br>
+        source file (e.g. interp.c) if it already exists.  Answer if the file needs regenerating.&quot;<br>
- &quot;check the timestamp for the relevant classes and then the timestamp for the interp.c file if it already exists. Return true if the file needs regenerating, false if not&quot;<br>
<br>
+       | classes tStamp |<br>
-       | classes tStamp fstat |<br>
        classes := self interpreterClass withAllSuperclasses copyUpTo: VMClass.<br>
        self interpreterClass objectMemoryClass ifNotNil:<br>
                [:objectMemoryClass|<br>
                classes addAllLast: (objectMemoryClass  withAllSuperclasses copyUpTo: VMClass)].<br>
        classes copy do:<br>
+               [:class| classes addAllLast: (class ancilliaryClasses: self options)].<br>
-               [:class| classes addAllLast: class ancilliaryClasses].<br>
-       classes copy do:<br>
-               [:class| classes addAllLast: class ancilliaryStructClasses].<br>
        tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].<br>
<br>
        &quot;don&#39;t translate if the file is newer than my timeStamp&quot;<br>
+       (self coreVMDirectory entryAt: self interpreterFilename ifAbsent: [nil]) ifNotNil:<br>
+               [:fstat|<br>
+               tStamp &lt; fstat modificationTime ifTrue:<br>
+                       [^self confirm: &#39;The interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate their source file?&#39; withCRs]].<br>
-       fstat := self coreVMDirectory entryAt: self interpreterFilename ifAbsent:[nil].<br>
-       fstat ifNotNil:[tStamp &lt; fstat modificationTime ifTrue:<br>
-               [^self confirm: &#39;The interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate their source file?&#39; withCRs]].<br>
        ^true<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: VMPluginCodeGenerator&gt;&gt;emitCTypesOn: (in category &#39;C code generator&#39;) -----<br>
+ emitCTypesOn: aStream<br>
- emitCTypesOn: aStream<br>
        &quot;Store local type declarations on the given stream.&quot;<br>
+       (self structClassesForTranslationClasses: { pluginClass }) do:<br>
+               [:structClass|<br>
+               (structClass isAbstract not<br>
+                and: [vmClass shouldGenerateTypedefFor: structClass]) ifTrue:<br>
+                       [structClass printTypedefOn: aStream.<br>
+                        aStream cr; cr]]!<br>
-       ([pluginClass ancilliaryStructClasses]<br>
-               on: MessageNotUnderstood<br>
-               do: [:ex| ex message selector == #ancilliaryStructClasses ifTrue: [^self].<br>
-                               ex pass]) do:<br>
-                       [:structClass|<br>
-                       (pluginClass shouldGenerateTypedefFor: structClass) ifTrue:<br>
-                               [structClass printTypedefOn: aStream.<br>
-                                aStream cr; cr]]!<br>
<br>
</blockquote></div><br></div>