[Vm-dev] VM Maker: VMMaker.oscog-eem.330.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Sun Sep 8 21:03:25 UTC 2013


In VMPluginCodeGenerator>>emitCTypesOn: shouldn't it be
    (pluginClass shouldGenerateTypedefFor: structClass)
rather than
    (vmClass shouldGenerateTypedefFor: structClass) ?

I can't generate IA32ABIPlugin because vmClass isNil, nor
ThreadedIA32FFIPlugin since that change

Nicolas


2013/8/21 <commits at source.squeak.org>

>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.330.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.330
> Author: eem
> Time: 21 August 2013, 2:20:31.076 pm
> UUID: 836f976a-35fa-404c-aa5a-c4af1c58852f
> Ancestors: VMMaker.oscog-eem.329
>
> Refactor ancilliaryClasses and ancilliaryStructClasses to pass in
> options to allow selecting different classes as required.
> i.e. collapse ancilliaryClasses and ancilliaryStructClasses onto
> ancilliaryClasses: optionsDictionary.  This also requires changing
> requiredMethodNames and exportAPISelectors to take options too.
> (this is prior to adding a NewspeakCogMethod class for maintaining
> a list of anonymous methods).
>
> Simplify CoInterpreter class>>exportAPISelectors: by marking a few
> methods as <api>.
>
> Eliminate CogStackPage, collapsing it onto InterpreterStackPage
> (it only has a class side).
>
> Use temporaryCountOfMethodHader: instead of tempCountOf: in
> SimpleStackBasedCogit>>compileFrameBuild (header is in hand).
>
> Reimplement CCodeGenerator>>structClassesForTranslationClasses:
> to keep the sort stable (ChangeSet superclassOrder: is a stable sort
> but structClassesForTranslationClasses: used a set).
>
> =============== Diff against VMMaker.oscog-eem.329 ===============
>
> Item was removed:
> - ----- Method: BitBltSimulation class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       ^self opTable asSet!
>
> Item was added:
> + ----- Method: BitBltSimulation class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       ^self opTable asSet!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>addClass: (in category 'public') -----
>   addClass: aClass
>         "Add the variables and methods of the given class to the code
> base."
>
>         aClass prepareToBeAddedToCodeGenerator: self.
>         self checkClassForNameConflicts: aClass.
>         self addClassVarsFor: aClass.
>         "ikp..."
>         self addPoolVarsFor: aClass.
>         (aClass inheritsFrom: VMStructType) ifFalse:
>                 [variables addAll: aClass instVarNames].
> +       self retainMethods: (aClass requiredMethodNames: self options).
> -       self retainMethods: aClass requiredMethodNames.
>
>         'Adding Class ' , aClass name , '...'
>                 displayProgressAt: Sensor cursorPoint
>                 from: 0
>                 to: aClass selectors size
>                 during:
>                         [:bar |
>                          aClass selectors doWithIndex:
>                                 [:sel :i | | source |
>                                 bar value: i.
>                                 self addMethodFor: aClass selector: sel]].
>         aClass declareCVarsIn: self!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>addStructClass: (in category 'public')
> -----
>   addStructClass: aClass
>         "Add the non-accessor methods of the given struct class to the
> code base."
>
>         aClass prepareToBeAddedToCodeGenerator: self.
>         self addClassVarsFor: aClass.
>         self addPoolVarsFor: aClass.
> +       self retainMethods: (aClass requiredMethodNames: self options).
> -       self retainMethods: aClass requiredMethodNames.
>
>         'Adding Class ' , aClass name , '...'
>                 displayProgressAt: Sensor cursorPoint
>                 from: 0
>                 to: aClass selectors size
>                 during:
>                         [:bar |
>                          aClass selectors doWithIndex:
>                                 [:sel :i | | source |
>                                 bar value: i.
>                                 self addStructMethodFor: aClass selector:
> sel]].
>         aClass declareCVarsIn: self!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>checkClassForNameConflicts: (in category
> 'error notification') -----
>   checkClassForNameConflicts: aClass
>         "Verify that the given class does not have constant, variable, or
> method names that conflict with
>          those of previously added classes. Raise an error if a conflict
> is found, otherwise just return."
>
>         "check for constant name collisions in class pools"
>         aClass classPool associationsDo:
>                 [:assoc |
>                 (constants includesKey: assoc key asString) ifTrue:
>                         [self error: 'Constant ', assoc key, ' was defined
> in a previously added class']].
>
>         "and in shared pools"
>         (aClass sharedPools reject: [:pool| pools includes: pool]) do:
>                 [:pool |
>                 pool bindingsDo:
>                         [:assoc |
>                         (constants includesKey: assoc key asString) ifTrue:
>                                 [self error: 'Constant ', assoc key, ' was
> defined in a previously added class']]].
>
>         "check for instance variable name collisions"
>         (aClass inheritsFrom: VMStructType) ifFalse:
>                 [aClass instVarNames do:
>                         [:varName |
>                         (variables includes: varName) ifTrue:
>                                 [self error: 'Instance variable ',
> varName, ' was defined in a previously added class']]].
>
>         "check for method name collisions"
>         aClass selectors do:
>                 [:sel |
>                 ((methods includesKey: sel)
> +               and: [(aClass isStructClass and: [(aClass isAccessor: sel)
> +                               and: [(methods at: sel)
> isStructAccessor]]) not
> +               and: [((aClass compiledMethodAt: sel) pragmaAt:
> #doNotGenerate) isNil]]) ifTrue:
> -               and: [((aClass compiledMethodAt: sel) pragmaAt:
> #doNotGenerate) isNil]) ifTrue:
>                         [self error: 'Method ', sel, ' was defined in a
> previously added class.']]!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>emitCAPIExportHeaderOn: (in category 'C
> code generator') -----
>   emitCAPIExportHeaderOn: aStream
>         "Store prototype declarations for all non-inlined methods on the
> given stream."
>         | api methodList |
> +       api := (vmClass translationClass exportAPISelectors: self options).
> -       api := vmClass translationClass exportAPISelectors.
>         methodList := api select: [:s| (methods includesKey: s) or:
> [(vmClass whichClassIncludesSelector: s) notNil]]
>                                           thenCollect:
>                                                 [:s|
>                                                 methods
>                                                         at: s
>                                                         ifAbsent: [self
> compileToTMethodSelector: s
>
>          in: (vmClass whichClassIncludesSelector: s)]].
>         methodList := self sortMethods: methodList.
>         methodList do:
>                 [:m|
>                 m static ifTrue:
>                         [logger ensureCr; show: m selector, ' excluded
> from export API because it is static'; cr]].
>         self emitCFunctionPrototypes: methodList on: aStream.
>         self emitGlobalCVariablesOn: aStream.
>         self emitCMacros: methodList on: aStream!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>emitCTypesOn: (in category 'C code
> generator') -----
>   emitCTypesOn: aStream
>         "Store local type declarations on the given stream."
>         vmClass ifNotNil:
> +               [(self structClassesForTranslationClasses: { vmClass }) do:
> -               [vmClass ancilliaryStructClasses do:
>                         [:structClass|
>                         (structClass isAbstract not
>                          and: [vmClass shouldGenerateTypedefFor:
> structClass]) ifTrue:
>                                 [structClass printTypedefOn: aStream.
>                                  aStream cr; cr]]]!
>
> Item was changed:
>   ----- Method: CCodeGenerator>>structClassesForTranslationClasses: (in
> category 'utilities') -----
>   structClassesForTranslationClasses: classes
> +       "Answer in superclass order (any superclass precedes any subclass)
> +        the ancilliaryClasses that are struct classes for all the given
> classes."
> -       "Answer in superclass order (any superclass precedes any subclass)
> the ancilliaryStructClasses for all the given classes."
>         | structClasses |
> +       structClasses := OrderedCollection new.
> -
> -       structClasses := Set new.
>         classes do:
>                 [:aTranslationClass|
> +               ([aTranslationClass ancilliaryClasses: self options]
> -               structClasses addAll:
> -                       ([aTranslationClass ancilliaryStructClasses]
>                                 on: MessageNotUnderstood
>                                 do: [:ex|
> +                                       ex message selector ==
> #ancilliaryClasses:
> -                                       ex message selector ==
> #ancilliaryStructClasses
>                                                 ifTrue: [#()]
> +                                               ifFalse: [ex pass]]) do:
> +                       [:class|
> +                       (class isStructClass
> +                        and: [(structClasses includes: class) not])
> ifTrue:
> +                               [structClasses addLast: class]]].
> +       ^ChangeSet superclassOrder: structClasses!
> -                                               ifFalse: [ex pass]])].
> -       ^ChangeSet superclassOrder: structClasses asArray!
>
> Item was removed:
> - ----- Method: CoInterpreter class>>ancilliaryClasses (in category
> 'translation') -----
> - ancilliaryClasses
> -       "Answer any extra classes to be included in the translation."
> -       ^super ancilliaryClasses
> -               copyReplaceAll: { InterpreterStackPages }
> -               with: { CoInterpreterStackPages }!
>
> Item was added:
> + ----- Method: CoInterpreter class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       "Answer any extra classes to be included in the translation."
> +       ^((super ancilliaryClasses: options) copyWithout:
> InterpreterStackPages),
> +          {    CoInterpreterStackPages.
> +               CogBlockMethod.
> +               CogMethod }!
>
> Item was removed:
> - ----- Method: CoInterpreter class>>ancilliaryStructClasses (in category
> 'translation') -----
> - ancilliaryStructClasses
> -       ^{ CogStackPage.
> -               CogBlockMethod.
> -               CogMethod }!
>
> Item was removed:
> - ----- Method: CoInterpreter class>>exportAPISelectors (in category
> 'translation') -----
> - exportAPISelectors
> -       "Yes this is a mess.  When all exportAPI methods are marked with
> the <api> pragma
> -        this can go away."
> -       | omExports |
> -       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo:
> VMClass)
> -                                       inject: Set new into: [:api :c|
> api addAll: c exportAPISelectors; yourself].
> -       ^((self withAllSuperclasses copyUpTo: VMClass),
> -               self ancilliaryClasses
> -                       inject: omExports
> -                       into: [:set :class| set addAll: (self
> exportAPISelectorsFor: class); yourself])
> -               addAll: #(      classHeader:
> -                                       compactClassIndexOf:
> -                                       fetchByte:ofObject:
> -                                       functionPointerFor:inClass:
> -                                       isNonIntegerObject:
> -                                       lastPointerOf:
> -                                       literal:ofMethod:
> -                                       popStack
> -
> primitiveClosureValueNoContextSwitch
> -                                       specialSelector:
> -                                       stackTop
> -                                       tempCountOf:);
> -               yourself!
>
> Item was added:
> + ----- Method: CoInterpreter class>>exportAPISelectors: (in category
> 'translation') -----
> + exportAPISelectors: options
> +       "Yes this is a mess.  When all exportAPI methods are marked with
> the <api> pragma
> +        this can go away."
> +       | omExports |
> +       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo:
> VMClass)
> +                                       inject: Set new into: [:api :c|
> api addAll: (c exportAPISelectors: options); yourself].
> +       ^(self withAllSuperclasses copyUpTo: VMClass), (self
> ancilliaryClasses: options)
> +               inject: omExports
> +               into: [:set :class| set addAll: (self
> exportAPISelectorsFor: class); yourself]!
>
> Item was changed:
>   ----- Method: CoInterpreter class>>shouldGenerateTypedefFor: (in
> category 'translation') -----
>   shouldGenerateTypedefFor: aStructClass
>         "Hack to work-around multiple definitions.  Sometimes a type has
> been defined in an include."
> +       ^({ CogBlockMethod. CogMethod. SistaCogMethod. VMCallbackContext }
> includes: aStructClass) not!
> -       ^({ CogBlockMethod. CogMethod. SistaCogMethod } includes:
> aStructClass) not!
>
> Item was changed:
>   ----- Method: CoInterpreter>>computeStackZoneSize (in category
> 'initialization') -----
>   computeStackZoneSize
> +       ^numStackPages * ((self sizeof: InterpreterStackPage) + self
> stackPageByteSize)
> -       ^numStackPages * ((self sizeof: CogStackPage) + self
> stackPageByteSize)
>          + stackPages extraStackBytes!
>
> Item was removed:
> - ----- Method: CoInterpreterMT class>>ancilliaryClasses (in category
> 'translation') -----
> - ancilliaryClasses
> -       ^super ancilliaryClasses, { CogThreadManager }!
>
> Item was added:
> + ----- Method: CoInterpreterMT class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       ^(super ancilliaryClasses: options), { CogThreadManager.
> CogVMThread }!
>
> Item was removed:
> - ----- Method: CoInterpreterMT class>>ancilliaryStructClasses (in
> category 'translation') -----
> - ancilliaryStructClasses
> -       ^super ancilliaryStructClasses, { CogVMThread }!
>
> Item was changed:
>   ----- Method:
> CoInterpreterStackPages>>initializeStack:numSlots:pageSize: (in category
> 'initialization') -----
>   initializeStack: theStackPages numSlots: stackSlots pageSize:
> slotsPerPage
>         "Initialize the stack pages.  In the C VM theStackPages will be
> alloca'ed memory to hold the
>          stack pages on the C stack.  In the simulator they are housed in
> the memory between the
>          cogMethodZone and the heap."
>
>         <var: #theStackPages type: #'char *'>
>         <returnTypeC: #void>
>         | numPages page structStackPageSize pageStructBase count |
>         <var: #page type: #'StackPage *'>
>         <var: #pageStructBase type: #'char *'>
>         self cCode: []
>                 inSmalltalk:
>                         [self assert: objectMemory startOfMemory -
> coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter
> primTraceLogSize - coInterpreter rumpCStackSize
>                                         = (stackSlots * BytesPerWord)].
> +       structStackPageSize := coInterpreter sizeof: InterpreterStackPage.
> -       structStackPageSize := coInterpreter sizeof: CogStackPage.
>         bytesPerPage := slotsPerPage * BytesPerWord.
>         numPages := coInterpreter numStkPages.
>
>         "Because stack pages grow down baseAddress is at the top of a
> stack page and so to avoid
>          subtracting BytesPerWord from baseAddress and lastAddress in the
> init loop below we simply
>          push the stackPage array up one word to avoid the overlap.  This
> word is extraStackBytes."
>         pageStructBase := theStackPages + (numPages * bytesPerPage) +
> BytesPerWord.
>         pages := self cCode: [self cCoerceSimple: pageStructBase to:
> #'StackPage *']
>                                   inSmalltalk:
>                                         [pageMap := Dictionary new.
>                                          ((0 to: numPages - 1) collect:
>                                                 [:i|
> +                                                InterpreterStackPage
> surrogateClass new
> -                                                CogStackPage
> surrogateClass new
>                                                         address:
> pageStructBase + (i * structStackPageSize)
>                                                         simulator:
> coInterpreter
>                                                         zoneBase:
> coInterpreter stackZoneBase
>                                                         zoneLimit:
> objectMemory startOfMemory])
>                                                 do: [:pageSurrogate|
>                                                         pageMap at:
> pageSurrogate address put: pageSurrogate];
>                                                 yourself].
>         "make sure there's enough headroom"
>         self assert: coInterpreter stackPageByteSize - coInterpreter
> stackLimitBytes - coInterpreter stackLimitOffset
>                                 >= coInterpreter stackPageHeadroom.
>         0 to: numPages - 1 do:
>                 [:index|
>                  page := self stackPageAt: index.
>                  page
>                         lastAddress: theStackPages + (index *
> bytesPerPage);
>                         baseAddress: page lastAddress + bytesPerPage;
>                         stackLimit: page baseAddress - coInterpreter
> stackLimitBytes;
>                         realStackLimit: page stackLimit;
>                         baseFP: 0;
>                         nextPage: (self stackPageAt: (index = (numPages -
> 1) ifTrue: [0] ifFalse: [index + 1]));
>                         prevPage: (self stackPageAt: (index = 0 ifTrue:
> [numPages - 1] ifFalse: [index - 1]))].
>
>         "Now compute stackBasePlus1 so that the pageIndexFor: call maps
> all addresses from
>          aPage baseAddress to aBase limitAddress + 1 to the same index
> (stacks grow down)"
>         stackBasePlus1 := (self cCoerceSimple: theStackPages to: #'char
> *') + 1.
>         self cCode: []
>                 inSmalltalk:
>                         [minStackAddress := theStackPages.
>                          maxStackAddress := theStackPages + (numPages *
> bytesPerPage) + BytesPerWord - 1].
>
>         "The overflow limit is the amount of stack to retain when moving
> frames from an overflowing
>          stack to reduce thrashing.  See
> stackOverflowOrEvent:mayContextSwitch:"
>         page := self stackPageAt: 0.
>         overflowLimit := page baseAddress - page realStackLimit * 3 // 5.
>         0 to: numPages - 1 do:
>                 [:index|
>                  page := self stackPageAt: index.
>                  self assert: (self pageIndexFor: page baseAddress) ==
> index.
>                  self assert: (self pageIndexFor: page baseAddress -
> (slotsPerPage - 1 * BytesPerWord)) == index.
>                  self assert: (self stackPageFor: page baseAddress) ==
> page.
>                  self assert: (self stackPageFor: page stackLimit) == page.
>                  self cCode: []
>                         inSmalltalk:
>                                 [| memIndex |
>                                  memIndex := index * slotsPerPage + 1.
> "this is memIndex in the block above"
>                                  self assert: (self memIndexFor: (self
> oopForPointer: page baseAddress))
>                                                         == (memIndex +
> slotsPerPage - 1).
>                                  index < (numPages - 1) ifTrue:
>                                         [self assert: (self stackPageFor:
> page baseAddress + BytesPerWord) == (self stackPageAt: index + 1)]].
>                 self assert: (page trace: -1) ~= 0 "for assert checking of
> the page tracing flags. -1 == invalid state"].
>
>         mostRecentlyUsedPage := self stackPageAt: 0.
>         page := mostRecentlyUsedPage.
>         count := 0.
>         [| theIndex |
>          count := count + 1.
>          theIndex := self pageIndexFor: page baseAddress.
>          self assert: (self stackPageAt: theIndex) == page.
>          self assert: (self pageIndexFor: page baseAddress) == theIndex.
>          self assert: (self pageIndexFor: page stackLimit) == theIndex.
>          self assert: (self pageIndexFor: page lastAddress + 1) ==
> theIndex.
>          (page := page nextPage) ~= mostRecentlyUsedPage] whileTrue.
>         self assert: count == numPages.
>         self assert: self pageListIsWellFormed!
>
> Item was removed:
> - ----- Method: CogAbstractInstruction class>>requiredMethodNames (in
> category 'translation') -----
> - requiredMethodNames
> -       ^self selectors reject:
> -               [:s|
> -               (self isAccessor: s)
> -               or: [((self compiledMethodAt: s) pragmaAt: #doNotGenerate)
> notNil]]!
>
> Item was added:
> + ----- Method: CogAbstractInstruction class>>requiredMethodNames: (in
> category 'translation') -----
> + requiredMethodNames: options
> +       ^self selectors reject:
> +               [:s|
> +               (self isAccessor: s)
> +               or: [((self compiledMethodAt: s) pragmaAt: #doNotGenerate)
> notNil]]!
>
> Item was removed:
> - InterpreterStackPage subclass: #CogStackPage
> -       instanceVariableNames: ''
> -       classVariableNames: ''
> -       poolDictionaries: ''
> -       category: 'VMMaker-JIT'!
>
> Item was removed:
> - ----- Method: CogStackPage class>>alignedByteSize (in category
> 'translation') -----
> - alignedByteSize
> -       ^self surrogateClass alignedByteSize!
>
> Item was removed:
> - ----- Method: CogStackPage class>>alignedByteSizeOf:forClient: (in
> category 'translation') -----
> - alignedByteSizeOf: anObject forClient: aVMClass
> -       ^self surrogateClass alignedByteSize!
>
> Item was removed:
> - ----- Method: CogStackPage class>>surrogateClass (in category
> 'simulation only') -----
> - surrogateClass
> -       ^BytesPerWord = 4
> -               ifTrue: [CogStackPageSurrogate32]
> -               ifFalse: [CogStackPageSurrogate64]!
>
> Item was removed:
> - ----- Method: Cogit class>>ancilliaryClasses (in category 'translation')
> -----
> - ancilliaryClasses
> -       ^super ancilliaryClasses,
> -         { CogMethodZone }!
>
> Item was added:
> + ----- Method: Cogit class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       ProcessorClass ifNil: [thisContext methodClass theNonMetaClass
> initialize].
> +       ^{      CogMethodZone.
> +               CogAbstractInstruction.
> +               ProcessorClass basicNew abstractInstructionCompilerClass.
> +               CogBlockStart.
> +               CogBytecodeDescriptor.
> +               CogBytecodeFixup.
> +               CogInstructionAnnotation.
> +               CogPrimitiveDescriptor.
> +               CogBlockMethod.
> +               CogMethod
> +         }!
>
> Item was removed:
> - ----- Method: Cogit class>>ancilliaryStructClasses (in category
> 'translation') -----
> - ancilliaryStructClasses
> -       ProcessorClass ifNil: [thisContext methodClass theNonMetaClass
> initialize].
> -       ^{      CogAbstractInstruction.
> -               ProcessorClass basicNew abstractInstructionCompilerClass.
> -               CogBlockStart.
> -               CogBytecodeDescriptor.
> -               CogBytecodeFixup.
> -               CogInstructionAnnotation.
> -               CogPrimitiveDescriptor.
> -               CogBlockMethod.
> -               CogMethod       }!
>
> Item was removed:
> - ----- Method: Cogit class>>exportAPISelectors (in category
> 'translation') -----
> - exportAPISelectors
> -       ^((self withAllSuperclasses copyUpThrough: Cogit), self
> ancilliaryClasses collect:
> -               [:c| self exportAPISelectorsFor: c]) fold: [:a :b| a, b]!
>
> Item was added:
> + ----- Method: Cogit class>>exportAPISelectors: (in category
> 'translation') -----
> + exportAPISelectors: options
> +       ^((self withAllSuperclasses copyUpThrough: Cogit), (self
> ancilliaryClasses: options) collect:
> +               [:c| self exportAPISelectorsFor: c]) fold: [:a :b| a, b]!
>
> Item was changed:
>   ----- Method: Cogit class>>preGenerationHook: (in category
> 'translation') -----
>   preGenerationHook: aCCodeGenerator
>         "Perform any last-minute changes to the code generator immediately
>          before it performs code analysis and generation.  In this case,
> make
>          all non-exported methods private."
>         | exportAPISelectors |
> +       exportAPISelectors := self exportAPISelectors: aCCodeGenerator
> options.
> -       exportAPISelectors := self exportAPISelectors.
>         aCCodeGenerator selectorsAndMethodsDo:
>                 [:s :m|
>                 (exportAPISelectors includes: s)
>                         ifTrue: [m static: false]
>                         ifFalse:
>                                 [m export ifFalse:
>                                         [m static: true]]]!
>
> Item was removed:
> - ----- Method: Cogit class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       "self requiredMethodNames"
> -       ^self exportAPISelectors
> -               addAll: self tableFunctions;
> -               yourself!
>
> Item was added:
> + ----- Method: Cogit class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       "self requiredMethodNames"
> +       ^(self exportAPISelectors: options)
> +               addAll: self tableFunctions;
> +               yourself!
>
> Item was added:
> + ----- Method: IA32ABIPlugin class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       ^{ VMCallbackContext. VMCallbackReturnValue }!
>
> Item was removed:
> - ----- Method: IA32ABIPlugin class>>ancilliaryStructClasses (in category
> 'translation') -----
> - ancilliaryStructClasses
> -       ^{ VMCallbackContext. VMCallbackReturnValue }!
>
> Item was changed:
>   ----- Method: Interpreter class>>preGenerationHook: (in category
> 'translation') -----
>   preGenerationHook: aCCodeGenerator
>         "Perform any last-minute changes to the code generator immediately
>          before it performs code analysis and generation.  In this case,
> make
>          all non-exported methods private."
>         | requiredMethodNames |
> +       requiredMethodNames := self requiredMethodNames: aCCodeGenerator
> options.
> -       requiredMethodNames := self requiredMethodNames.
>         aCCodeGenerator selectorsAndMethodsDo:
>                 [:s :m|
>                 (m export or: [requiredMethodNames includes: s]) ifTrue:
>                         [m static: false]]!
>
> Item was removed:
> - ----- Method: Interpreter class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       "return the list of method names that should be retained for
> export or other support reasons"
> -       | requiredList |
> -       requiredList := Set new: 400.
> -       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> -       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).
> -
> -       "Nice to actually have all the primitives available"
> -       requiredList addAll: self primitiveTable.
> -
> -       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> -       InterpreterProxy organization categories do: [:cat |
> -               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue: [
> -                       requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> -
> -       ^requiredList!
>
> Item was added:
> + ----- Method: Interpreter class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       "return the list of method names that should be retained for
> export or other support reasons"
> +       | requiredList |
> +       requiredList := Set new: 400.
> +       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> +       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).
> +
> +       "Nice to actually have all the primitives available"
> +       requiredList addAll: self primitiveTable.
> +
> +       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> +       InterpreterProxy organization categories do: [:cat |
> +               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue: [
> +                       requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> +
> +       ^requiredList!
>
> Item was changed:
>   ----- Method:
> InterpreterPrimitives>>primitiveClosureValueNoContextSwitch (in category
> 'control primitives') -----
>   primitiveClosureValueNoContextSwitch
>         "An exact clone of primitiveClosureValue except that this version
> will not
>          check for interrupts on stack overflow.  It may invoke the
> garbage collector
>          but will not switch processes.  See
> checkForInterruptsMayContextSwitch:"
> +       <api>
>         | blockClosure numArgs closureMethod outerContext |
>         blockClosure := self stackValue: argumentCount.
>         numArgs := self argumentCountOfClosure: blockClosure.
>         argumentCount = numArgs ifFalse:
>                 [^self primitiveFail].
>
>         "Somewhat paranoiac checks we need while debugging that we may be
> able to discard
>          in a robust system."
>         outerContext := objectMemory fetchPointer:
> ClosureOuterContextIndex ofObject: blockClosure.
>         (objectMemory isContext: outerContext) ifFalse:
>                 [^self primitiveFail].
>         closureMethod := objectMemory fetchPointer: MethodIndex ofObject:
> outerContext.
>         "Check if the closure's method is actually a CompiledMethod."
>         (objectMemory isOopCompiledMethod: closureMethod) ifFalse:
>                 [^self primitiveFail].
>
>         "Note we use activateNewMethod, not executeNewMethod, to avoid
>          quickCheckForInterrupts.  Don't check until we have a full
> activation."
>         self activateNewClosureMethod: blockClosure numArgs: numArgs
> mayContextSwitch: false!
>
> Item was changed:
> + ----- Method: InterpreterStackPage class>>alignedByteSize (in category
> 'translation') -----
> - ----- Method: InterpreterStackPage class>>alignedByteSize (in category
> 'accessing') -----
>   alignedByteSize
> +       ^self surrogateClass alignedByteSize!
> -       "Simulation only.  In the simulation stack pages are purely
> Smalltalk objects
> -        and don't exist in memory."
> -       ^0!
>
> Item was changed:
>   ----- Method: InterpreterStackPage class>>alignedByteSizeOf:forClient:
> (in category 'translation') -----
>   alignedByteSizeOf: anObject forClient: aVMClass
> +       ^self surrogateClass alignedByteSize!
> -       ^self alignedByteSize!
>
> Item was added:
> + ----- Method: InterpreterStackPage class>>surrogateClass (in category
> 'simulation only') -----
> + surrogateClass
> +       ^BytesPerWord = 4
> +               ifTrue: [CogStackPageSurrogate32]
> +               ifFalse: [CogStackPageSurrogate64]!
>
> Item was changed:
>   ----- Method: NewObjectMemory>>lastPointerOf: (in category 'object
> enumeration') -----
>   lastPointerOf: oop
>         "Return the byte offset of the last pointer field of the given
> object.
>          Can be used even when the type bits are not correct.
>          Works with CompiledMethods, as well as ordinary objects."
> +       <api>
> -       | fmt header contextSize numLiterals |
>         <inline: true>
>         <asmLabel: false>
> +       | fmt header contextSize numLiterals |
>         header := self baseHeader: oop.
>         fmt := self formatOfHeader: header.
>         fmt <= 4 ifTrue:
>                 [(fmt = 3
>                   and: [self isContextHeader: header]) ifTrue:
>                         ["contexts end at the stack pointer"
>                         contextSize := coInterpreter fetchStackPointerOf:
> oop.
>                         ^CtxtTempFrameStart + contextSize * BytesPerOop].
>                 ^(self sizeBitsOfSafe: oop) - BaseHeaderSize  "all
> pointers"].
>         fmt < 12 ifTrue: [^0]. "no pointers"
>
>         "CompiledMethod: contains both pointers and bytes"
>         numLiterals := coInterpreter literalCountOf: oop.
>         ^numLiterals + LiteralStart * BytesPerOop!
>
> Item was added:
> + ----- Method: NewspeakInterpreter class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       ^{ VMCallbackContext }!
>
> Item was removed:
> - ----- Method: NewspeakInterpreter class>>ancilliaryStructClasses (in
> category 'translation') -----
> - ancilliaryStructClasses
> -       ^{ VMCallbackContext }!
>
> Item was changed:
>   ----- Method: NewspeakInterpreter class>>preGenerationHook: (in category
> 'translation') -----
>   preGenerationHook: aCCodeGenerator
>         "Perform any last-minute changes to the code generator immediately
>          before it performs code analysis and generation.  In this case,
> make
>          all non-exported methods private."
>         | publicMethodNames |
> +       publicMethodNames := (self requiredMethodNames: aCCodeGenerator
> options)
> -       publicMethodNames := self requiredMethodNames
>
> copyWithoutAll: (self primitiveTable
>
>                                       copyWithout: #primitiveFail).
>         aCCodeGenerator selectorsAndMethodsDo:
>                 [:s :m|
>                 (m export or: [publicMethodNames includes: s]) ifTrue:
>                         [m static: false]]!
>
> Item was removed:
> - ----- Method: NewspeakInterpreter class>>requiredMethodNames (in
> category 'translation') -----
> - requiredMethodNames
> -       "return the list of method names that should be retained for
> export or other support reasons"
> -       | requiredList |
> -       requiredList := self exportAPISelectors..
> -       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> -       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:).
> -
> -       "Nice to actually have all the primitives available"
> -       requiredList addAll: self primitiveTable.
> -
> -       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> -       InterpreterProxy organization categories do: [:cat |
> -               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue: [
> -                       requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> -
> -       ^requiredList!
>
> Item was added:
> + ----- Method: NewspeakInterpreter class>>requiredMethodNames: (in
> category 'translation') -----
> + requiredMethodNames: options
> +       "return the list of method names that should be retained for
> export or other support reasons"
> +       | requiredList |
> +       requiredList := self exportAPISelectors: options.
> +       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> +       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:).
> +
> +       "Nice to actually have all the primitives available"
> +       requiredList addAll: self primitiveTable.
> +
> +       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> +       InterpreterProxy organization categories do: [:cat |
> +               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue: [
> +                       requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> +
> +       ^requiredList!
>
> Item was added:
> + ----- Method: NewsqueakIA32ABIPlugin class>>ancilliaryClasses: (in
> category 'translation') -----
> + ancilliaryClasses: options
> +       ^{ VMCallbackContext. VMCallbackReturnValue }!
>
> Item was removed:
> - ----- Method: NewsqueakIA32ABIPlugin class>>ancilliaryStructClasses (in
> category 'translation') -----
> - ancilliaryStructClasses
> -       ^{ VMCallbackContext. VMCallbackReturnValue }!
>
> Item was removed:
> - ----- Method: ObjectMemory class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       "return the list of method names that should be retained for
> export or other support reasons"
> -       ^self exportAPISelectors!
>
> Item was added:
> + ----- Method: ObjectMemory class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       "return the list of method names that should be retained for
> export or other support reasons"
> +       ^self exportAPISelectors: options!
>
> Item was changed:
>   ----- Method: ObjectMemory>>classHeader: (in category 'header access')
> -----
>   classHeader: oop
> +       <api>
> +       ^self longAt: oop - BaseHeaderSize!
> -
> -       ^ self longAt: oop - BaseHeaderSize!
>
> Item was changed:
>   ----- Method: ObjectMemory>>compactClassIndexOf: (in category 'header
> access') -----
>   compactClassIndexOf: oop
> +       <api>
>         <inline: true>
>         ^((self baseHeader: oop) >> 12) bitAnd: 16r1F!
>
> Item was changed:
>   ----- Method: ObjectMemory>>fetchByte:ofObject: (in category
> 'interpreter access') -----
>   fetchByte: byteIndex ofObject: oop
> +       <api>
> +       ^self byteAt: oop + BaseHeaderSize + byteIndex!
> -
> -       ^ self byteAt: oop + BaseHeaderSize + byteIndex!
>
> Item was changed:
>   ----- Method: ObjectMemory>>isNonIntegerObject: (in category
> 'interpreter access') -----
>   isNonIntegerObject: objectPointer
> +       <api>
> +       ^(objectPointer bitAnd: 1) = 0!
> -
> -       ^ (objectPointer bitAnd: 1) = 0!
>
> Item was changed:
>   ----- Method: ObjectMemory>>lastPointerOf: (in category 'object
> enumeration') -----
>   lastPointerOf: oop
>         "Return the byte offset of the last pointer field of the given
> object.
>         Works with CompiledMethods, as well as ordinary objects.
>         Can be used even when the type bits are not correct."
> +       <api>
> -       | fmt sz methodHeader header contextSize |
>         <inline: true>
>         <asmLabel: false>
> +       | fmt sz methodHeader header contextSize |
>         header := self baseHeader: oop.
>         fmt := self formatOfHeader: header.
>         fmt <= 4 ifTrue: [(fmt = 3 and: [self isContextHeader: header])
>                                         ifTrue: ["contexts end at the
> stack pointer"
>                                                 contextSize := self
> fetchStackPointerOf: oop.
>                                                 ^ CtxtTempFrameStart +
> contextSize * BytesPerWord].
>                                 sz := self sizeBitsOfSafe: oop.
>                                 ^ sz - BaseHeaderSize  "all pointers"].
>         fmt < 12 ifTrue: [^ 0]. "no pointers"
>
>         "CompiledMethod: contains both pointers and bytes:"
>         methodHeader := self longAt: oop + BaseHeaderSize.
>         ^ (methodHeader >> 10 bitAnd: 255) + LiteralStart * BytesPerWord!
>
> Item was removed:
> - ----- Method: SimpleStackBasedCogit class>>ancilliaryClasses (in
> category 'translation') -----
> - ancilliaryClasses
> -       ^super ancilliaryClasses, { CogObjectRepresentationForSqueakV3 }!
>
> Item was added:
> + ----- Method: SimpleStackBasedCogit class>>ancilliaryClasses: (in
> category 'translation') -----
> + ancilliaryClasses: options
> +       "hard-wired for now"
> +       ^(super ancilliaryClasses: options), {
> CogObjectRepresentationForSqueakV3 }!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category
> 'compile abstract instructions') -----
>   compileFrameBuild
>         "Build a frame for a CogMethod activation.  See CoInterpreter
> class>>initializeFrameIndices.
>                         receiver (in ReceiverResultReg)
>                         arg0
>                         ...
>                         argN
>                         caller's saved ip/this stackPage (for a base frame)
>         fp->    saved fp
>                         method
>                         context (uninitialized?)
>                         receiver
>                         first temp
>                         ...
>         sp->    Nth temp
>         If there is a primitive and an error code the Nth temp is the
> error code.
>         Ensure SendNumArgsReg is set early on (incidentally to nilObj)
> because
>         it is the flag determining whether context switch is allowed on
> stack-overflow."
>         | methodHeader jumpSkip |
>         <inline: false>
>         <var: #jumpSkip type: #'AbstractInstruction *'>
>         needsFrame ifFalse: [^0].
>         methodHeader := coInterpreter headerOf: methodObj.
>         backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
>         self PushR: FPReg.
>         self MoveR: SPReg R: FPReg.
>         methodLabel addDependent: (self annotateAbsolutePCRef:
>                 (self PushCw: methodLabel asInteger)). "method"
>         self annotate: (self MoveCw: objectMemory nilObject R:
> SendNumArgsReg)
>                 objRef: objectMemory nilObject.
>         self PushR: SendNumArgsReg. "context"
>         self PushR: ReceiverResultReg.
> +       methodOrBlockNumArgs + 1 to: (coInterpreter
> temporaryCountOfMethodHeader: methodHeader) do:
> -       methodOrBlockNumArgs + 1 to: (coInterpreter tempCountOf:
> methodObj) do:
>                 [:i|
>                 self PushR: SendNumArgsReg].
>         (primitiveIndex > 0
>          and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
>                         = (objectMemory
>                                 fetchByte: initialPC + (coInterpreter
> sizeOfCallPrimitiveBytecode: methodHeader)
>                                 ofObject: methodObj)]) ifTrue:
>                 [self compileGetErrorCode.
>                  initialPC := initialPC
>                                    + (coInterpreter
> sizeOfCallPrimitiveBytecode: methodHeader)
>                                    + (coInterpreter
> sizeOfLongStoreTempBytecode: methodHeader)].
>         self MoveAw: coInterpreter stackLimitAddress R: TempReg.
>         self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
>         "If we can't context switch for this method, use a slightly
>          slower overflow check that clears SendNumArgsReg."
>         (coInterpreter canContextSwitchIfActivating: methodObj header:
> methodHeader)
>                 ifTrue:
>                         [self JumpBelow: stackOverflowCall.
>                          stackCheckLabel := self Label]
>                 ifFalse:
>                         [jumpSkip := self JumpAboveOrEqual: 0.
>                          self MoveCq: 0 R: SendNumArgsReg.
>                          self Jump: stackOverflowCall.
>                          jumpSkip jmpTarget: (stackCheckLabel := self
> Label)].
>         self annotateBytecode: stackCheckLabel!
>
> Item was added:
> + ----- Method: SistaStackToRegisterMappingCogit class>>ancilliaryClasses:
> (in category 'translation') -----
> + ancilliaryClasses: options
> +       ^(super ancilliaryClasses: options) copyWith: SistaCogMethod!
>
> Item was removed:
> - ----- Method: SistaStackToRegisterMappingCogit
> class>>ancilliaryStructClasses (in category 'translation') -----
> - ancilliaryStructClasses
> -       "self ancilliaryStructClasses"
> -       ^super ancilliaryStructClasses copyWith: SistaCogMethod!
>
> Item was removed:
> - ----- Method: StackInterpreter class>>ancilliaryClasses (in category
> 'translation') -----
> - ancilliaryClasses
> -       "Answer any extra classes to be included in the translation."
> -       ^{ self objectMemoryClass. InterpreterStackPages }!
>
> Item was added:
> + ----- Method: StackInterpreter class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       "Answer any extra classes to be included in the translation."
> +       ^{      self objectMemoryClass.
> +               VMCallbackContext.
> +               InterpreterStackPages.
> +               InterpreterStackPage }!
>
> Item was removed:
> - ----- Method: StackInterpreter class>>ancilliaryStructClasses (in
> category 'translation') -----
> - ancilliaryStructClasses
> -       ^{ InterpreterStackPage. VMCallbackContext }!
>
> Item was removed:
> - ----- Method: StackInterpreter class>>exportAPISelectors (in category
> 'translation') -----
> - exportAPISelectors
> -       | omExports |
> -       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo:
> VMClass)
> -                                       inject: Set new
> -                                       into: [:api :c| api addAll: c
> exportAPISelectors; yourself].
> -       ^(self withAllSuperclasses copyUpTo: VMClass), self
> ancilliaryClasses
> -               inject: omExports
> -               into: [:set :class| set addAll: (self
> exportAPISelectorsFor: class); yourself]!
>
> Item was added:
> + ----- Method: StackInterpreter class>>exportAPISelectors: (in category
> 'translation') -----
> + exportAPISelectors: options
> +       | omExports |
> +       omExports := (self objectMemoryClass withAllSuperclasses copyUpTo:
> VMClass)
> +                                       inject: Set new
> +                                       into: [:api :c| api addAll: (c
> exportAPISelectors: options); yourself].
> +       ^(self withAllSuperclasses copyUpTo: VMClass), (self
> ancilliaryClasses: options)
> +               inject: omExports
> +               into: [:set :class| set addAll: (self
> exportAPISelectorsFor: class); yourself]!
>
> Item was changed:
>   ----- Method: StackInterpreter class>>preGenerationHook: (in category
> 'translation') -----
>   preGenerationHook: aCCodeGenerator
>         "Perform any last-minute changes to the code generator immediately
>          before it performs code analysis and generation.  In this case,
> make
>          all non-exported methods private."
>         | publicMethodNames |
> +       publicMethodNames := (self requiredMethodNames: aCCodeGenerator
> options)
> -       publicMethodNames := self requiredMethodNames
>
> copyWithoutAll: (self primitiveTable
>
>                                       copyWithout: #primitiveFail).
>         aCCodeGenerator selectorsAndMethodsDo:
>                 [:s :m|
>                 (m export or: [publicMethodNames includes: s]) ifTrue:
>                         [m static: false]]!
>
> Item was removed:
> - ----- Method: StackInterpreter class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       "return the list of method names that should be retained for
> export or other support reasons"
> -       | requiredList |
> -       requiredList := self exportAPISelectors.
> -       requiredList addAll: NewObjectMemory requiredMethodNames.
> -       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> -       requiredList addAll: #(
> -               assertValidExecutionPointe:r:s:
> -               characterForAscii: checkedLongAt:
> -               delayExpired
> -               findClassOfMethod:forReceiver: findSelectorOfMethod:
> -                       forceInterruptCheck
> forceInterruptCheckFromHeartbeat fullDisplayUpdate
> -               getCurrentBytecode getFullScreenFlag getInterruptKeycode
> getInterruptPending
> -                       getSavedWindowSize getThisSessionID
> -               highBit:
> -               interpret
> -               loadInitialContext
> -               oopFromChunk:
> -               primitiveFail primitiveFailFor:
> primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
> -                       printExternalHeadFrame printFramesInPage:
> printFrame: printHeadFrame printMemory printOop:
> -                               printStackPages printStackPageList
> printStackPagesInUse printStackPageListInUse
> -               readableFormat: readImageFromFile:HeapSize:StartingAt:
> -               setFullScreenFlag: setInterruptKeycode:
> setInterruptPending: setInterruptCheckChain:
> -                       setSavedWindowSize: success:
> -               validInstructionPointer:inMethod:framePointer:).
> -
> -       "Nice to actually have all the primitives available"
> -       requiredList addAll: (self primitiveTable select: [:each| each
> isSymbol]).
> -
> -       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> -       InterpreterProxy organization categories do:
> -               [:cat |
> -               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue:
> -                       [requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> -
> -       ^requiredList!
>
> Item was added:
> + ----- Method: StackInterpreter class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       "return the list of method names that should be retained for
> export or other support reasons"
> +       | requiredList |
> +       requiredList := self exportAPISelectors: options.
> +       requiredList addAll: (NewObjectMemory requiredMethodNames:
> options).
> +       "A number of methods required by VM support code, jitter, specific
> platforms etc"
> +       requiredList addAll: #(
> +               assertValidExecutionPointe:r:s:
> +               characterForAscii:
> +               findClassOfMethod:forReceiver: findSelectorOfMethod:
> +                       forceInterruptCheck
> forceInterruptCheckFromHeartbeat fullDisplayUpdate
> +               getCurrentBytecode getFullScreenFlag getInterruptKeycode
> getInterruptPending
> +                       getSavedWindowSize getThisSessionID
> +               interpret
> +               loadInitialContext
> +               oopFromChunk:
> +               primitiveFail primitiveFailFor:
> primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
> +                       printExternalHeadFrame printFramesInPage:
> printFrame: printHeadFrame printMemory printOop:
> +                               printStackPages printStackPageList
> printStackPagesInUse printStackPageListInUse
> +               readableFormat: readImageFromFile:HeapSize:StartingAt:
> +               setFullScreenFlag: setInterruptKeycode:
> setInterruptPending: setInterruptCheckChain:
> +                       setSavedWindowSize: success:
> +               validInstructionPointer:inMethod:framePointer:).
> +
> +       "Nice to actually have all the primitives available"
> +       requiredList addAll: (self primitiveTable select: [:each| each
> isSymbol]).
> +
> +       "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
> so make sure to keep all those"
> +       InterpreterProxy organization categories do:
> +               [:cat |
> +               ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue:
> +                       [requiredList addAll: (InterpreterProxy
> organization listAtCategoryNamed: cat)]].
> +
> +       ^requiredList!
>
> Item was changed:
>   ----- Method: StackInterpreter>>computeStackZoneSize (in category
> 'initialization') -----
>   computeStackZoneSize
>         "In C the StackPage structs live next to the actual stack pages in
> the alloca'ed stack
>          zone.  In simulation these live in some dictionary and don't
> exist in the memory."
> +       ^numStackPages * ((self cCode: [self sizeof: InterpreterStackPage]
> inSmalltalk: [0])
> -       ^numStackPages * ((self cCode: 'sizeof(StackPage)' inSmalltalk:
> [0])
>                                                 + self stackPageByteSize)
>          + stackPages extraStackBytes!
>
> Item was changed:
>   ----- Method: StackInterpreter>>functionPointerFor:inClass: (in category
> 'method lookup cache') -----
>   functionPointerFor: primIdx inClass: theClass
>         "Find an actual function pointer for this primitiveIndex.  This is
> an
>         opportunity to specialise the prim for the relevant class (format
> for
>         example).  Default for now is simply the entry in the base
> primitiveTable."
> +       <api>
> -
>         <returnTypeC: 'void (*functionPointerForinClass(sqInt
> primIdx,sqInt theClass))(void)'>
>         ^primIdx > MaxPrimitiveIndex ifTrue: [0] ifFalse: [primitiveTable
> at: primIdx]!
>
> Item was changed:
>   ----- Method: StackInterpreter>>literal:ofMethod: (in category 'compiled
> methods') -----
>   literal: offset ofMethod: methodPointer
> +       <api>
> +       ^objectMemory fetchPointer: offset + LiteralStart ofObject:
> methodPointer
> -
> -       ^ objectMemory fetchPointer: offset + LiteralStart ofObject:
> methodPointer
>   !
>
> Item was changed:
>   ----- Method: StackInterpreter>>popStack (in category 'internal
> interpreter access') -----
>   popStack
>         "In the StackInterpreter stacks grow down."
> +       <api>
>         | top |
>         <inline: true>
>         top := stackPages longAt: stackPointer.
>         stackPointer := stackPointer + BytesPerWord.
>         ^top!
>
> Item was changed:
>   ----- Method: StackInterpreter>>specialSelector: (in category 'message
> sending') -----
>   specialSelector: index
> +       <api>
> +       ^objectMemory fetchPointer: (index * 2) ofObject: (objectMemory
> splObj: SpecialSelectors)!
> -
> -       ^ objectMemory fetchPointer: (index * 2) ofObject: (objectMemory
> splObj: SpecialSelectors)!
>
> Item was changed:
>   ----- Method: StackInterpreter>>stackTop (in category 'internal
> interpreter access') -----
>   stackTop
> +       <api>
>         ^stackPages longAt: stackPointer!
>
> Item was changed:
>   ----- Method: StackInterpreter>>tempCountOf: (in category 'compiled
> methods') -----
>   tempCountOf: methodPointer
> +       <api>
>         ^self temporaryCountOfMethodHeader: (self headerOf: methodPointer)!
>
> Item was added:
> + ----- Method: StackToRegisterMappingCogit class>>ancilliaryClasses: (in
> category 'translation') -----
> + ancilliaryClasses: options
> +       ^((super ancilliaryClasses: options) copyWithout:
> CogBytecodeFixup),
> +         { CogSSBytecodeFixup. CogSimStackEntry. CogSSOptStatus }!
>
> Item was removed:
> - ----- Method: StackToRegisterMappingCogit class>>ancilliaryStructClasses
> (in category 'translation') -----
> - ancilliaryStructClasses
> -       "self ancilliaryStructClasses"
> -       ^(super ancilliaryStructClasses copyWithout: CogBytecodeFixup),
> -         { CogSSBytecodeFixup. CogSimStackEntry. CogSSOptStatus }!
>
> Item was removed:
> - ----- Method: StackToRegisterMappingCogit class>>requiredMethodNames (in
> category 'translation') -----
> - requiredMethodNames
> -       "self requiredMethodNames"
> -       ^super requiredMethodNames
> -               add: self isPushNilFunction;
> -               add: self pushNilSizeFunction;
> -               yourself!
>
> Item was added:
> + ----- Method: StackToRegisterMappingCogit class>>requiredMethodNames:
> (in category 'translation') -----
> + requiredMethodNames: options
> +       ^(super requiredMethodNames: options)
> +               add: self isPushNilFunction;
> +               add: self pushNilSizeFunction;
> +               yourself!
>
> Item was added:
> + ----- Method: ThreadedFFIPlugin class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: options
> +       ^{ self calloutStateClass }!
>
> Item was removed:
> - ----- Method: ThreadedFFIPlugin class>>ancilliaryStructClasses (in
> category 'translation') -----
> - ancilliaryStructClasses
> -       ^{ self calloutStateClass }!
>
> Item was removed:
> - ----- Method: VMClass class>>ancilliaryClasses (in category
> 'translation') -----
> - ancilliaryClasses
> -       "Answer any extra classes to be included in the translation."
> -       ^#()!
>
> Item was added:
> + ----- Method: VMClass class>>ancilliaryClasses: (in category
> 'translation') -----
> + ancilliaryClasses: optionsDictionary
> +       "Answer any extra classes to be included in the translation."
> +       ^{}!
>
> Item was removed:
> - ----- Method: VMClass class>>ancilliaryStructClasses (in category
> 'translation') -----
> - ancilliaryStructClasses
> -       ^#()!
>
> Item was removed:
> - ----- Method: VMClass class>>exportAPISelectors (in category
> 'translation') -----
> - exportAPISelectors
> -       ^self exportAPISelectorsFor: self!
>
> Item was added:
> + ----- Method: VMClass class>>exportAPISelectors: (in category
> 'translation') -----
> + exportAPISelectors: options
> +       ^self exportAPISelectorsFor: self!
>
> Item was removed:
> - ----- Method: VMClass class>>requiredMethodNames (in category
> 'translation') -----
> - requiredMethodNames
> -       "Answer a list of method names that should be retained for export
> or other
> -        support reasons.  These are typically entry-points that unless
> explicitly noted
> -        will be deleted by the code generator since it will assume these
> are not used."
> -       ^#()!
>
> Item was added:
> + ----- Method: VMClass class>>requiredMethodNames: (in category
> 'translation') -----
> + requiredMethodNames: options
> +       "Answer a list of method names that should be retained for export
> or other
> +        support reasons.  These are typically entry-points that unless
> explicitly noted
> +        will be deleted by the code generator since it will assume these
> are not used."
> +       ^#()!
>
> Item was changed:
>   ----- Method: VMMaker>>buildCodeGeneratorForCogit: (in category
> 'generate sources') -----
>   buildCodeGeneratorForCogit: getAPIMethods
>         "Answer the code generator for translating the cogit."
>
>         | cg cogitClass cogitClasses apicg |
>         cg := self createCogitCodeGenerator.
>
>         cg vmClass: (cogitClass := self cogitClass).
>         { cogitClass. self interpreterClass } do:
>                 [:cgc|
>                 (cgc respondsTo: #initializeWithOptions:)
>                         ifTrue: [cgc initializeWithOptions:
> optionsDictionary]
>                         ifFalse: [cgc initialize]].
>
>         cogitClasses := OrderedCollection new.
>         [cogitClasses addFirst: cogitClass.
>          cogitClass ~~ Cogit
>          and: [cogitClass inheritsFrom: Cogit]] whileTrue:
>                 [cogitClass := cogitClass superclass].
>         cogitClasses addFirst: VMClass.
> +       cogitClasses addAllLast: ((self cogitClass ancilliaryClasses:
> optionsDictionary) reject: [:class| class isStructClass]).
> -       cogitClasses addAllLast: self cogitClass ancilliaryClasses.
>         cogitClasses do: [:cgc| cg addClass: cgc].
>         (cg structClassesForTranslationClasses: cogitClasses) do:
>                 [:structClass| cg addStructClass: structClass].
>
>         getAPIMethods ifTrue:
>                 [apicg := self buildCodeGeneratorForInterpreter: false.
>                  cg apiMethods: apicg selectAPIMethods].
>
>         ^cg!
>
> Item was changed:
>   ----- Method: VMMaker>>buildCodeGeneratorForInterpreter: (in category
> 'generate sources') -----
>   buildCodeGeneratorForInterpreter: getAPIMethods
>         "Answer the code generator for translating the interpreter."
>
> +       | cg interpreterClass interpreterClasses apicg |
> -       | cg interpreterClass interpreterClasses structClasses apicg |
>         interpreterClasses := OrderedCollection new.
>
>         (cg := self createCodeGenerator) vmClass: (interpreterClass :=
> self interpreterClass).
>
>         [interpreterClass ~~ VMClass] whileTrue:
>                 [interpreterClasses addFirst: interpreterClass.
>                  interpreterClass := interpreterClass superclass].
>
>         cg vmClass objectMemoryClass ifNotNil:
>                 [:objectMemoryClass|
>                 interpreterClass := objectMemoryClass.
>                 [interpreterClass ~~ VMClass] whileTrue:
>                         [interpreterClasses addFirst: interpreterClass.
>                          interpreterClass := interpreterClass superclass]].
>
>         interpreterClasses addFirst: VMClass.
> +       interpreterClasses addAllLast: (((self interpreterClass
> ancilliaryClasses: optionsDictionary) reject: [:class| class
> isStructClass]) copyWithout: cg vmClass objectMemoryClass).
> +       (cg structClassesForTranslationClasses: interpreterClasses) do:
> -       interpreterClasses addAllLast: (self interpreterClass
> ancilliaryClasses copyWithout: cg vmClass objectMemoryClass).
> -       structClasses := Set new.
> -       interpreterClasses do: [:class| structClasses addAll: class
> ancilliaryStructClasses].
> -       (ChangeSet superclassOrder: structClasses asArray) do:
>                 [:structClass|
>                 structClass initialize.
>                 cg addStructClass: structClass].
>
>         interpreterClasses do:
>                 [:ic|
>                 (ic respondsTo: #initializeWithOptions:)
>                         ifTrue: [ic initializeWithOptions:
> optionsDictionary]
>                         ifFalse: [ic initialize]].
>
>         interpreterClasses do: [:ic| cg addClass: ic].
>
>         (getAPIMethods
>         and: [self interpreterClass needsCogit]) ifTrue:
>                 [apicg := self buildCodeGeneratorForCogit: false.
>                  cg apiMethods: apicg selectAPIMethods].
>
>         ^cg!
>
> Item was changed:
>   ----- Method: VMMaker>>needsToRegenerateCogitFile (in category 'generate
> sources') -----
>   needsToRegenerateCogitFile
> +       "Check the timestamp for the relevant classes and then the
> timestamp for the main source file (e.g. interp.c)
> +        file if it already exists. Answer if the file needs regenerating."
> - "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"
>
> +       | cogitClass cogitClasses tStamp |
> +       cogitClasses := (cogitClass := self cogitClass)
> withAllSuperclasses copyUpThrough: Cogit.
> +       cogitClasses addAllLast: (cogitClass ancilliaryClasses: self
> options).
> -       | cogitClass cogitClasses tStamp fstat |
> -       cogitClass := self cogitClass.
> -       cogitClasses := cogitClass withAllSuperclasses copyUpThrough:
> Cogit.
> -       cogitClasses addAllLast: cogitClass ancilliaryClasses.
>         tStamp := cogitClasses inject: 0 into: [:tS :cl| tS max: cl
> timeStamp].
> -       cogitClasses do:
> -               [:c|
> -               tStamp := c ancilliaryStructClasses inject: tStamp into:
> [:tS :cl| tS max: cl timeStamp]].
>
>         "don't translate if the file is newer than my timeStamp"
> +       (self coreVMDirectory entryAt: cogitClass sourceFileName ifAbsent:
> [nil]) ifNotNil:
> +               [:fstat|
> +               tStamp < fstat modificationTime ifTrue:
> +                       [^self confirm: 'The ', cogitClass printString, '
> classes have not been modified since\ the source file was last
> generated.\Do you still want to regenerate it?' withCRs]].
> -       fstat := self coreVMDirectory entryAt: cogitClass sourceFileName
> ifAbsent:[nil].
> -       fstat ifNotNil:[tStamp < fstat modificationTime ifTrue:
> -               [^self confirm: 'The ', cogitClass printString, ' classes
> have not been modified since\ the source file was last generated.\Do you
> still want to regenerate it?' withCRs]].
>         ^true
>   !
>
> Item was changed:
>   ----- Method: VMMaker>>needsToRegenerateInterpreterFile (in category
> 'initialize') -----
>   needsToRegenerateInterpreterFile
> +       "Check the timestamp for the relevant classes and then the
> timestamp for the main
> +        source file (e.g. interp.c) if it already exists.  Answer if the
> file needs regenerating."
> - "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"
>
> +       | classes tStamp |
> -       | classes tStamp fstat |
>         classes := self interpreterClass withAllSuperclasses copyUpTo:
> VMClass.
>         self interpreterClass objectMemoryClass ifNotNil:
>                 [:objectMemoryClass|
>                 classes addAllLast: (objectMemoryClass
>  withAllSuperclasses copyUpTo: VMClass)].
>         classes copy do:
> +               [:class| classes addAllLast: (class ancilliaryClasses:
> self options)].
> -               [:class| classes addAllLast: class ancilliaryClasses].
> -       classes copy do:
> -               [:class| classes addAllLast: class
> ancilliaryStructClasses].
>         tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].
>
>         "don't translate if the file is newer than my timeStamp"
> +       (self coreVMDirectory entryAt: self interpreterFilename ifAbsent:
> [nil]) ifNotNil:
> +               [:fstat|
> +               tStamp < fstat modificationTime ifTrue:
> +                       [^self confirm: 'The interpreter classes have not
> been modified since\ the interpreter file was last generated.\Do you still
> want to regenerate their source file?' withCRs]].
> -       fstat := self coreVMDirectory entryAt: self interpreterFilename
> ifAbsent:[nil].
> -       fstat ifNotNil:[tStamp < fstat modificationTime ifTrue:
> -               [^self confirm: 'The interpreter classes have not been
> modified since\ the interpreter file was last generated.\Do you still want
> to regenerate their source file?' withCRs]].
>         ^true
>   !
>
> Item was changed:
>   ----- Method: VMPluginCodeGenerator>>emitCTypesOn: (in category 'C code
> generator') -----
> + emitCTypesOn: aStream
> - emitCTypesOn: aStream
>         "Store local type declarations on the given stream."
> +       (self structClassesForTranslationClasses: { pluginClass }) do:
> +               [:structClass|
> +               (structClass isAbstract not
> +                and: [vmClass shouldGenerateTypedefFor: structClass])
> ifTrue:
> +                       [structClass printTypedefOn: aStream.
> +                        aStream cr; cr]]!
> -       ([pluginClass ancilliaryStructClasses]
> -               on: MessageNotUnderstood
> -               do: [:ex| ex message selector == #ancilliaryStructClasses
> ifTrue: [^self].
> -                               ex pass]) do:
> -                       [:structClass|
> -                       (pluginClass shouldGenerateTypedefFor:
> structClass) ifTrue:
> -                               [structClass printTypedefOn: aStream.
> -                                aStream cr; cr]]!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20130908/0a55f10c/attachment-0001.htm


More information about the Vm-dev mailing list