VM Maker: VMMaker.oscog-eem.2050.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.2050.mcz

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

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

Name: VMMaker.oscog-eem.2050
Author: eem
Time: 26 December 2016, 7:16:12.441075 pm
UUID: d45b0fc7-802c-400f-a433-5d4c1941fdfd
Ancestors: VMMaker.oscog-eem.2049

Slang:
Fix inlining bugs due to an overcomplex and inaccurate completion check.

Specifically:
- inlineableFunctionCall:in: & inlineableSend:in: must see if a method wants to be inlined, so that completeness can be computed properly.
- fix slips in tryToInlineMethodsIn: exiting too soon and always setting complete in a macro.
- refactor checkForCompleteness:in: to checkForCompletenessIn: and simplify, setting complete if no incomplete send is found, rather than assuming completeness and then looking for inlineability, which is wrong.

Have collectInlineList: set inline to false (rather than nil) if using asSpecified or asSpecifiedOrQuick.

Fix pruneUnreachableMethods: to not delete <api> methods.

Add cppIf:ifTrue: to statementsListsForInliningIn:'s filtering out.

Slightly more flexible generateTruncateTo:on:indent:,probably not needed due to inlining fixes, but is goodness.

Fix mis-initialization on code generation by setting the vmClass's objectmemoryClass's initializationOptions before asking it for its ancilliary classes.

Spur:
Include the compactorClass's exportAPISelectors:.

Revert some now unnecessary <inline: #always> to <inline: true>.

Declare savedFirstFieldsSpace correctly.

Declatre the compactor's default return type correctly.

General:
Add printMethodImplementorsOf: for debugging.

=============== Diff against VMMaker.oscog-eem.2049 ===============

Item was changed:
  ----- Method: CCodeGenerator>>collectInlineList: (in category 'inlining') -----
  collectInlineList: inlineFlagOrSymbol
  "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: [m compiledMethod isQuick]].
  [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]]]!
- (#(asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol) ifFalse:
- [callsOf associationsDo:
- [:assoc|
- (assoc value = 1
- and: [(selectorsOfMethodsNotToInline includes: assoc key) not]) ifTrue:
- [inlineList add: assoc key]]]!

Item was changed:
  ----- Method: CCodeGenerator>>generateTruncateTo:on:indent: (in category 'C translation') -----
  generateTruncateTo: msgNode on: aStream indent: level
  "Generate the C code for this message onto the given stream."
 
+ | arg |
+ (self isConstantNode: msgNode args first valueInto: [:a| arg := a]) ifFalse:
+ [self error: 'can''t find method for inlining truncateTo:'].
+ self assert: (arg isInteger and: [arg isPowerOfTwo]).
- self assert: msgNode args first isConstant.
- self assert: msgNode args first value isInteger.
- self assert: msgNode args first value isPowerOfTwo.
  aStream nextPut: $(.
  self emitCExpression: msgNode receiver on: aStream.
+ aStream nextPutAll: ' & ~'; print: arg - 1; nextPut: $)!
- aStream nextPutAll: ' & ~'; print: msgNode args first value - 1; nextPut: $)!

Item was added:
+ ----- Method: CCodeGenerator>>maybeBreakForTestOfInliningOf: (in category 'inlining') -----
+ maybeBreakForTestOfInliningOf: aNodeOrSelector
+ "convenient for debugging..."
+ | selector |
+ selector := aNodeOrSelector isSymbol
+ ifTrue: [aNodeOrSelector]
+ ifFalse:
+ [aNodeOrSelector isSend
+ ifTrue: [aNodeOrSelector selector]
+ ifFalse: [^self]].
+ ((breakSrcInlineSelectors includes: selector)
+ and: [breakDestInlineSelectors isEmpty
+ and: [breakOnInline == true]]) ifTrue:
+ [self halt: selector]!

