VM Maker Inbox: VMMaker.oscog-eem.2765.mcz

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

VM Maker Inbox: VMMaker.oscog-eem.2765.mcz

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

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

Name: VMMaker.oscog-eem.2765
Author: eem
Time: 23 June 2020, 6:41:19.556484 pm
UUID: 91b9976e-60b9-4b5c-a2f8-b621dd454a07
Ancestors: VMMaker.oscog-eem.2764

Spur: Rewrite the revised followForwardedObjectFields:toDepth: soi it can be correctly inlined.

Slang: Change the order of application of ensureConditionalAssignmentsAreTransformedIn: so it is always the last thing done in tryToInlineMethodsIn:.

Straight-forward optimization of bindVariablesIn: in the common case of methods being inlined swith unchanged parameters.

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

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>followForwardedObjectFields:toDepth: (in category 'as yet unclassified') -----
  followForwardedObjectFields: objOop toDepth: depth
  "Follow pointers in the object to depth.
  Answer if any forwarders were found.
  How to avoid cyclic structures?? A temporary mark bit? eem 6/22/2020 no need since depth is always finite."
  <api>
  <inline: false>
+ | found fmt limit |
- | oop found fmt |
  found := false.
  self assert: ((self isPointers: objOop) or: [self isOopCompiledMethod: objOop]).
  fmt := self formatOf: objOop.
+ limit := (self numPointerSlotsOf: objOop format: fmt) - 1.
  "It is essential to skip the first field of a method because it may be a
  reference to a Cog method in the method zone, not a real object at all."
  ((self isCompiledMethodFormat: fmt)
  ifTrue: [1]
  ifFalse: [0])
