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

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

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

Name: VMMaker.oscog-eem.2728
Author: eem
Time: 17 March 2020, 6:33:59.809562 pm
UUID: 9d29dbcb-8c21-4d75-a8cc-c2af3fd75b03
Ancestors: VMMaker.oscog-eem.2727

Slang:
Fix a bug with value expansions. The original code elided the value[:value:]* send when inlining a literal block evaluation whose block didn't end in return.  When  dispatchConcretize, and all concretize mehtods invoked there-in were changed to answer the number of bytes of generated code, rather than each concretize mehtod assigning the number of bytes of generated code individually, this bug surfaced, and invalid code was produced.  Amazing that this affected only ARMv5.

Nuke an obsolete pragma in an genForwardersInlinedIdenticalOrNotIf:.
Nuke an unsent method in ObjectMemory.

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

Item was removed:
- ----- Method: ObjectMemory>>isObjMutable: (in category 'header access') -----
- isObjMutable: anOop
- <inline: true>
- ^(self isObjImmutable: anOop) not!

Item was changed:
  ----- Method: SistaRegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  "Override to count inlined branches if followed by a conditional branch.
  We borrow the following conditional branch's counter and when about to
  inline the comparison we decrement the counter (without writing it back)
  and if it trips simply abort the inlining, falling back to the normal send which
  will then continue to the conditional branch which will trip and enter the abort."
  | nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
   counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask
   rcvrConstant argConstant |
  <var: #fixup type: #'BytecodeFixup *'>
  <var: #countTripped type: #'AbstractInstruction *'>
- <var: #label type: #'AbstractInstruction *'>
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
  <var: #jumpEqual type: #'AbstractInstruction *'>
  <var: #jumpNotEqual type: #'AbstractInstruction *'>
 
  ((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
  [^super genForwardersInlinedIdenticalOrNotIf: orNot].
 
  regMask := 0.
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
  branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  unforwardRcvr := (self ssValue: 1) mayBeAForwarder.
  unforwardArg := self ssTop mayBeAForwarder.
  (unforwardRcvr not and: [unforwardArg not])
  ifTrue: [unforwardRcvr := true.
  "TODO: use genVanilla with profiling counters (not implemented).
  ^self genVanillaInlinedIdenticalOrNotIf: orNot"].
  self assert: (unforwardArg or: [unforwardRcvr]).
  "We use reg for non annotable constants to avoid duplicating objRef."
  rcvrConstant := objectRepresentation isUnannotatableConstant: (self ssValue: 1).
  argConstant := objectRepresentation isUnannotatableConstant: self ssTop.
 
  "If an operand is an annotable constant, it may be forwarded, so we need to store it into a
  register so the forwarder check can jump back to the comparison after unforwarding the constant.
  However, if one of the operand is an unnanotable constant, does not allocate a register for it
  (machine code will use operations on constants)."
  rcvrReg:= argReg := NoReg.
  self
  allocateEqualsEqualsRegistersArgNeedsReg: argConstant not
  rcvrNeedsReg: rcvrConstant not
  into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
 
  argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ].
  rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
 
  "Only interested in inlining if followed by a conditional branch."
  (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  [^ self
  genIdenticalNoBranchArgIsConstant: argConstant
  rcvrIsConstant: rcvrConstant
  argReg: argReg
  rcvrReg: rcvrReg
  orNotIf: orNot].
 
  unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
  unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
 
  counterReg := self allocateRegNotConflictingWith: regMask.
  self
  genExecutionCountLogicInto: [ :cAddress :countTripBranch |
  counterAddress := cAddress.
  countTripped := countTripBranch ]
  counterReg: counterReg.
 
  self assert: (unforwardArg or: [ unforwardRcvr ]).
  self genCmpArgIsConstant: argConstant rcvrIsConstant: rcvrConstant argReg: argReg rcvrReg: rcvrReg.
  self ssPop: 2.
 
  orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
  ifFalse:
  [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
  self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ]
  ifTrue:
  [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
  self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ].
 
  self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  self Jump: fixup.
 
  countTripped jmpTarget: self Label.
 
  "inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
  self ssPop: -2.
  self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  self ssPop: 2.
 
  "This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg.
  We therefore directly assign the result to TempReg to save one move instruction"
  jumpEqual := orNot ifFalse: [self JumpZero: 0] ifTrue: [self JumpNonZero: 0].
  self genMoveFalseR: TempReg.
  jumpNotEqual := self Jump: 0.
  jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
  jumpNotEqual jmpTarget: self Label.
  self ssPushRegister: TempReg.
 
  (self fixupAt: nextPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
 
  ^ 0!

Item was changed:
  ----- Method: TReturnNode>>emitValueExpansionOn:level:generator: (in category 'C code generation') -----
  emitValueExpansionOn: aStream level: level generator: aCodeGen
+ | stmtList lastStmt copiedStatements |
- | stmtList lastStmt copy |
  self assert: (expression isSend and: [expression isValueExpansion]).
  stmtList := expression receiver.
  lastStmt := stmtList statements last.
  lastStmt isReturn ifTrue:
  [^expression emitCCodeOn: aStream level: level generator: aCodeGen].
+ copiedStatements := stmtList copy.
+ copiedStatements statements
- copy := stmtList copy.
- copy statements
  at: stmtList statements size
  put: (TReturnNode new setExpression: lastStmt).
+ expression copy
+ receiver: copiedStatements;
+ emitCCodeOn: aStream level: level generator: aCodeGen!
- copy emitCCodeOn: aStream level: level generator: aCodeGen!