Item was changed:
  ----- Method: CCodeGenerator>>pruneUnreachableMethods (in category 'inlining') -----
  pruneUnreachableMethods
  "Remove any methods that are not reachable. Retain methods needed by the translated classes - see implementors of requiredMethodNames"
   
  | neededSelectors newMethods previousSize visited |
  "add all the exported methods and all the called methods to the requiredSelectors"
  "keep all the fake methods (macros and struct accessors; these are needed
  to ensure correct code generation."
 
  neededSelectors := Set withAll: requiredSelectors.
  methods do: [ :m |
  m export ifTrue:
  [neededSelectors add: m selector].
+ m isAPIMethod ifTrue:
+ [neededSelectors add: m selector].
  m isRealMethod ifFalse:
  [neededSelectors add: m selector]].
 
  "Now compute the transitive closure..."
  previousSize := neededSelectors size.
  visited := IdentitySet new: methods size.
  [neededSelectors do:
  [:s|
  (methods at: s ifAbsent: []) ifNotNil:
  [:m|
  (visited includes: m) ifFalse:
  [visited add: m.
  (m isRealMethod
   and: [self shouldGenerateMethod: m]) ifTrue:
  [neededSelectors addAll: m allCalls]]]].
  neededSelectors size > previousSize]
  whileTrue:
  [previousSize := neededSelectors size].
 
  "build a new dictionary of methods from the collection of all the ones to keep"
  newMethods := Dictionary new: neededSelectors size.
  neededSelectors do:
  [:sel|
  methods at: sel ifPresent: [:meth| newMethods at: sel put: meth]].
  methods := newMethods!

Item was added:
+ ----- Method: ObjectMemory>>printMethodImplementorsOf: (in category 'debug printing') -----
+ printMethodImplementorsOf: anOop
+ "Scan the heap printing the oops of any and all methods that implement anOop"
+ <api>
+ | obj |
+ obj := self firstAccessibleObject.
+ [obj = nil] whileFalse:
+ [((self isCompiledMethod: obj)
+  and: [(self maybeSelectorOfMethod: obj) = anOop]) ifTrue:
+ [self printHex: obj; space; printOopShort: obj; cr]]!

Item was changed:
  ----- Method: Spur32BitCoMemoryManager class>>exportAPISelectors: (in category 'translation') -----
  exportAPISelectors: options
  ^(Set withAll: (self exportAPISelectorsFor: self))
  addAll: (SpurGenerationScavenger exportAPISelectors: options);
+ addAll: (self compactorClass exportAPISelectors: options);
  yourself!

Item was changed:
  ----- Method: Spur64BitCoMemoryManager class>>exportAPISelectors: (in category 'translation') -----
  exportAPISelectors: options
  ^(Set withAll: (self exportAPISelectorsFor: self))
  addAll: (SpurGenerationScavenger exportAPISelectors: options);
+ addAll: (self compactorClass exportAPISelectors: options);
  yourself!

Item was added:
+ ----- Method: SpurMemoryManager>>printMethodImplementorsOf: (in category 'debug printing') -----
+ printMethodImplementorsOf: anOop
+ "Scan the heap printing the oops of any and all methods that implement anOop"
+ <api>
+ self allObjectsDo:
+ [:obj|
+ ((self isCompiledMethod: obj)
+  and: [(coInterpreter maybeSelectorOfMethod: obj) = anOop]) ifTrue:
+ [coInterpreter printHex: obj; space; printOopShort: obj; cr]]!

Item was changed:
  ----- Method: SpurMemoryManager>>slidingCompactionShouldRemapObj: (in category 'gc - scavenge/compact') -----
  slidingCompactionShouldRemapObj: objOop