+ to: limit
+ do: [:i| | oop |
- to: (self numPointerSlotsOf: objOop format: fmt) - 1
- do: [:i|
  oop := self fetchPointer: i ofObject: objOop.
  (self isNonImmediate: oop) ifTrue:
  [(self isForwarded: oop) ifTrue:
  [found := true.
  oop := self followForwarded: oop.
  self storePointer: i ofObject: objOop withValue: oop].
  (depth > 0
  and: [(self hasPointerFields: oop)
  and: [self followForwardedObjectFields: oop toDepth: depth - 1]]) ifTrue:
  [found := true]]].
  ^found!

Item was changed:
  ----- Method: Spur64BitCoMemoryManager>>followForwardedObjectFields:toDepth: (in category 'forwarding') -----
  followForwardedObjectFields: objOop toDepth: depth
  "Follow pointers in the object to depth.
  Answer if any forwarders were found.
  How to avoid cyclic structures?? A temporary mark bit? eem 6/22/2020 no need since depth is always finite."
  <api>
  <inline: false>
+ | found fmt limit |
- | oop found fmt |
  found := false.
  self assert: ((self isPointers: objOop) or: [self isOopCompiledMethod: objOop]).
  fmt := self formatOf: objOop.
+ limit := (self numPointerSlotsOf: objOop format: fmt) - 1.
  "It is essential to skip the first field of a method because it may be a
  reference to a Cog method in the method zone, not a real object at all."
  ((self isCompiledMethodFormat: fmt)
  ifTrue: [1]
  ifFalse: [0])
+ to: limit
+ do: [:i| | oop |
- to: (self numPointerSlotsOf: objOop format: fmt) - 1
- do: [:i|
  oop := self fetchPointer: i ofObject: objOop.
  (self isNonImmediate: oop) ifTrue:
  [(self isForwarded: oop) ifTrue:
  [found := true.
  oop := self followForwarded: oop.
  self storePointer: i ofObject: objOop withValue: oop].
  (depth > 0
  and: [(self hasPointerFields: oop)
  and: [self followForwardedObjectFields: oop toDepth: depth - 1]]) ifTrue:
  [found := true]]].
  ^found!

Item was changed:
  ----- Method: TMethod>>exitVar:label:in: (in category 'inlining') -----
  exitVar: exitVar label: exitLabel in: aCodeGen
  "Replace each return statement in this method with an assignment to the
  exit variable followed by either a return or a goto to the given label.
  Answer if a goto was generated."
  "Optimization: If exitVar is nil, the return value of the inlined method is not being used, so don't add the assignment statement."
 
  | labelUsed map elisions eliminateReturnSelfs |
  labelUsed := false.
  map := Dictionary new.
  elisions := Set new.
  "Conceivably one might ^self from a struct class and mean it.  In most cases though
  ^self means `get me outta here, fast'.  So unless this method is from a VMStruct class,
  elide any ^self's"
  eliminateReturnSelfs := ((definingClass inheritsFrom: VMClass) and: [definingClass isStructClass]) not
   and: [returnType = #void or: [returnType = #sqInt]].
  parseTree nodesDo:
  [:node | | replacement |
  node isReturn ifTrue:
  [self transformReturnSubExpression: node
  toAssignmentOf: exitVar
  andGoto: exitLabel
  unless: eliminateReturnSelfs
  into: [:rep :labelWasUsed|
  replacement := rep.
  labelWasUsed ifTrue: [labelUsed := true]]
  in: aCodeGen.
  "replaceNodesIn: is strictly top-down, so any replacement for ^expr ifTrue: [...^fu...] ifFalse: [...^bar...]
  will prevent replacement of either ^fu or ^bar. The corollary is that ^expr ifTrue: [foo] ifFalse: [^bar]
  must be transformed into expr ifTrue: [^foo] ifFalse: [^bar]"
  (node expression isConditionalSend
  and: [node expression hasExplicitReturn])
  ifTrue:
  [elisions add: node.
  (node expression args reject: [:arg| arg endsWithReturn]) do:
  [:nodeNeedingReturn|
  self transformReturnSubExpression: nodeNeedingReturn statements last
  toAssignmentOf: exitVar
  andGoto: exitLabel
  unless: eliminateReturnSelfs
  into: [:rep :labelWasUsed|
  replacement := rep.
+ labelWasUsed ifTrue: [labelUsed := true]]
+ in: aCodeGen.
- labelWasUsed ifTrue: [labelUsed := true]].
  map
  at: nodeNeedingReturn statements last
  put: replacement]]
  ifFalse:
  [map
  at: node
  put: (replacement ifNil:
  [TLabeledCommentNode new setComment: 'return ', node expression printString])]]].
  map isEmpty ifTrue:
  [self deny: labelUsed.
  ^false].
  "Now do a top-down replacement for all returns that should be mapped to assignments and gotos"
  parseTree replaceNodesIn: map.
  "Now it is safe to eliminate the returning ifs..."
  elisions isEmpty ifFalse:
  [| elisionMap |
  elisionMap := Dictionary new.
  elisions do: [:returnNode| elisionMap at: returnNode put: returnNode expression].
  parseTree replaceNodesIn: elisionMap].
  "Now flatten any new statement lists..."
  parseTree nodesDo:
  [:node| | list |
  (node isStmtList
  and: [node statements notEmpty
  and: [node statements last isStmtList]]) ifTrue:
  [list := node statements last statements.
  node statements removeLast; addAllLast: list]].
  ^labelUsed!

Item was changed:
  ----- Method: TMethod>>inlineFunctionCall:in: (in category 'inlining') -----
  inlineFunctionCall: aSendNode in: aCodeGen
  "Answer the body of the called function, substituting the actual
  parameters for the formal argument variables in the method body.
  Assume caller has established that:
  1. the method arguments are all substitutable nodes, and
  2. the method to be inlined contains no additional embedded returns."
 
  | sel meth doNotRename argsForInlining substitutionDict |
+ aCodeGen maybeBreakForInlineOf: aSendNode in: self.
  sel := aSendNode selector.
  meth := (aCodeGen methodNamed: sel) copy.
  meth ifNil:
  [^self inlineBuiltin: aSendNode in: aCodeGen].
  doNotRename := Set withAll: args.
  argsForInlining := aSendNode argumentsForInliningCodeGenerator: aCodeGen.
  meth args with: argsForInlining do:
  [ :argName :exprNode |
  exprNode isLeaf ifTrue:
  [doNotRename add: argName]].
  (meth statements size = 2
  and: [meth statements first isSend
  and: [meth statements first selector == #flag:]]) ifTrue:
  [meth statements removeFirst].
  meth renameVarsForInliningInto: self except: doNotRename in: aCodeGen.
  meth renameLabelsForInliningInto: self.
  self addVarsDeclarationsAndLabelsOf: meth except: doNotRename.
  substitutionDict := Dictionary new: meth args size * 2.
  meth args with: argsForInlining do:
  [ :argName :exprNode |
+ (exprNode isVariable and: [exprNode name = argName]) ifFalse:
+ [substitutionDict at: argName put: exprNode].
- substitutionDict at: argName put: exprNode.
  (doNotRename includes: argName) ifFalse:
  [locals remove: argName]].
  meth parseTree bindVariablesIn: substitutionDict.
  ^meth parseTree endsWithReturn
  ifTrue: [meth parseTree copyWithoutReturn]
  ifFalse: [meth parseTree]!

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].
 
- self ensureConditionalAssignmentsAreTransformedIn: aCodeGen.
  didSomething := self tryToInlineMethodStatementsIn: aCodeGen statementListsInto: [:stmtLists| statementLists := stmtLists].
  didSomething := (self tryToInlineMethodExpressionsIn: aCodeGen) or: [didSomething].
+ self ensureConditionalAssignmentsAreTransformedIn: aCodeGen.
 
  didSomething ifTrue:
  [writtenToGlobalVarsCache := nil].
 
  complete ifFalse:
  [self checkForCompletenessIn: aCodeGen.
  complete ifTrue: [didSomething := true]].  "marking a method complete is progress"
  ^didSomething!

Item was changed:
  ----- Method: TStmtListNode>>bindVariablesIn: (in category 'transformations') -----
  bindVariablesIn: aDictionary
 
+ aDictionary notEmpty ifTrue:
+ [statements := statements collect: [:s| s bindVariablesIn: aDictionary]]!
- statements := statements collect: [ :s | s bindVariablesIn: aDictionary ].!