VM Maker: VMMaker.oscog-eem.2581.mcz

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

VM Maker: VMMaker.oscog-eem.2581.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2581.mcz

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

Name: VMMaker.oscog-eem.2581
Author: eem
Time: 15 November 2019, 3:36:14.08875 pm
UUID: 26e0d549-8fd4-4bee-b74d-9fbad7e8dbed
Ancestors: VMMaker.oscog-nice.2580

Add an ImageLeakChecker that is only able to load an image (currently only Spur formats have been generated and tested).  Do this with horrible Slang hackery to discard lots of stuff.  Generate validImage.c in a stack vm directory. (N.B. this hasn't been run in the simulator yet; it'll take a little bit of work to get this to work, but in teh simulator it's easy to use the inbuilt facilities in a VM via setCheckForLeaks:)

As part of this effort clean up several methods scattered around the system so that they either are marked with <api> when they're exported, or they are always inlined, or use symbols for returnTypeC:, or have the correct return type, or no longer the sole method in a category.

Slang:
Get VMMaker to respect doInlining if imolemented by an interpreter.  It used to only pay attention to a Cogit.

Enlarge and rationalize the kinds of "quick" mthods that will be inlined when doInlinign answers asSpecifiedAndQuick.  Include any and all that just answer self or a constant (i.e. include those that take arguments).  Include any and all that perform only a signle assignment, either answering the value or answering self.

Fix inlining of literal blocks vs inlining of two element statement lists created by the inliner.  Do so by introducing a subclass of TStmtListNode called TLiteralBlockNode which has one method, isLiteralBlock and is used by BlockNode>>asTranslatorNodeIn:.  Use asRootTranslatorNodeIn: to create top-level method statement lists.  Better comment collectInlineList:.

Allow comma on strings to translate into ANSI C automatic literal string concatenation.

Next step is to update the stack makefiles to build validImage executables.

=============== Diff against VMMaker.oscog-nice.2580 ===============

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation-Morphic'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
+ SystemOrganization addCategory: #'VMMaker-Utilities'!

Item was added:
+ ----- Method: BlockNode>>asRootTranslatorNodeIn: (in category '*VMMaker-C translation') -----
+ asRootTranslatorNodeIn: aTMethod
+ "Answer a TParseNode subclass equivalent of me"
+ | statementList |
+ statementList := OrderedCollection new.
+ statements do:
+ [:s | | newS |
+ newS := s asTranslatorNodeIn: aTMethod.
+ "inline the statement list returned when a CascadeNode is translated and/or when ifNotNil: is transformed"
+ newS isStmtList
+ ifTrue:  [statementList addAll: newS statements]
+ ifFalse: [statementList add: newS]].
+ ^TStmtListNode new
+ setArguments: (arguments asArray collect: [:arg | arg key])
+ statements: statementList;
+ comment: comment!

Item was changed:
  ----- Method: BlockNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  "Answer a TParseNode subclass equivalent of me"
  | statementList |
  statementList := OrderedCollection new.
  statements do:
  [:s | | newS |
  newS := s asTranslatorNodeIn: aTMethod.
  "inline the statement list returned when a CascadeNode is translated and/or when ifNotNil: is transformed"
  newS isStmtList
  ifTrue:  [statementList addAll: newS statements]
  ifFalse: [statementList add: newS]].
+ ^TLiteralBlockNode new
- ^TStmtListNode new
  setArguments: (arguments asArray collect: [:arg | arg key])
  statements: statementList;
  comment: comment!

Item was added:
+ ----- Method: CCodeGenerator>>atMostThreeBytecodeMessagesFrom: (in category 'inlining') -----
+ atMostThreeBytecodeMessagesFrom: aCompiledMethod
+ "If aCompiledMethod has two or three btecodes, then answer a sequence of the abstract bytewcode messages
+ for those bytecodes, otherwise answer nil."
+ | msgs encoderClass endpc scanner |
+ msgs := OrderedCollection new.
+ scanner := InstructionStream new method: aCompiledMethod pc: aCompiledMethod initialPC.
+ endpc  := aCompiledMethod endPC.
+ encoderClass := aCompiledMethod encoderClass.
+ [scanner pc <= endpc] whileTrue:
+ "i.e. nil will not understand any message and so the exception block will collect all of them."
+ [[encoderClass interpretNextInstructionFor: nil in: scanner]
+ on: MessageNotUnderstood
+ do: [:ex| (msgs addLast: ex message; yourself) size > 3 ifTrue: [^nil]]].
+ ^msgs!

Item was changed:
  ----- Method: CCodeGenerator>>collectInlineList: (in category 'inlining') -----
  collectInlineList: inlineFlagOrSymbol
+ "Make a list of methods that should be inlined.
+ If inlineFlagOrSymbol == false, inline nothing.
+ If inlineFlagOrSymbol == #asSpecified include methods marked with <inline: true>, and <inline: #always>.
+ If inlineFlagOrSymbol == #asSpecifiedOrQuick include methods marked with <inline: true>, and <inline: #always>,
+ and methods that are quick (^constant, ^inst var).
+ If inlineFlagOrSymbol == true include methods marked with <inline: true>, and <inline: #always>,
+ and methods with 40 parse nodes or fewer."
+
- "Make a list of methods that should be inlined.  If inlineFlagOrSymbol == #asSpecified
- only inline methods marked with <inline: true>.  If inlineFlagOrSymbol == #asSpecifiedOrQuick
- only inline methods marked with <inline: true> or methods that are quick (^constant, ^inst var)."
  "Details: The method must not include any inline C, since the
  translator cannot currently map variable names in inlined C code.
  Methods to be inlined must be small or called from only one place."
 
  | selectorsOfMethodsNotToInline callsOf |
  self assert: (#(true false asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol).
  selectorsOfMethodsNotToInline := Set new: methods size.
  selectorsOfMethodsNotToInline addAll: macros keys.
  apiMethods ifNotNil:
  [selectorsOfMethodsNotToInline addAll: apiMethods keys].
  methods do:
  [:m|
  m isStructAccessor ifTrue:
  [selectorsOfMethodsNotToInline add: m selector]].
 
  "build dictionary to record the number of calls to each method"
  callsOf := Dictionary new: methods size * 2.
  methods keysAndValuesDo:
  [:s :m|
  (m isRealMethod
  and: [self shouldGenerateMethod: m]) ifTrue:
  [callsOf at: s put: 0]].
 
  "For each method, scan its parse tree once or twice to:
  1. determine if the method contains unrenamable C code or declarations or has a C builtin
  2. determine how many nodes it has
  3. increment the sender counts of the methods it calls"
  inlineList := Set new: methods size * 2.
  (methods reject: [:m| selectorsOfMethodsNotToInline includes: m selector]) do:
  [:m| | inlineIt hasUnrenamableCCode nodeCount |
  ((breakSrcInlineSelectors includes: m selector)
  and: [breakOnInline isNil]) ifTrue:
  [self halt].
  inlineIt := #dontCare.
  (translationDict includesKey: m selector)
  ifTrue: [hasUnrenamableCCode := true]
  ifFalse:
  [hasUnrenamableCCode := m hasUnrenamableCCode.
  nodeCount := 0.
  m parseTree nodesDo:
  [:node|
  node isSend ifTrue:
  [callsOf
  at: node selector
  ifPresent:
  [:senderCount| callsOf at: node selector put: senderCount + 1]].
  nodeCount := nodeCount + 1].
  inlineIt := m extractInlineDirective].  "may be true, false, #always, #never or #dontCare"
  (hasUnrenamableCCode or: [inlineIt == false])
  ifTrue: "don't inline if method has C code or contains negative inline directive"
  [inlineIt == true ifTrue:
  [logger
  ensureCr;
  nextPutAll: 'failed to inline ';
  nextPutAll: m selector;
  nextPutAll: ' as it contains unrenamable C declarations or C code';
  cr; flush].
  selectorsOfMethodsNotToInline add: m selector]
  ifFalse:
  [(inlineFlagOrSymbol caseOf: {
  [#asSpecified] -> [inlineIt == true].
  [#asSpecifiedOrQuick] -> [inlineIt == true
  or: [self isQuickCompiledMethod: m compiledMethod]].
  [true] -> [nodeCount < 40 or: [inlineIt == true]].
  [false] -> [false]})
  ifTrue: "inline if method has no C code and is either small or contains inline directive"
  [inlineList add: m selector]
  ifFalse:
  [(#(asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol) ifTrue:
  [selectorsOfMethodsNotToInline add: m selector]]]].
 
  (#(asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol)
  ifTrue:
  [methods do: [:m| m inline ifNil: [m inline: (inlineList includes: m selector)]]]
  ifFalse:
  [callsOf associationsDo:
  [:assoc|
  (assoc value = 1
  and: [(selectorsOfMethodsNotToInline includes: assoc key) not]) ifTrue:
  [inlineList add: assoc key]]]!

Item was added:
+ ----- Method: CCodeGenerator>>generateComma:on:indent: (in category 'C translation') -----
+ generateComma: msgNode on: aStream indent: level
+ "Generate the C code for this message onto the given stream.
+ Assume that the arguments are literal strings"
+ self emitCExpression: msgNode receiver on: aStream.
+ aStream space.
+ self emitCExpression: msgNode args first on: aStream!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation support') -----
  initializeCTranslationDictionary
  "Initialize the dictionary mapping message names to actions for C code generation."
 
  | pairs |
 
  translationDict := Dictionary new: 200.
  pairs := #(
  #& #generateAnd:on:indent:
  #| #generateOr:on:indent:
  #abs #generateAbs:on:indent:
  #and: #generateSequentialAnd:on:indent:
  #or: #generateSequentialOr:on:indent:
  #not #generateNot:on:indent:
 
  #+ #generatePlus:on:indent:
  #- #generateMinus:on:indent:
  #negated #generateNegated:on:indent:
  #* #generateTimes:on:indent:
  #/ #generateDivide:on:indent:
  #// #generateDivide:on:indent:
  #\\ #generateModulo:on:indent:
  #<< #generateShiftLeft:on:indent:
  #>> #generateShiftRight:on:indent:
  #>>> #generateSignedShiftRight:on:indent:
+ #, #generateComma:on:indent:
  #min: #generateMin:on:indent:
  #max: #generateMax:on:indent:
  #between:and: #generateBetweenAnd:on:indent:
 
  #bitAnd: #generateBitAnd:on:indent:
  #bitOr: #generateBitOr:on:indent:
  #bitXor: #generateBitXor:on:indent:
  #bitShift: #generateBitShift:on:indent:
  #signedBitShift: #generateSignedBitShift:on:indent:
  #bitInvert32 #generateBitInvert:on:indent:
  #bitInvert64 #generateBitInvert:on:indent:
  #bitClear: #generateBitClear:on:indent:
  #truncateTo: #generateTruncateTo:on:indent:
  #rounded #generateRounded:on:indent:
 
  #byteSwap32 #generateByteSwap32:on:indent:
  #byteSwap64 #generateByteSwap64:on:indent:
  #byteSwapped32IfBigEndian: generateByteSwap32IfBigEndian:on:indent:
  #byteSwapped64IfBigEndian: generateByteSwap64IfBigEndian:on:indent:
 
  #< #generateLessThan:on:indent:
  #<= #generateLessThanOrEqual:on:indent:
  #= #generateEqual:on:indent:
  #> #generateGreaterThan:on:indent:
  #>= #generateGreaterThanOrEqual:on:indent:
  #~= #generateNotEqual:on:indent:
  #== #generateEqual:on:indent:
  #~~ #generateNotEqual:on:indent:
  #isNil #generateIsNil:on:indent:
  #notNil #generateNotNil:on:indent:
 
  #whileTrue: #generateWhileTrue:on:indent:
  #whileFalse: #generateWhileFalse:on:indent:
  #whileTrue #generateDoWhileTrue:on:indent:
  #whileFalse #generateDoWhileFalse:on:indent:
  #to:do: #generateToDo:on:indent:
  #to:by:do: #generateToByDo:on:indent:
  #repeat #generateRepeat:on:indent:
  #timesRepeat: #generateTimesRepeat:on:indent:
 
  #ifTrue: #generateIfTrue:on:indent:
  #ifFalse: #generateIfFalse:on:indent:
  #ifTrue:ifFalse: #generateIfTrueIfFalse:on:indent:
  #ifFalse:ifTrue: #generateIfFalseIfTrue:on:indent:
 
  #ifNotNil: #generateIfNotNil:on:indent:
  #ifNil: #generateIfNil:on:indent:
  #ifNotNil:ifNil: #generateIfNotNilIfNil:on:indent:
  #ifNil:ifNotNil: #generateIfNilIfNotNil:on:indent:
 
  #at: #generateAt:on:indent:
  #at:put: #generateAtPut:on:indent:
  #basicAt: #generateAt:on:indent:
  #basicAt:put: #generateAtPut:on:indent:
 
  #integerValueOf: #generateIntegerValueOf:on:indent:
  #integerObjectOf: #generateIntegerObjectOf:on:indent:
  #isIntegerObject: #generateIsIntegerObject:on:indent:
  #cCode: #generateInlineCCode:on:indent:
  #cCode:inSmalltalk: #generateInlineCCode:on:indent:
  #cPreprocessorDirective: #generateInlineCPreprocessorDirective:on:indent:
  #cppIf:ifTrue:ifFalse: #generateInlineCppIfElse:on:indent:
  #cppIf:ifTrue: #generateInlineCppIfElse:on:indent:
  #cCoerce:to: #generateCCoercion:on:indent:
  #cCoerceSimple:to: #generateCCoercion:on:indent:
  #addressOf: #generateAddressOf:on:indent:
  #addressOf:put: #generateAddressOf:on:indent:
  #asAddress:put: #generateAsAddress:on:indent:
  #signedIntFromLong64 #generateSignedIntFromLong64:on:indent:
  #signedIntFromLong #generateSignedIntFromLong:on:indent:
  #signedIntFromShort #generateSignedIntFromShort:on:indent:
  #signedIntToLong64 #generateSignedIntToLong64:on:indent:
  #signedIntToLong #generateSignedIntToLong:on:indent:
  #signedIntToShort #generateSignedIntToShort:on:indent:
  #preIncrement #generatePreIncrement:on:indent:
  #preDecrement #generatePreDecrement:on:indent:
  #inline: #generateInlineDirective:on:indent:
  #asFloat #generateAsFloat:on:indent:
  #asInteger #generateAsInteger:on:indent:
  #asIntegerPtr #generateAsIntegerPtr:on:indent:
  #asUnsignedInteger #generateAsUnsignedInteger:on:indent:
  #asUnsignedIntegerPtr #generateAsUnsignedIntegerPtr:on:indent:
  #asLong #generateAsLong:on:indent:
  #asUnsignedLong #generateAsUnsignedLong:on:indent:
  #asUnsignedLongLong #generateAsUnsignedLongLong:on:indent:
  #asVoidPointer #generateAsVoidPointer:on:indent:
  #asSymbol #generateAsSymbol:on:indent:
  #flag: #generateFlag:on:indent:
  #anyMask: #generateBitAnd:on:indent:
  #allMask: #generateAllMask:on:indent:
  #noMask: #generateNoMask:on:indent:
  #raisedTo: #generateRaisedTo:on:indent:
  #touch: #generateTouch:on:indent:
 
  #bytesPerOop #generateBytesPerOop:on:indent:
  #bytesPerWord #generateBytesPerWord:on:indent:
  #wordSize #generateBytesPerWord:on:indent:
  #baseHeaderSize #generateBaseHeaderSize:on:indent:
  #minSmallInteger #generateSmallIntegerConstant:on:indent:
  #maxSmallInteger #generateSmallIntegerConstant:on:indent:
 
  #sharedCodeNamed:inCase: #generateSharedCodeDirective:on:indent:
 
  #perform: #generatePerform:on:indent:
  #perform:with: #generatePerform:on:indent:
  #perform:with:with: #generatePerform:on:indent:
  #perform:with:with:with: #generatePerform:on:indent:
  #perform:with:with:with:with: #generatePerform:on:indent:
  #perform:with:with:with:with:with: #generatePerform:on:indent:
 
  #value #generateValue:on:indent:
  #value: #generateValue:on:indent:
  #value:value: #generateValue:on:indent:
  #value:value:value: #generateValue:on:indent:
  #value:value:value:value: #generateValue:on:indent:
  #value:value:value:value:value: #generateValue:on:indent:
  #value:value:value:value:value:value: #generateValue:on:indent:
 
  #deny: #generateDeny:on:indent:
 
  #shouldNotImplement #generateSmalltalkMetaError:on:indent:
  #shouldBeImplemented #generateSmalltalkMetaError:on:indent:
  #subclassResponsibility #generateSmalltalkMetaError:on:indent:
  ).
 
  1 to: pairs size by: 2 do: [:i |
  translationDict at: (pairs at: i) put: (pairs at: i + 1)].
 
  pairs := #(
  #ifTrue: #generateIfTrueAsArgument:on:indent:
  #ifFalse: #generateIfFalseAsArgument:on:indent:
  #ifTrue:ifFalse: #generateIfTrueIfFalseAsArgument:on:indent:
  #ifFalse:ifTrue: #generateIfFalseIfTrueAsArgument:on:indent:
  #ifNotNil: #generateIfNotNilAsArgument:on:indent:
  #ifNil: #generateIfNilAsArgument:on:indent:
  #ifNotNil:ifNil: #generateIfNotNilIfNilAsArgument:on:indent:
  #ifNil:ifNotNil: #generateIfNilIfNotNilAsArgument:on:indent:
  #cCode: #generateInlineCCodeAsArgument:on:indent:
  #cCode:inSmalltalk: #generateInlineCCodeAsArgument:on:indent:
  #cppIf:ifTrue:ifFalse: #generateInlineCppIfElseAsArgument:on:indent:
  #cppIf:ifTrue: #generateInlineCppIfElseAsArgument:on:indent:
 
  #value #generateValueAsArgument:on:indent:
  #value: #generateValueAsArgument:on:indent:
  #value:value: #generateValueAsArgument:on:indent:
  ).
 
  asArgumentTranslationDict := Dictionary new: 8.
  1 to: pairs size by: 2 do: [:i |
  asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: CCodeGenerator>>isQuickCompiledMethod: (in category 'inlining') -----
  isQuickCompiledMethod: aCompiledMethod
+ "Answer methods that returen a constant or an instance variable, or assign an instance variable."
+ aCompiledMethod isQuick ifTrue:
+ [^true].
+ (self atMostThreeBytecodeMessagesFrom: aCompiledMethod) ifNotNil:
+ [:messages| | s1 sz |
+ (#(methodReturnReceiver methodReturnConstant:) includes: (s1 := messages first selector)) ifTrue:
+ [^true].
+ ((sz := messages size) = 2
+ and: [(#(pushConstant: pushLiteralVariable:) includes: s1)
+ and: [messages second selector == #methodReturnTop]]) ifTrue:
+ [^true].
+ (aCompiledMethod numArgs = 1
+  and: [sz = 3
+  and: [(s1 = #pushTemporaryVariable: and: [messages first argument = 0])
+  and: [(#(popIntoReceiverVariable: storeIntoReceiverVariable:) includes: messages second selector)
+  and: [#(methodReturnReceiver methodReturnTop) includes: messages third selector]]]]) ifTrue:
+ [^true]].
+ ^false!
- ^aCompiledMethod isQuick
- or: [(#(pushConstant: pushLiteralVariable:) includes: (aCompiledMethod abstractBytecodeMessageAt: aCompiledMethod initialPC) selector)
- and: [(aCompiledMethod abstractBytecodeMessageAt: (InstructionStream on: aCompiledMethod) followingPc) selector == #methodReturnTop]]!

Item was added:
+ StackInterpreter subclass: #ImageLeakChecker
+ instanceVariableNames: 'verbose'
+ classVariableNames: ''
+ poolDictionaries: 'VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices'
+ category: 'VMMaker-Utilities'!
+
+ !ImageLeakChecker commentStamp: 'eem 11/15/2019 15:11' prior: 0!
+ An ImageLeakChecker loads an image and runs the leak checker, answering true if there are no leaks.  When used stand alone it takes one argument, --verbose, which if set causes the ImageLeakChecker to print information on each leak.
+
+ Instance Variables
+ verbose <Boolean> whether to print details, or simply to answer an exist status.!

Item was added:
+ ----- Method: ImageLeakChecker class>>additionalHeadersDo: (in category 'translation') -----
+ additionalHeadersDo: aBinaryBlock
+ "Nothing to do here. These are not the droids you are looking for..."!

Item was added:
+ ----- Method: ImageLeakChecker class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ self declareInterpreterVersionIn: aCCodeGenerator defaultName: 'ImageChecker'.
+ aCCodeGenerator
+ var: #interpreterProxy  type: #'struct VirtualMachine*'.
+ "Do this to avoid redefining interp.h when we generate the image checker.  i.e. agree with StackInterpereter class's version above."
+ aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
+ #('checkAllocFiller' 'primitiveTable' 'primitiveAccessorDepthTable' 'stackPages') do:
+ [:surplus| aCCodeGenerator removeVariable: surplus]!

Item was added:
+ ----- Method: ImageLeakChecker class>>doInlining (in category 'translation') -----
+ doInlining
+ ^#asSpecifiedOrQuick!

Item was added:
+ ----- Method: ImageLeakChecker class>>isAcceptableAncilliaryClass: (in category 'translation') -----
+ isAcceptableAncilliaryClass: aClass
+ ^aClass == CogStackPage or: [self objectMemoryClass ancilliaryClasses includes: aClass]!

Item was added:
+ ----- Method: ImageLeakChecker class>>namesOfVariablesToLocalize (in category 'translation') -----
+ namesOfVariablesToLocalize
+ ^#()!

Item was added:
+ ----- Method: ImageLeakChecker class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGen
+ "Attempt to nuke everything we don't need in our hierarchy.  We will leave the
+ pruning of most of methods in the memory manager hierarchy to the code generator."
+ | interpreterSelectors toBeRemoved |
+ toBeRemoved := Set withAll: (interpreterSelectors := StackInterpreter selectors, InterpreterPrimitives selectors).
+
+ "Now make sure we *don't* remove any of the following.  These we need."
+ {self selectors.
+  #(addressCouldBeClassObj: checkAssumedCompactClasses fetchStackPointerOf:
+ highBit: is:KindOfClass: includesBehavior:ThatOf: initializeExtraClassInstVarIndices initializeInterpreter:
+ literalCountOfAlternateHeader: maybeSelectorOfMethod: maybeFixClonedCompiledMethod:
+ objCouldBeClassObj: primitiveFail primitiveFailFor: successful superclassOf:).
+  (StackInterpreter methodsInCategory: #'debug printing') reject:
+ [:s1| #('Context' 'Frame' 'Proc' "Procs and Process" 'Stack') anySatisfy: [:s2| s1 includesSubstring: s2]].
+  StackInterpreter methodsInCategory: #'compiled methods'.
+  StackInterpreter methodsInCategory: #'frame access'.
+  StackInterpreter methodsInCategory: #'image save/restore'.
+ interpreterSelectors select: [:s| s includesSubstring: 'Alien'].
+ "the ^self methods are usually no-op stubs overridden in CoInterpreter; we want these."
+  interpreterSelectors select: [:s| ((StackInterpreter whichClassIncludesSelector: s) >> s) isReturnSelf].
+  "And include all the isFoo methods..."
+  interpreterSelectors select: [:s| s size > 2 and: [(s beginsWith: 'is') and: [s third isUppercase]]]} do:
+ [:selectors|
+ toBeRemoved removeAll: (selectors intersection: toBeRemoved)].
+
+ "These we explicitly prune; they're used by InterpreterProxy and/or the Cogit and/or pieces of machinery we don't want"
+ toBeRemoved addAll: #(indexOf:in: instantiateClass:indexableSize: integerValueOf:
+ maybeMethodClassOf:seemsToBeInstantiating: remapObj:).
+
+ aCCodeGen pruneMethods: toBeRemoved.
+ aCCodeGen sortedExportMethods do:
+ [:tm| tm export: false]!

Item was added:
+ ----- Method: ImageLeakChecker class>>preambleCCode (in category 'translation') -----
+ preambleCCode
+
+ "readImageFromFile:HeapSizeStartingAt is declared public in sq.h, so it has to be exported,
+ but some weird bug with clang clang-1000.11.45.5 makes it complian that _m is undecared in this:
+
+ static char _m[] = "";
+ void* vm_exports[][3] = {
+    {(void*)_m, ''readImageFromFileHeapSizeStartingAt'', (void*)readImageFromFileHeapSizeStartingAt},
+    {NULL, NULL, NULL}
+ };
+
+ so we hack around it by redefining readImageFromFileHeapSizeStartingAt after sq.h is included and keep
+ our version of it private, and hence have no exports, avoiding generating the offending code above."
+
+ ^super preambleCCode,
+ ('\#define readImageFromFileHeapSizeStartingAt readImageFromFile\',
+ '\void error(char *msg) {\  warning(msg);\  abort();\}\\') withCRs!

Item was added:
+ ----- Method: ImageLeakChecker class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
+ prepareToBeAddedToCodeGenerator: aCodeGen
+ aCodeGen
+ removeMethodForSelector: #become:with:;
+ removeMethodForSelector: #fullGC;
+ removeMethodForSelector: #growOldSpaceByAtLeast:;
+ removeMethodForSelector: #runLeakCheckerFor:;
+ removeMethodForSelector: #runLeakCheckerForFreeSpace:;
+ removeMethodForSelector: #runLeakCheckerFor:excludeUnmarkedObjs:classIndicesShouldBeValid:;
+ removeMethodForSelector: #inLineRunLeakCheckerFor:excludeUnmarkedObjs:classIndicesShouldBeValid:;
+ removeMethodForSelector: #scheduleScavenge;
+ removeMethodForSelector: #tenuringIncrementalGC!

Item was added:
+ ----- Method: ImageLeakChecker class>>requiredMethodNames: (in category 'translation') -----
+ requiredMethodNames: options
+ "Answer the list of method names that should be retained for export or other support reasons"
+ ^#(#'main:_:')!

Item was added:
+ ----- Method: ImageLeakChecker class>>sourceFileName (in category 'translation') -----
+ sourceFileName
+ "Answer the filename for the core interpreter"
+
+ ^'validImage.c'!

Item was added:
+ ----- Method: ImageLeakChecker>>asCommandLineArgument: (in category 'implementation') -----
+ asCommandLineArgument: aString
+ <inline: #always>
+ ^PharoVM ifTrue: ['--', aString] ifFalse: ['-', aString]!

Item was added:
+ ----- Method: ImageLeakChecker>>checkAllocFiller (in category 'no-op overrides') -----
+ checkAllocFiller
+ <inline: #always>
+ ^false!

Item was added:
+ ----- Method: ImageLeakChecker>>couldBeFramePointer: (in category 'no-op overrides') -----
+ couldBeFramePointer: fp
+ <var: #pointer type: #'void *'>
+ <inline: #always>
+ ^false!

Item was added:
+ ----- Method: ImageLeakChecker>>cr (in category 'printing') -----
+ cr
+ verbose ifTrue: [super cr]!

Item was added:
+ ----- Method: ImageLeakChecker>>defaultNumStackPages (in category 'no-op overrides') -----
+ defaultNumStackPages
+ ^0!

Item was added:
+ ----- Method: ImageLeakChecker>>dummyReferToProxy (in category 'no-op overrides') -----
+ dummyReferToProxy!

Item was added:
+ ----- Method: ImageLeakChecker>>fireEphemeron: (in category 'no-op overrides') -----
+ fireEphemeron: ephemeron!

Item was added:
+ ----- Method: ImageLeakChecker>>fireFinalization: (in category 'no-op overrides') -----
+ fireFinalization: thing!

Item was added:
+ ----- Method: ImageLeakChecker>>freeUntracedStackPages (in category 'no-op overrides') -----
+ freeUntracedStackPages!

Item was added:
+ ----- Method: ImageLeakChecker>>growOldSpaceByAtLeast: (in category 'implementation') -----
+ growOldSpaceByAtLeast: minAmmount
+ self error: 'growOldSpaceByAtLeast: was invoked; should not happen!!'.
+ ^false!

Item was added:
+ ----- Method: ImageLeakChecker>>initStackPageGC (in category 'no-op overrides') -----
+ initStackPageGC!

Item was added:
+ ----- Method: ImageLeakChecker>>initialCleanup (in category 'no-op overrides') -----
+ initialCleanup!

Item was added:
+ ----- Method: ImageLeakChecker>>initialize (in category 'initialization') -----
+ initialize
+ verbose := false!

Item was added:
+ ----- Method: ImageLeakChecker>>interpreterAllocationReserveBytes (in category 'no-op overrides') -----
+ interpreterAllocationReserveBytes
+ ^0!

Item was added:
+ ----- Method: ImageLeakChecker>>ioExitWithErrorCode: (in category 'api') -----
+ ioExitWithErrorCode: ec
+ <inline: true>
+ self exit: ec!

Item was added:
+ ----- Method: ImageLeakChecker>>ioLoadFunction:From: (in category 'no-op overrides') -----
+ ioLoadFunction: functionName From: moduleName
+ <api>
+ <returnTypeC: #'void *'>
+ <var: #functionName type: #'char *'>
+ <var: #moduleName type: #'char *'>
+ ^nil!

Item was added:
+ ----- Method: ImageLeakChecker>>ioMSecs (in category 'implementation') -----
+ ioMSecs
+ ^1!

Item was added:
+ ----- Method: ImageLeakChecker>>isFree: (in category 'no-op overrides') -----
+ isFree: thePage
+ <var: 'thePage' type: #'StackPage *'>
+ ^true!

Item was added:
+ ----- Method: ImageLeakChecker>>main:_: (in category 'api') -----
+ main: argc _: argv
+ <var: 'argc' type: #int>
+ <var: 'argv' declareC: 'char *argv[]'>
+ <returnTypeC: #int>
+ <api>
+ | argi ifh ok |
+ <var: 'ifh' type: #'FILE *'>
+ argi := 1.
+ (argc >= 2
+ and: [(self strcmp: (self asCommandLineArgument: 'verbose') _: (argv at: argi)) = 0]) ifTrue:
+ [verbose := true.
+ argi := argi + 1].
+
+ (argc ~= (argi + 1)
+ or: [(ifh := self sqImageFileOpen: (argv at: argi) _: 'rb') = 0]) ifTrue:
+ ['Usage: %s [%s] imageFileName\n' printf: {(argv at: 0). self asCommandLineArgument: 'verbose'}.
+ ^self cCode: [1] inSmalltalk: [false]].
+
+ self readImageFromFile: ifh HeapSize: 0 StartingAt: 0.
+ self sqImageFileClose: ifh.
+ ok := objectMemory runLeakCheckerForResult: GCModeFull.
+ (verbose and: [ok]) ifTrue:
+ ['Image %s is free of leaks\n' printf: {(argv at: argi)}].
+ ^self cCode: [ok ifTrue: [0] ifFalse: [2]] inSmalltalk: [ok]!

Item was added:
+ ----- Method: ImageLeakChecker>>mapInterpreterOops (in category 'no-op overrides') -----
+ mapInterpreterOops!

Item was added:
+ ----- Method: ImageLeakChecker>>markAndTraceAndMaybeFreeStackPages: (in category 'no-op overrides') -----
+ markAndTraceAndMaybeFreeStackPages: fullGCFlag!

Item was added:
+ ----- Method: ImageLeakChecker>>markAndTraceInterpreterOops: (in category 'no-op overrides') -----
+ markAndTraceInterpreterOops: fullGCFlag!

Item was added:
+ ----- Method: ImageLeakChecker>>markAndTraceUntracedReachableStackPages (in category 'no-op overrides') -----
+ markAndTraceUntracedReachableStackPages!

Item was added:
+ ----- Method: ImageLeakChecker>>mostRecentlyUsedPage (in category 'no-op overrides') -----
+ mostRecentlyUsedPage
+ <returnTypeC: #'StackPage *'>
+ <inline: #always>
+ ^nil!

Item was added:
+ ----- Method: ImageLeakChecker>>plugInNotifyUser: (in category 'api') -----
+ plugInNotifyUser: msg
+ "This is used in macros in sq.h, sigh..."
+ <api>
+ <returnTypeC: #int>
+ <var: 'msg' type: #'char *'>
+ self error: msg!

Item was added:
+ ----- Method: ImageLeakChecker>>postBecomeAction: (in category 'no-op overrides') -----
+ postBecomeAction: theBecomeEffectsFlags!

Item was added:
+ ----- Method: ImageLeakChecker>>postGCAction: (in category 'no-op overrides') -----
+ postGCAction: gcModeArg!

Item was added:
+ ----- Method: ImageLeakChecker>>preBecomeAction (in category 'no-op overrides') -----
+ preBecomeAction!

Item was added:
+ ----- Method: ImageLeakChecker>>preGCAction: (in category 'no-op overrides') -----
+ preGCAction: gcModeArg!

Item was added:
+ ----- Method: ImageLeakChecker>>print: (in category 'printing') -----
+ print: s
+ verbose ifTrue: [super print: s]!

Item was added:
+ ----- Method: ImageLeakChecker>>printHex: (in category 'printing') -----
+ printHex: n
+ verbose ifTrue: [super printHex: n]!

Item was added:
+ ----- Method: ImageLeakChecker>>printNum: (in category 'printing') -----
+ printNum: n
+ verbose ifTrue: [super printNum: n]!

Item was added:
+ ----- Method: ImageLeakChecker>>runLeakCheckerFor: (in category 'no-op overrides') -----
+ runLeakCheckerFor: gcModes!

Item was added:
+ ----- Method: ImageLeakChecker>>runLeakCheckerFor:excludeUnmarkedObjs:classIndicesShouldBeValid: (in category 'no-op overrides') -----
+ runLeakCheckerFor: gcModes excludeUnmarkedObjs: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid!

Item was added:
+ ----- Method: ImageLeakChecker>>runLeakCheckerForFreeSpace: (in category 'implementation') -----
+ runLeakCheckerForFreeSpace: gcModes!

Item was added:
+ ----- Method: ImageLeakChecker>>runLeakCheckerForResult: (in category 'implementation') -----
+ runLeakCheckerForResult: gcModes
+ objectMemory clearLeakMapAndMapAccessibleObjects.
+ ^objectMemory checkHeapIntegrity: true classIndicesShouldBeValid: true!

Item was added:
+ ----- Method: ImageLeakChecker>>scheduleScavenge (in category 'no-op overrides') -----
+ scheduleScavenge!

Item was added:
+ ----- Method: ImageLeakChecker>>setMaxExtSemSizeTo: (in category 'no-op overrides') -----
+ setMaxExtSemSizeTo: maxExtSemTabSize!

Item was added:
+ ----- Method: ImageLeakChecker>>setTraceFlagOnContextsFramesPageIfNeeded: (in category 'no-op overrides') -----
+ setTraceFlagOnContextsFramesPageIfNeeded: aContext!

Item was added:
+ ----- Method: ImageLeakChecker>>sqGetInterpreterProxy (in category 'no-op overrides') -----
+ sqGetInterpreterProxy
+ <returnTypeC: 'struct VirtualMachine *'>
+ ^nil!

Item was added:
+ ----- Method: ImageLeakChecker>>stackLimitOffset (in category 'no-op overrides') -----
+ stackLimitOffset
+ ^0!

Item was added:
+ ----- Method: ImageLeakChecker>>stackPageAt: (in category 'no-op overrides') -----
+ stackPageAt: index
+ <returnTypeC: #'StackPage *'>
+ <inline: #always>
+ ^nil!

Item was added:
+ ----- Method: ImageLeakChecker>>stackPageFor: (in category 'no-op overrides') -----
+ stackPageFor: pointer
+ <returnTypeC: #'StackPage *'>
+ <var: #pointer type: #'void *'>
+ <inline: #always>
+ ^nil!

Item was added:
+ ----- Method: ImageLeakChecker>>whereIsMaybeStackThing: (in category 'no-op overrides') -----
+ whereIsMaybeStackThing: thing
+ <returnTypeC: #'char *'>
+ ^nil!

Item was changed:
  ----- 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: getCurrentBytecode characterForAscii: findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver: loadInitialContext nullCompilerHook primitiveFlushExternalPrimitives setCompilerInitialized: getFullScreenFlag getInterruptCheckCounter getInterruptKeycode getInterruptPending getNextWakeupTick getSavedWindowSize setFullScreenFlag: setInterruptCheckCounter: setInterruptKeycode: setInterruptPending: setNextWakeupTick: setSavedWindowSize: forceInterruptCheck getThisSessionID).
- 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: Interpreter>>readableFormat: (in category 'image save/restore') -----
  readableFormat: imageVersion
  "Anwer true if images of the given format are readable by this interpreter. Allows a virtual machine to accept selected older image formats."
+ <api>
-
  ^ imageVersion = self imageFormatVersion
  or: [imageVersion = self imageFormatCompatibilityVersion]
  "
  Example of multiple formats:
  ^ (imageVersion = self imageFormatVersion) or: [imageVersion = 6504]
  "!

Item was changed:
  ----- Method: InterpreterProxy>>floatValueOf: (in category 'converting') -----
  floatValueOf: oop
+ <returnTypeC: #double>
- <returnTypeC:'double'>
  oop isFloat
  ifTrue:[^oop]
  ifFalse:[self primitiveFail. ^0.0].!

Item was changed:
  ----- Method: NewObjectMemory>>floatValueOf: (in category 'interpreter access') -----
  floatValueOf: oop
  "Answer the C double precision floating point value of the argument,
  or fail if it is not a Float, and answer 0.
  Note: May be called by translated primitive code."
+ <api>
-
- | isFloat result |
  <returnTypeC: #double>
+ | isFloat result |
  <var: #result type: #double>
  isFloat := self isFloatInstance: oop.
  isFloat ifTrue:
  [self cCode: '' inSmalltalk: [result := Float new: 2].
  self fetchFloatAt: oop + self baseHeaderSize into: result.
  ^result].
  coInterpreter primitiveFail.
  ^0.0!

Item was changed:
  ----- Method: ObjectMemory>>floatValueOf: (in category 'interpreter access') -----
  floatValueOf: oop
  "Answer the C double precision floating point value of the argument,
  or fail if it is not a Float, and answer 0.
  Note: May be called by translated primitive code."
+ <api>
-
- | isFloat result |
  <returnTypeC: #double>
+ | isFloat result |
  <var: #result type: #double>
  isFloat := self isFloatInstance: oop.
  isFloat ifTrue:
  [self cCode: '' inSmalltalk: [result := Float new: 2].
  self fetchFloatAt: oop + self baseHeaderSize into: result.
  ^result].
  self primitiveFail.
  ^0.0!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initialization') -----
  setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
  "Initialize this method using the given information."
 
  selector := sel.
  definingClass := class.
  returnType := #sqInt. "assume return type is sqInt for now"
  args := argList asOrderedCollection collect: [:arg | arg key].
  locals := (localList collect: [:arg | arg key]) asSet.
  declarations := Dictionary new.
  primitive := aNumber.
  properties := methodProperties.
  comment := aComment.
+ parseTree := aBlockNode asRootTranslatorNodeIn: self.
- parseTree := aBlockNode asTranslatorNodeIn: self.
  labels := Set new.
  complete := false.  "set to true when all possible inlining has been done"
  export := self extractExportDirective.
  static := self extractStaticDirective.
  self extractSharedCase.
  isPrimitive := false.  "set to true only if you find a primtive direction."
  self recordDeclarationsIn: CCodeGenerator basicNew. "Just for conventionalTypeForType:"
  self extractPrimitiveDirectives.
  !

Item was changed:
  ----- Method: Spur32BitMemoryManager>>floatValueOf: (in category 'interpreter access') -----
  floatValueOf: oop
  "Answer the C double precision floating point value of the argument,
  or fail if it is not a Float, and answer 0.
  Note: May be called by translated primitive code."
+ <api>
-
- | isFloat result |
  <returnTypeC: #double>
+ | isFloat result |
  <var: #result type: #double>
  isFloat := self isFloatInstance: oop.
  isFloat ifTrue:
  [self cCode: '' inSmalltalk: [result := Float new: 2].
  self fetchFloatAt: oop + self baseHeaderSize into: result.
  ^result].
  coInterpreter primitiveFail.
  ^0.0!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>floatValueOf: (in category 'interpreter access') -----
  floatValueOf: oop
  "Answer the C double precision floating point value of the argument,
  or fail if it is not a Float, and answer 0.
  Note: May be called by translated primitive code."
+ <api>
-
- | result tagBits |
  <returnTypeC: #double>
+ | result tagBits |
  <var: #result type: #double>
  (tagBits := oop bitAnd: self tagMask) ~= 0
  ifTrue:
  [tagBits = self smallFloatTag ifTrue:
  [^self smallFloatValueOf: oop]]
  ifFalse:
  [(self classIndexOf: oop) = ClassFloatCompactIndex ifTrue:
  [self cCode: '' inSmalltalk: [result := Float new: 2].
  self fetchFloatAt: oop + self baseHeaderSize into: result.
  ^result]].
  coInterpreter primitiveFail.
  ^0.0!

Item was changed:
  ----- Method: SpurGenerationScavenger>>edenBytes (in category 'accessing') -----
  edenBytes
+ <inline: #always>
  ^eden limit - eden start!

Item was changed:
  ----- Method: SpurGenerationScavenger>>nextCorpseOffset: (in category 'weakness and ephemerality') -----
  nextCorpseOffset: corpse
  "Answer the offset of the next corpse to corpse, which is zero if none.
  Use the identityHash and format fields to construct a 27 bit offset through
  non-future newSpace and use this to implement lists for weak array and
  ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30 bytes
  or 1Gb, big enough for newSpace for a good few years yet."
+ <inline: true>
  ^(manager rawHashBitsOf: corpse) << manager formatFieldWidthShift
  + (manager formatOf: corpse)!

Item was changed:
  ----- Method: SpurGenerationScavenger>>rememberedSetWithIndexDo: (in category 'debug support') -----
  rememberedSetWithIndexDo: aBlock
+ <inline: #always>
  0 to: rememberedSetSize - 1 do:
  [:i| aBlock value: (rememberedSet at: i) value: i]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeUnfiredEphemeronsOnEphemeronList (in category 'weakness and ephemerality') -----
  scavengeUnfiredEphemeronsOnEphemeronList
  "There may be ephemerons to be scavenged on the ephemeronList.
  Scavenge any with unfired (live) keys, removing them from the
  list, and answer if any with unfired keys were found."
  | unfiredEphemeronsScavenged corpseOffset previousCorpse |
  ephemeronList ifNil:
  [^false].
  unfiredEphemeronsScavenged := false.
  corpseOffset := ephemeronList.
  [corpseOffset ~= 0] whileTrue:
+ [| ephemeronCorpse ephemeron offsetToNextCorpse  |
- [| ephemeronCorpse ephemeron nextCorpseOffset  |
  ephemeronCorpse := self corpseForCorpseOffset: corpseOffset.
  self assert: (manager isForwarded: ephemeronCorpse).
  ephemeron := manager followForwarded: ephemeronCorpse.
+ offsetToNextCorpse := self nextCorpseOffset: ephemeronCorpse.
- nextCorpseOffset := self nextCorpseOffset: ephemeronCorpse.
  (self isScavengeSurvivor: (manager keyOfEphemeron: ephemeron))
  ifTrue:
  [corpseOffset = ephemeronList
+ ifTrue: [ephemeronList := offsetToNextCorpse ~= 0 ifTrue: [offsetToNextCorpse]]
+ ifFalse: [self setCorpseOffsetOf: previousCorpse to: offsetToNextCorpse].
- ifTrue: [ephemeronList := nextCorpseOffset ~= 0 ifTrue: [nextCorpseOffset]]
- ifFalse: [self setCorpseOffsetOf: previousCorpse to: nextCorpseOffset].
  unfiredEphemeronsScavenged := true.
  self cCoerceSimple: (self scavengeReferentsOf: ephemeron) to: #void]
  ifFalse:
  [previousCorpse := ephemeronCorpse].
+ corpseOffset := offsetToNextCorpse].
- corpseOffset := nextCorpseOffset].
  ^unfiredEphemeronsScavenged!

Item was changed:
  ----- Method: SpurHybridCompactor>>biasForGC (in category 'api') -----
  biasForGC
+ <inline: true>
  planNotSelect := false.
  selectiveCompactor biasForGC!

Item was changed:
  ----- Method: SpurMemoryManager>>checkFreeSpace: (in category 'debug support') -----
  checkFreeSpace: gcModes
+ <api>
  self assert: self bitsSetInFreeSpaceMaskForAllFreeLists.
  self assert: totalFreeOldSpace = self totalFreeListBytes.
  (gcModes > 0
  and: [checkForLeaks allMask: (GCModeFreeSpace bitOr: gcModes)]) ifTrue:
  [self runLeakCheckerForFreeSpace: GCModeFreeSpace]!

Item was changed:
  ----- Method: SpurMemoryManager>>rememberedSetObj (in category 'scavenger') -----
  rememberedSetObj
+ <inline: #always>
  ^self fetchPointer: RememberedSetRootIndex ofObject: hiddenRootsObj!

Item was changed:
  ----- Method: SpurPlanningCompactor>>biasForGC (in category 'compaction - api') -----
  biasForGC
+ <inline: true>
  biasForGC := true!

Item was changed:
  ----- Method: SpurSegmentManager>>readHeapFrom:at:dataBytes: (in category 'private') -----
  readHeapFrom: f at: location dataBytes: numBytes
  "Read numBytes from f into mmory at location.  Answer the number of bytes read."
+ <inline: true>
  ^self cCode:
  [self
  sq: (self pointerForOop: location)
  Image: (self sizeof: #char)
  File: numBytes
  Read: f]
  inSmalltalk:
  [| bytesPerElement |
  bytesPerElement := manager memory bytesPerElement.
  (f readInto: manager memory
  startingAt: location // bytesPerElement + 1
  count: numBytes // bytesPerElement)
   * bytesPerElement]!

Item was changed:
  ----- Method: StackInterpreter class>>requiredMethodNames: (in category 'translation') -----
  requiredMethodNames: options
  "Answer the list of method names that should be retained for export or other support reasons"
  | requiredList |
  "A number of methods required by VM support code, specific platforms, etc"
  requiredList := #(
  assertValidExecutionPointe:r:s:
  characterForAscii:
  findClassOfMethod:forReceiver: findSelectorOfMethod:
  forceInterruptCheck forceInterruptCheckFromHeartbeat fullDisplayUpdate
  getCurrentBytecode getFullScreenFlag getInterruptKeycode getInterruptPending
  getSavedWindowSize getThisSessionID
  interpret
  loadInitialContext
  primitiveFail primitiveFailFor: primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
  printExternalHeadFrame printFramesInPage: printFrame: printHeadFrame printMemory printOop:
  printStackPages printStackPageList printStackPagesInUse printStackPageListInUse
+ readImageFromFile:HeapSize:StartingAt:
- readableFormat: readImageFromFile:HeapSize:StartingAt:
  setFullScreenFlag: setInterruptKeycode: setInterruptPending: setInterruptCheckChain:
  setSavedWindowSize: success:
  validInstructionPointer:inMethod:framePointer:) asSet.
 
  "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>>printDecodeMethodHeaderOop: (in category 'debug printing') -----
- ----- Method: StackInterpreter>>printDecodeMethodHeaderOop: (in category 'printing') -----
  printDecodeMethodHeaderOop: methodHeaderOop
  self printOopShort: methodHeaderOop.
  (self methodHeaderHasPrimitive: methodHeaderOop) ifTrue:
  [self print: ' hasPrim'].
  (self methodHeaderIndicatesLargeFrame: methodHeaderOop) ifTrue:
  [self print: ' largeFrame'].
  (SistaVM and: [self isOptimizedMethodHeader: methodHeaderOop]) ifTrue:
  [self print: ' optimized'].
  (MULTIPLEBYTECODESETS and: [(objectMemory integerValueOf: methodHeaderOop) < 0]) ifTrue:
  [self print: ' altSet'].
  NewspeakVM ifTrue:
  [| s |
  s := (self accessModifierOfMethodHeader: methodHeaderOop) caseOf: {
  [0] -> [' public'].
  [1] -> [' private'].
  [2] -> [' protected'].
  [3] -> [' access undefined'] }.
  self print: s].
  self print: ' nLits '; printNum: (objectMemory literalCountOfMethodHeader: methodHeaderOop);
  print: ' nArgs '; printNum: (self argumentCountOfMethodHeader: methodHeaderOop);
  print: ' nTemps '; printNum: (self temporaryCountOfMethodHeader: methodHeaderOop)!

Item was changed:
  ----- Method: StackInterpreter>>readableFormat: (in category 'image save/restore') -----
  readableFormat: imageVersion
  "Anwer true if images of the given format are readable by this interpreter.
  Allows a virtual machine to accept selected older image formats."
+ <api>
-
  ^imageVersion = self imageFormatVersion "Float words in platform-order"
    or: [objectMemory hasSpurMemoryManagerAPI not "No compatibility version for Spur as yet"
  and: [imageVersion = self imageFormatCompatibilityVersion]] "Float words in BigEndian order"!

Item was changed:
  ----- Method: StackInterpreter>>shortPrintOop: (in category 'debug printing') -----
  shortPrintOop: oop
  <inline: false>
  self printHexnp: oop.
  (objectMemory isImmediate: oop) ifTrue:
  [(objectMemory isIntegerObject: oop) ifTrue:
  [self
+ cCode: ['=%ld\n' printf: {(objectMemory integerValueOf: oop) asLong}]
- cCode: 'printf("=%ld\n", (long)integerValueOf(oop))'
  inSmalltalk: [self print: (self shortPrint: oop); cr]].
  (objectMemory isImmediateCharacter: oop) ifTrue:
  [self
+ cCode: ['=$%ld ($%lc)\n' printf: {(objectMemory characterValueOf: oop) asLong.
+ self cCoerce: (objectMemory characterValueOf: oop) to: 'wint_t'}]
- cCode: 'printf("=$%ld ($%lc)\n", (long)characterValueOf(oop), (wint_t)characterValueOf(oop))'
  inSmalltalk: [self print: (self shortPrint: oop); cr]].
  (objectMemory isImmediateFloat: oop) ifTrue:
  [self
+ cCode: ['=%g\n' printf: (objectMemory floatValueOf: oop)]
- cCode: 'printf("=%g\n", floatValueOf(oop))'
  inSmalltalk: [self print: '='; printFloat: (objectMemory floatValueOf: oop); cr]].
  ^self].
  (objectMemory addressCouldBeObj: oop) ifFalse:
  [^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  ifTrue: [' is misaligned']
  ifFalse: [self whereIs: oop]); cr].
  ((objectMemory isFreeObject: oop)
  or: [objectMemory isForwarded: oop]) ifTrue:
  [^self printOop: oop].
  self print: ': a(n) '.
  self printNameOfClass: (objectMemory fetchClassOfNonImm: oop) count: 5.
  self cr!

Item was added:
+ TStmtListNode subclass: #TLiteralBlockNode
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-Translation to C'!

Item was added:
+ ----- Method: TLiteralBlockNode>>isLiteralBlock (in category 'testing') -----
+ isLiteralBlock
+ ^true!

Item was changed:
  ----- Method: TMethod>>argAssignmentsFor:send:except:in: (in category 'inlining') -----
  argAssignmentsFor: meth send: aSendNode except: elidedArgs in: aCodeGen
  "Return a collection of assignment nodes that assign the given argument expressions to the formal parameter variables of the given method."
  "Optimization: If the actual parameters are either constants or local variables in the target method (the receiver), substitute them directly into the body of meth. Note that global variables cannot be subsituted because the inlined method might depend on the exact ordering of side effects to the globals."
 
  | stmtList substitutionDict argList |
  meth args size > (argList := aSendNode args) size ifTrue:
  [self assert: (meth args first beginsWith: 'self_in_').
  argList := {aSendNode receiver}, aSendNode args].
 
  stmtList := OrderedCollection new: argList size.
  substitutionDict := Dictionary new: argList size.
  meth args with: argList do:
  [:argName :exprNode |
  (self isNode: exprNode substitutableFor: argName inMethod: meth in: aCodeGen)
  ifTrue:
  [substitutionDict
  at: argName
  put: (aCodeGen
  node: exprNode
  typeCompatibleWith: argName
  inliningInto: meth
  in: self).
  locals remove: argName ifAbsent: [self assert: (argName beginsWith: 'self_in_')].
  declarations removeKey: argName ifAbsent: nil]
  ifFalse: "Add an assignment for anything except an unused self_in_foo argument"
  [(elidedArgs includes: argName) ifFalse:
+ [self deny: exprNode isLiteralBlock.
+ stmtList addLast:
- [stmtList addLast:
  (TAssignmentNode new
  setVariable: (TVariableNode new setName: argName)
  expression: (aCodeGen
  node: exprNode copy
  typeCompatibleWith: argName
  inliningInto: meth
  in: self))]]].
  meth parseTree: (meth parseTree bindVariablesIn: substitutionDict).
  ^stmtList!

Item was changed:
  ----- Method: TMethod>>isNode:substitutableFor:inMethod:in: (in category 'inlining') -----
  isNode: aNode substitutableFor: argName inMethod: targetMeth in: aCodeGen
  "Answer if the given parameter node may be substituted directly into the body of
  the method during inlining, instead of being bound to the actual parameter variable.
  We allow a constant, a local variable, or a formal parameter, or simple expressions
  involving only these to to be directly substituted. Note that global variables cannot
  be subsituted into methods with possible side effects (i.e., methods that may assign
  to global variables) because the inlined method might depend on having the value of
  the global variable captured when it is passed in as an argument."
 
  | madeNonTrivialCall count constantExpression usageCount |
  aNode isConstant ifTrue: [^true].
 
  aNode isVariable ifTrue:
  [((locals includes: aNode name)
  or: [(args includes: aNode name)
  or: [#('self' 'true' 'false' 'nil') includes: aNode name]]) ifTrue: [^true].
  "We can substitute any variable provided it is only read in the method being inlined,
  and if it is not read after any non-trivial call (which may update the variable)."
  madeNonTrivialCall := false.
  (targetMeth isComplete
  and: [targetMeth parseTree
  noneSatisfy:
  [:node|
  (node isSend
   and: [(aCodeGen isBuiltinSelector: node selector) not]) ifTrue:
  [madeNonTrivialCall := true].
  (madeNonTrivialCall and: [node isVariable and: [node name = argName]])
  or: [node isAssignment
   and: [node variable name = argName]]]
  unless:
  [:node|
  node isSend and: [aCodeGen isAssertSelector: node selector]]]) ifTrue:
  [^true].
  ^targetMeth maySubstituteGlobal: aNode name in: aCodeGen].
 
  "don't much up asserts with complex expansions"
  (targetMeth usesVariableUninlinably: argName in: aCodeGen) ifTrue:
  [^false].
 
  "For now allow literal blocks to be substituted.  They better be accessed only
  with value[:value:*] messages though!!"
+ aNode isLiteralBlock ifTrue: [^true].
- aNode isStmtList ifTrue: [^true].
 
  "Don't inline expressions unless type-compatible,"
  aNode isSend ifTrue:
  [(aCodeGen
  isActualType: (aCodeGen returnTypeForSend: aNode in: self ifNil: #incompatible)
  compatibleWithFormalType: (self typeFor: argName in: aCodeGen)) ifFalse:
  [^false]].
 
  count := 0.
  constantExpression := true.
  "scan expression tree; must contain only constants, builtin ops, and inlineable vars"
  aNode nodesDo:
  [:node|
  node isConstant
  ifTrue: [] ifFalse:
  [node isSend
  ifTrue:
  [((VMBasicConstants mostBasicConstantSelectors includes: node selector)
   or: [node isBuiltinOperator]) ifFalse: [^false].
  count := count + 1] ifFalse:
  [node isVariable ifTrue:
  [(aCodeGen isNonArgumentImplicitReceiverVariableName: node name) ifFalse:
  [constantExpression := false.
  ((locals includes: node name)
  or: [(args includes: node name)
  or: [(#('self' 'true' 'false' 'nil') includes: node name)
  or: [targetMeth maySubstituteGlobal: node name in: aCodeGen]]]) ifFalse: [^false]]] ifFalse:
  [^false]]]].
  "inline constant expressions"
  constantExpression ifNil: [^true].
 
  "scan target to find usage count"
  usageCount := 0.
  targetMeth parseTree nodesDo:
  [:node|
  (node isVariable and: [node name = argName]) ifTrue:
  [usageCount := usageCount + 1]].
  "(usageCount > 1 and: [count <= usageCount]) ifTrue:
  [[UsageCounts := Dictionary new.
   self removeClassVarName: #UsageCounts].
  (UsageCounts at: usageCount ifAbsentPut: [Set new]) add: ({targetMeth. argName. aNode})]."
  "Now only inline expressions if they are used only once or are simple
  w.r.t. the usage count, and the usage count is not large; a heuristic that seems to work well enough."
  ^usageCount = 1 or: [usageCount <= 7 and: [count <= usageCount]]!

Item was changed:
  ----- Method: TMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initialization') -----
  setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
  "Initialize this method using the given information."
 
  selector := sel.
  definingClass := class.
  args := argList asOrderedCollection collect: [:arg | arg key].
  locals := (localList collect: [:arg | arg key]) asSet.
  declarations := Dictionary new.
  self addTypeForSelf.
  primitive := aNumber.
  properties := methodProperties.
  comment := aComment.
  labels := Set new.
  parseTree := aBlockNode. "hack; allows nodes to find their parent, etc"
+ parseTree := aBlockNode asRootTranslatorNodeIn: self.
- parseTree := aBlockNode asTranslatorNodeIn: self.
  complete := false.  "set to true when all possible inlining has been done"
  export := self extractExportDirective.
  static := self extractStaticDirective.
  self extractSharedCase.
  globalStructureBuildMethodHasFoo := false!

Item was added:
+ ----- Method: TParseNode>>isLiteralBlock (in category 'testing') -----
+ isLiteralBlock
+ ^false!

Item was added:
+ ----- Method: TParseNode>>parentIn: (in category 'accessing') -----
+ parentIn: aParseTree
+ aParseTree nodesWithParentsDo:
+ [:node :parent|
+ self == node ifTrue: [^parent]].
+ ^nil!

Item was added:
+ ----- Method: VMClass>>strcmp:_: (in category 'C library simulation') -----
+ strcmp: aString _: bString
+ <doNotGenerate>
+ "implementation of strcmp(3); assumption is that aStrung is always a literal Smalltalk string."
+ bString isString ifTrue:
+ [1 to: (aString size min: bString size) do:
+ [:i| | v |
+ v := (aString basicAt: i) - (bString basicAt: i).
+ v ~= 0 ifTrue: [^v]].
+ aString size = bString size ifTrue:
+ [^0].
+ ^aString size < bString size
+ ifTrue: [bString basicAt: aString size]
+ ifFalse: [aString basicAt: bString size]].
+ ^self strcmp: aString bytes: bString!

Item was added:
+ ----- Method: VMClass>>strcmp:bytes: (in category 'C library simulation') -----
+ strcmp: aString bytes: bString
+ "Helper for implementation of strcmp(3); see strcmp:_:"
+ <doNotGenerate>
+ | i limit b v |
+ i := 0.
+ limit := aString size.
+ [(i := i + 1) <= limit] whileTrue:
+ [b := self byteAt: bString + i - 1.
+ b = 0 ifTrue:
+ [^aString basicAt: i].
+ v := (aString basicAt: i) - b.
+ v ~= 0 ifTrue: [^v]].
+ ^self byteAt: bString + i - 1!

Item was changed:
  ----- Method: VMClass>>stretch:cat: (in category 'C library extensions') -----
  stretch: s1 cat: s2
  <var: 's1' type: #'char *'>
  <var: 's2' type: #'char *'>
+ <returnTypeC: #'char *'>
  | ns |
  <var: 'ns' type: #'char *'>
  ^self
  cCode:
  [ns := self malloc: (self strlen: s1) + (self strlen: s2) + 2.
  self strcpy: ns _: s1.
  self strcat: ns  _: s2]
  inSmalltalk: [self strcat: s1  _: s2]!

Item was changed:
  ----- Method: VMMaker class>>generateAllConfigurationsUnderVersionControl (in category 'configurations') -----
  generateAllConfigurationsUnderVersionControl
  self
  executeDisplayingProgress:
  (OrderedDictionary
  with: 'Generate all newspeak configurations under VCS' -> [ self generateAllNewspeakConfigurationsUnderVersionControl ]
  with: 'Generate all squeak cofigurations under VCS' -> [ self generateAllSqueakConfigurationsUnderVersionControl ]
  with: 'Generate all spur lowcode configurations' -> [ self generateAllSpurLowcodeConfigurations ]
+ with: 'Generate VM plugins' -> [ self generateVMPlugins ]
+ with: 'Generate spur leak checkers' -> [ self generateSpur32LeakChecker; generateSpur64LeakChecker ])!
- with: 'Generate VM plugins' -> [ self generateVMPlugins ])!

Item was changed:
  ----- Method: VMMaker class>>generateAllSpurConfigurations (in category 'configurations') -----
  generateAllSpurConfigurations
  self
  executeDisplayingProgress:
  (OrderedDictionary new
  add: 'Generate all newspeak configurations under VCS' -> [ self generateAllNewspeakConfigurationsUnderVersionControl ];
  add: 'Generate squeak spur cog 32bits' -> [ self generateSqueakSpurCogVM ];
  add: 'Generate squeak spur cog 64bits' -> [ self generateSqueakSpurCog64VM ];
  add: 'Generate squeak spur cog sista 32bits' -> [ self generateSqueakSpurCogSistaVM ];
  add: 'Generate squeak spur cog sista 64bits' -> [ self generateSqueakSpurCogSista64VM ];
  add: 'Generate squeak spur stack 32bits' -> [ self generateSqueakSpurStackVM ];
  add: 'Generate squeak spur stack 64bits' -> [ self generateSqueakSpurStack64VM ];
  add: 'Generate all spur lowcode configurations' -> [ self generateAllSpurLowcodeConfigurations ];
+ add: 'Generate spur leak checkers' -> [ self generateSpur32LeakChecker; generateSpur64LeakChecker ];
  yourself)
  !

Item was changed:
  ----- Method: VMMaker class>>generateAllSpurConfigurationsUnderVersionControl (in category 'configurations') -----
  generateAllSpurConfigurationsUnderVersionControl
  self
  executeDisplayingProgress:
  (OrderedDictionary new
  add: 'Generate newspeak spur stack 32bits' -> [ self generateNewspeakSpurStackVM ];
  add: 'Generate newspeak spur cog 64bits' -> [ self generateNewspeakSpurCog64VM ];
  add: 'Generate squeak spur stack 32bits' -> [ self generateSqueakSpurStackVM ];
  add: 'Generate squeak spur stack 64bits' -> [ self generateSqueakSpurStack64VM ];
  add: 'Generate newspeak spur cog 32bits' -> [ self generateNewspeakSpurCogVM ];
  add: 'Generate squeak spur cog 32bits' -> [ self generateSqueakSpurCogVM ];
  add: 'Generate squeak spur cog 64bits' -> [ self generateSqueakSpurCog64VM ];
  add: 'Generate squeak spur cog multi-threaded 32bits' -> [ self generateSqueakSpurCogMTVM ];
  add: 'Generate squeak spur cog multi-threaded 64bits' -> [ self generateSqueakSpurCog64MTVM ];
  add: 'Generate squeak spur cog sista 32bits' -> [ self generateSqueakSpurCogSistaVM ];
+ add: 'Generate squeak spur cog sista 64bits' -> [ self generateSqueakSpurCogSista64VM ];
+ add: 'Generate spur leak checkers' -> [ self generateSpur32LeakChecker; generateSpur64LeakChecker ];
- add: 'Generate squeak spur cog sista 64bits' -> [ self generateSqueakSpurCogSista64VM ];
  yourself)
  !

Item was added:
+ ----- Method: VMMaker class>>generateSpur32LeakChecker (in category 'configurations') -----
+ generateSpur32LeakChecker
+ ^VMMaker
+ generate: ImageLeakChecker
+ with: #(ObjectMemory Spur32BitMemoryManager
+ MULTIPLEBYTECODESETS true)
+ to: self sourceTree, '/spurstacksrc'
+ platformDir: self sourceTree, '/platforms'
+ including: #()!

Item was added:
+ ----- Method: VMMaker class>>generateSpur64LeakChecker (in category 'configurations') -----
+ generateSpur64LeakChecker
+ ^VMMaker
+ generate: ImageLeakChecker
+ with: #(ObjectMemory Spur64BitMemoryManager
+ MULTIPLEBYTECODESETS true)
+ to: self sourceTree, '/spurstack64src'
+ platformDir: self sourceTree, '/platforms'
+ including: #()!

Item was changed:
  ----- Method: VMMaker>>doInlining (in category 'generate sources') -----
  doInlining
  "default is true but see VMMaker>initialize for details"
+ self interpreterClass ifNotNil:
+    [:interpreterClass|
+ (interpreterClass respondsTo: #doInlining) ifTrue:
+ [^interpreterClass doInlining]].
  ^inline!