+ <inline: true>
- <inline: #always>
  "Answer if the obj should be scavenged, or simply followed. Sent via the compactor
  from shouldRemapObj:.  We test for being already scavenged because mapStackPages
  via mapInterpreterOops may be applied twice in the context of a global GC where a
  scavenge, followed by a scan-mark-free, and final compaction passes may result in
  scavenged fields being visited twice."
  ^(self isForwarded: objOop)
    or: [gcPhaseInProgress > 0 "Hence either scavengeInProgress or slidingCompactionInProgress"
    and: [self scavengeInProgress
  ifTrue: [(self isReallyYoungObject: objOop)
  and: [(self isInFutureSpace: objOop) not]]
  ifFalse: [compactor isMobile: objOop]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>vanillaShouldRemapObj: (in category 'gc - scavenge/compact') -----
  vanillaShouldRemapObj: objOop
+ <inline: true>
- <inline: #always>
  "Answer if the obj should be scavenged, or simply followed. Sent via the compactor
  from shouldRemapObj:.  We test for being already scavenged because mapStackPages
  via mapInterpreterOops may be applied twice in the context of a global GC where a
  scavenge, followed by a scan-mark-free, and final compaction passes may result in
  scavenged fields being visited twice."
  ^(self isForwarded: objOop)
   or: [(self isReallyYoungObject: objOop)
  and: [(self isInFutureSpace: objOop) not]]!

Item was added:
+ ----- Method: SpurPigCompactor class>>implicitReturnTypeFor: (in category 'translation') -----
+ implicitReturnTypeFor: aSelector
+ "Answer the return type for methods that don't have an explicit return."
+ ^#void!

Item was added:
+ ----- Method: SpurPlanningCompactor class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ aCCodeGenerator var: 'savedFirstFieldsSpace' type: #SpurContiguousObjStack!

Item was added:
+ ----- Method: SpurPlanningCompactor class>>implicitReturnTypeFor: (in category 'translation') -----
+ implicitReturnTypeFor: aSelector
+ "Answer the return type for methods that don't have an explicit return."
+ ^#void!

Item was changed:
  ----- Method: SpurPlanningCompactor>>copyAndUnmarkObject:to:firstField: (in category 'compaction') -----
  copyAndUnmarkObject: o to: toFinger firstField: firstField
  "Copy the object to toFinger, clearing its mark bit and restoring its firstField, which was overwritten with a forwarding pointer.
  Answer the number of bytes in the object, including overflow header."
+ <inline: true>
- <inline: #always>
  | bytes numSlots destObj start |
  numSlots := manager rawNumSlotsOf: o.
  destObj := (manager objectWithRawSlotsHasOverflowHeader: numSlots)
  ifTrue: [toFinger + manager baseHeaderSize]
  ifFalse: [toFinger].
  bytes := manager bytesInObject: o given: numSlots.
  start := manager startOfObject: o given: numSlots.
  manager
  mem: toFinger asVoidPointer cp: start asVoidPointer y: bytes;
  setIsMarkedOf: destObj to: false;
  storePointerUnchecked: 0 ofObject: destObj withValue: firstField.
  ^bytes!

Item was changed:
  ----- Method: SpurPlanningCompactor>>isMobile: (in category 'private') -----
  isMobile: obj
+ <inline: true>
- <inline: #always>
  ^(self oop: obj isGreaterThanOrEqualTo: firstMobileObject andLessThanOrEqualTo:  lastMobileObject)
  and: [(manager isPinned: obj) not]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>shouldRemapObj: (in category 'gc - scavenge/compact') -----
  shouldRemapObj: objOop
- <api>
  "Answer if the obj should be scavenged, or simply followed. Sent via the compactor
  from shouldRemapObj:.  We test for being already scavenged because mapStackPages
  via mapInterpreterOops may be applied twice in the context of a global GC where a
  scavenge, followed by a scan-mark-free, and final compaction passes may result in
  scavenged fields being visited twice."
+ <api>
+ <inline: false>
  ^manager slidingCompactionShouldRemapObj: objOop!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointersFrom:to:in: (in category 'compaction') -----
  updatePointersFrom: start to: finish in: obj
+ <inline: true>
- <inline: #always>
  start to: finish do:
  [:i| | oop fwd |
  oop := manager fetchPointer: i ofObject: obj.
  ((manager isNonImmediate: oop) and: [self isMobile: oop]) ifTrue:
  [self assert: (manager isMarked: oop).
  fwd := manager fetchPointer: 0 ofObject: oop.
  self assert: (self isPostMobile: fwd).
  manager storePointerUnchecked: i ofObject: obj withValue: fwd]]!

Item was removed:
- ----- Method: TMethod>>checkForCompleteness:in: (in category 'inlining') -----
- checkForCompleteness: stmtLists in: aCodeGen
- "Set the complete flag if none of the given statement list nodes contains further candidates for inlining."
-
- complete := true.
- stmtLists do:
- [:stmtList|
- stmtList statements do:
- [:node|
- [(self inlineableSend: node in: aCodeGen) ifTrue:
- [complete := false.  "more inlining to do"
- ^self]]]].
-
- parseTree
- nodesDo:
- [:node|
- (self inlineableFunctionCall: node in: aCodeGen) ifTrue:
- [complete := false.  "more inlining to do"
- ^self]]
- unless:
- [:node|
- node isSend
- and: [node selector == #cCode:inSmalltalk:
- or: [aCodeGen isAssertSelector: node selector]]]!

Item was added:
+ ----- Method: TMethod>>checkForCompletenessIn: (in category 'inlining support') -----
+ checkForCompletenessIn: aCodeGen
+ "Set the complete flag if the parse tree contains no further candidates for inlining."
+ | foundIncompleteSend incompleteSends |
+ aCodeGen maybeBreakForTestOfInliningOf: selector.
+
+ foundIncompleteSend := false.
+ incompleteSends := IdentitySet new.
+
+ parseTree
+ nodesDo:
+ [:node|
+ node isSend ifTrue:
+ [(self methodIsEffectivelyComplete: node selector in: aCodeGen)
+ ifTrue:
+ [(self inlineableFunctionCall: node in: aCodeGen) ifTrue:
+ [complete := false.  "more inlining to do"
+ ^self]]
+ ifFalse:
+ [foundIncompleteSend := true.
+ incompleteSends add: node]]]
+ unless:
+ [:node|
+ node isSend
+ and: [node selector == #cCode:inSmalltalk:
+ or: [aCodeGen isAssertSelector: node selector]]].
+
+ foundIncompleteSend ifFalse:
+ [complete := true]!

Item was added:
+ ----- Method: TMethod>>incompleteSendsIn: (in category 'inlining support') -----
+ incompleteSendsIn: aCodeGen
+ "Debugging support; answer the incomplete and inlineable sends in the receiver."
+ | incompleteSends inlineableSends |
+ aCodeGen maybeBreakForTestOfInliningOf: selector.
+
+ incompleteSends := IdentitySet new.
+ inlineableSends := IdentitySet new.
+
+ parseTree
+ nodesDo:
+ [:node|
+ node isSend ifTrue:
+ [(self methodIsEffectivelyComplete: node selector in: aCodeGen)
+ ifTrue:
+ [(self inlineableFunctionCall: node in: aCodeGen) ifTrue:
+ [inlineableSends add: node]]
+ ifFalse:
+ [incompleteSends add: node]]]
+ unless:
+ [:node|
+ node isSend
+ and: [node selector == #cCode:inSmalltalk:
+ or: [aCodeGen isAssertSelector: node selector]]].
+
+ ^{incompleteSends. inlineableSends}!

Item was added:
+ ----- Method: TMethod>>inline: (in category 'accessing') -----
+ inline: aBoolean
+ inline := aBoolean!

Item was changed:
  ----- Method: TMethod>>inlineableFunctionCall:in: (in category 'inlining') -----
  inlineableFunctionCall: aNode in: aCodeGen
  "Answer if the given send node is a call to a 'functional' method--a method whose body is a single return statement of some expression and whose actual parameters can all be directly substituted."
 
  aCodeGen maybeBreakForTestToInline: aNode in: self.
  aNode isSend ifFalse:
  [^false].
  ^(aCodeGen methodNamed: aNode selector)
  ifNil:
  [aNode asTransformedConstantPerform
  ifNil: [self isInlineableConditional: aNode in: aCodeGen]
  ifNotNil: [:n| self inlineableFunctionCall: n in: aCodeGen]]
  ifNotNil:
  [:m|
  (m ~~ self
+  and: [(m isFunctionalIn: aCodeGen)
+  and: [m mayBeInlined
-  and: [(m isFunctionalIn: aCodeGen)
   and: [(aCodeGen mayInline: m selector)
+  and: [aNode args allSatisfy: [:a| self isSubstitutableNode: a intoMethod: m in: aCodeGen]]]]])
-  and: [aNode args allSatisfy: [:a| self isSubstitutableNode: a intoMethod: m in: aCodeGen]]]])
  or: [m checkForRequiredInlinability]]!

Item was changed:
  ----- Method: TMethod>>inlineableSend:in: (in category 'inlining') -----
  inlineableSend: aNode in: aCodeGen
  "Answer if the given send node is a call to a method that can be inlined."
 
  | m |
  aCodeGen maybeBreakForTestToInline: aNode in: self.
  aNode isSend ifFalse: [^false].
  m := aCodeGen methodNamed: aNode selector.  "nil if builtin or external function"
  ^m ~= nil
  and: [m ~~ self
+ and: [m mayBeInlined
  and: [(m isComplete and: [aCodeGen mayInline: m selector])
+ or: [m checkForRequiredInlinability]]]]!
- or: [m checkForRequiredInlinability]]]!

Item was added:
+ ----- Method: TMethod>>mayBeInlined (in category 'accessing') -----
+ mayBeInlined
+ ^inline == true or: [inline == nil or: [inline == #always]]!

Item was added:
+ ----- Method: TMethod>>methodIsEffectivelyComplete:in: (in category 'inlining support') -----
+ methodIsEffectivelyComplete: selector in: aCodeGen
+ "Answer if selector is effectively not inlineable in the receiver.
+ This is tricky because block inlining requires that certain methods must be inlined, which
+ can be at odds wuth the opportunistic strategy the inliner takes.  Since the inliner only
+ inlines complete methods and certain methods may never be marked as complete (e.g.
+ recursive methods) we have to short-cut certain kinds of send.  In particular, short-cut
+ sends that turn into jumps in the interpret routine (sharedCase and sharedLabel below)."
+ ^(aCodeGen methodNamed: selector)
+ ifNil: [true] "builtins or externals are not inlineable"
+ ifNotNil:
+ [:m|
+ m isComplete
+ "unlinable methods can't be inlined"
+ or: [m mayBeInlined not
+ "Methods which are inlined as jumps don't need inlining"
+ or: [m sharedCase notNil or: [m sharedLabel notNil]]]]!

Item was changed:
  ----- Method: TMethod>>statementsListsForInliningIn: (in category 'inlining') -----
  statementsListsForInliningIn: aCodeGen
  "Answer a collection of statement list nodes that are candidates for inlining.
  Currently, we cannot inline into the argument blocks of and: and or: messages.
  We do not want to inline code strings within cCode:inSmalltalk: blocks (those with a
  proper block for the cCode: argument are inlined in MessageNode>>asTranslatorNodeIn:).
  We do not want to inline code within assert: sends (because we want the assert to read nicely)."
 
  | stmtLists |
  stmtLists := OrderedCollection new: 10.
  parseTree
  nodesDo:
  [:node|
  node isStmtList ifTrue: [stmtLists add: node]]
  unless:
  [:node|
  node isSend
  and: [node selector == #cCode:inSmalltalk:
  or: [aCodeGen isAssertSelector: node selector]]].
  parseTree nodesDo:
  [:node|
  node isSend ifTrue:
  [node selector = #cCode:inSmalltalk: ifTrue:
  [node nodesDo:
  [:ccisNode| stmtLists remove: ccisNode ifAbsent: []]].
+ (node selector = #cppIf:ifTrue:ifFalse: or: [node selector = #cppIf:ifTrue:]) ifTrue:
- node selector = #cppIf:ifTrue:ifFalse: ifTrue:
  [node args first nodesDo:
  [:inCondNode| stmtLists remove: inCondNode ifAbsent: []]].
  ((node selector = #and:) or: [node selector = #or:]) ifTrue:
  "Note: the PP 2.3 compiler produces two arg nodes for these selectors"
  [stmtLists remove: node args first ifAbsent: [].
  stmtLists remove: node args last ifAbsent: []].
  (#( #ifTrue: #ifFalse: #ifTrue:ifFalse: #ifFalse:ifTrue:
  #ifNil: #ifNotNil: #ifNil:ifNotNil: #ifNotNil:ifNil: ) includes: node selector) ifTrue:
  [stmtLists remove: node receiver ifAbsent: []].
  (#(whileTrue whileTrue: whilefalse whileFalse:) includes: node selector) ifTrue:
  "Allow inlining if it is a [...] whileTrue/whileFalse.
  This is identified by having more than one statement in the
  receiver block in which case the C code wouldn't work anyways"
  [node receiver statements size = 1 ifTrue:
  [stmtLists remove: node receiver ifAbsent: []]].
  (node selector = #to:do:) ifTrue:
  [stmtLists remove: node receiver ifAbsent: [].
  stmtLists remove: node args first ifAbsent: []].
  (node selector = #to:by:do:) ifTrue:
  [stmtLists remove: node receiver ifAbsent: [].
  stmtLists remove: node args first ifAbsent: [].
  stmtLists remove: node args second ifAbsent: []]].
  node isCaseStmt ifTrue: "don't inline cases"
  [node cases do: [:case| stmtLists remove: case ifAbsent: []]]].
  ^stmtLists!

Item was changed:
  ----- Method: TMethod>>tryToInlineMethodsIn: (in category 'inlining') -----
  tryToInlineMethodsIn: aCodeGen
  "Expand any (complete) inline methods sent by this method.
  Set the complete flag when all inlining has been done.
  Answer if something was inlined."
 
  | didSomething statementLists |
+ "complete ifTrue:
+ [^false]."
+
  self definedAsMacro ifTrue:
+ [complete ifTrue:
+ [^false].
+ ^complete := true].
+
- [complete := true.
- ^false].
  didSomething := self tryToInlineMethodStatementsIn: aCodeGen statementListsInto: [:stmtLists| statementLists := stmtLists].
  didSomething := (self tryToInlineMethodExpressionsIn: aCodeGen) or: [didSomething].
 
  didSomething ifTrue:
+ [writtenToGlobalVarsCache := nil].
- [writtenToGlobalVarsCache := nil.
- ^didSomething].
 
  complete ifFalse:
+ [self checkForCompletenessIn: aCodeGen.
- [self checkForCompleteness: statementLists in: aCodeGen.
  complete ifTrue: [didSomething := true]].  "marking a method complete is progress"
  ^didSomething!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: interpreterClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  "Answer the code generator for translating the interpreter."
 
  | cg interpreterClasses |
  initializeClasses ifTrue:
  [interpreterClass initializeWithOptions: optionsDictionary.
  interpreterClass hasCogit ifTrue:
+ [interpreterClass cogitClass initializeWithOptions: optionsDictionary].
+ interpreterClass objectMemoryClass initializationOptions: optionsDictionary].
- [interpreterClass cogitClass initializeWithOptions: optionsDictionary]].
 
  (cg := self createCodeGenerator) vmClass: interpreterClass.
 
  "Construct interpreterClasses as all classes from interpreterClass &
  objectMemoryClass up to VMClass in superclass to subclass order."
  interpreterClasses := OrderedCollection new.
  {interpreterClass. interpreterClass objectMemoryClass} do:
  [:vmClass| | theClass |
  theClass := vmClass.
  [theClass ~~ VMClass] whileTrue:
+ [theClass initializationOptions: optionsDictionary.
+ interpreterClasses addFirst: theClass.
- [interpreterClasses addFirst: theClass.
  theClass := theClass superclass]].
  interpreterClasses
  addFirst: VMClass;
  addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
 
  initializeClasses ifTrue:
  [interpreterClasses do:
  [:ic|
  (ic respondsTo: #initializeWithOptions:)
  ifTrue: [ic initializeWithOptions: optionsDictionary]
  ifFalse: [ic initialize]].
  (cg structClassesForTranslationClasses: interpreterClasses) do:
  [:structClass| structClass initialize]].
 
  cg addStructClasses: (cg structClassesForTranslationClasses: interpreterClasses).
 
  interpreterClasses do: [:ic| cg addClass: ic].
 
  getAPIMethods ifTrue:
  [interpreterClass cogitClass ifNotNil:
  [:cogitClass|
  cg includeAPIFrom: (self
  buildCodeGeneratorForCogit: cogitClass
  includeAPIMethods: false
  initializeClasses: false)]].
 
  ^cg!