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

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

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

Name: VMMaker.oscog-eem.673
Author: eem
Time: 11 April 2014, 12:37:19.779 pm
UUID: a10ccba5-8338-4cc4-ae49-a11440780603
Ancestors: VMMaker.oscog-eem.672

Sista:
We cannot back-up the machine-code pc in ceCounterTripped:
because there isn't always a send preceeding the jump (e.g. in
and: [] and or: [] chains).  Instead, prevent subsequent counter
trips (to reduce the number of necessary skipBackBeforeJump
sends in the image) by nilling out SelectorCounterTripped.
The image-level optimization code will both restore the selector
and back-up the pc.

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

Item was changed:
  ----- Method: CoInterpreter>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
  "Two things are going on here.  The main one is catching a counter trip and attempting
+ to send the SelectorCounterTripped selector.  In this case we would like to back-up
+ the pc to the return address of the send that yields the boolean to be tested, so that
+ after potential optimization, computation proceeds by retrying the jump.  But we cannot,
+ since there may be no send, just a pop (as in and: [] and or: [] chains).  In this case we also
+ want to prevent further callbacks until optimization is complete.  So we nil-out the
+ SelectorCounterTripped entry in the specialSelectorArray.
- to send the SelectorCounterTripped selector.  In this case, if the send can be made, the
- pc should be backed up to the return address of the send that yields the boolean to be
- tested, so that after potential optimization, computation proceeds by retryying the jump.
 
  The minor case is that there is an unlikely  possibility that the cointer tripped but condition
  is not a boolean, in which case a mustBeBoolean response should occur."
  <api>
  <option: #SistaStackToRegisterMappingCogit>
  "Send e.g. thisContext conditionalBranchCounterTrippedOn: boolean."
  | context counterTrippedSelector classTag |
  (condition = objectMemory falseObject
  or: [condition = objectMemory trueObject]) ifFalse:
  [^self ceSendMustBeBoolean: condition].
 
  counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
  (counterTrippedSelector isNil
  or: [counterTrippedSelector = objectMemory nilObject]) ifTrue:
  [cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  ^condition].
 
  classTag := objectMemory
  classTagForSpecialObjectsIndex: ClassMethodContext
  compactClassIndex: ClassMethodContextCompactIndex.
  (self lookupInMethodCacheSel: counterTrippedSelector classTag: classTag) ifFalse:
  [messageSelector := counterTrippedSelector.
  (self lookupMethodNoMNUEtcInClass: (objectMemory classTagForClass: classTag)) ~= 0 ifTrue:
  [cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  ^condition]].
 
  (primitiveFunctionPointer ~= 0
  or: [(self argumentCountOf: newMethod) ~= 1]) ifTrue:
  [cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  ^condition].
 
+ objectMemory splObj: SelectorCounterTripped put: objectMemory nilObject.
+ instructionPointer := self popStack.
- "now back-up the pc; there is always a jump following the
- call to the ceSendMustBeBooleanAddTrue/FalseTrampoline."
- instructionPointer := cogit getJumpTargetPCAt: self popStack.
  context := self ensureFrameIsMarried: framePointer SP: stackPointer.
  self push: context.
  self push: condition.
  self ifAppropriateCompileToNativeCode: newMethod selector: counterTrippedSelector.
  self activateNewMethod.
  "not reached"
  ^true!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generators') -----
  genJumpIf: boolean to: targetBytecodePC
  "The heart of performance counting in Sista.  Conditional branches are 6 times less
  frequent than sends and can provide basic block frequencies (send counters can't).
  Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  and a lower half counting untaken executions of the branch.  Executing the branch
  decrements the upper half, tripping if the count goes negative.  Not taking the branch
  decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
  so that scanning for send and branch data is simplified and that branch data is correct."
  <inline: false>
  | desc ok counter countTripped retry |
  <var: #desc type: #'CogSimStackEntry *'>
  <var: #ok type: #'AbstractInstruction *'>
  <var: #retry type: #'AbstractInstruction *'>
  <var: #counter type: #'AbstractInstruction *'>
  <var: #countTripped type: #'AbstractInstruction *'>
  self ssFlushTo: simStackPtr - 1.
  desc := self ssTop.
  self ssPop: 1.
- retry := self Label.
  desc popToReg: TempReg.
 
  self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  counter := self addressOf: (counters at: counterIndex).
  counterIndex := counterIndex + 1.
  self flag: 'will need to use MoveAw32:R: if 64 bits'.
  self assert: BytesPerWord = CounterBytes.
+ retry := self MoveAw: counter asUnsignedInteger R: SendNumArgsReg.
+ counter addDependent: (self annotateAbsolutePCRef: retry).
- counter addDependent: (self annotateAbsolutePCRef: (self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  "Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  countTripped := self JumpCarry: 0.
  counter addDependent: (self annotateAbsolutePCRef:
  (self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
 
  "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  Correct result is either 0 or the distance between them.  If result is not 0 or
  their distance send mustBeBoolean."
  self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
 
  self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  counter addDependent: (self annotateAbsolutePCRef:
  (self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
 
  self CmpCq: (boolean == objectMemory falseObject
  ifTrue: [objectMemory trueObject - objectMemory falseObject]
  ifFalse: [objectMemory falseObject - objectMemory trueObject])
  R: TempReg.
  ok := self JumpZero: 0.
  self MoveCq: 0 R: SendNumArgsReg. "if SendNumArgsReg is 0 this is a mustBeBoolean, not a counter trip."
  countTripped jmpTarget:
  (self CallRT: (boolean == objectMemory falseObject
  ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
+ "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
+ trampoline will return directly to machine code, returning the boolean.  So the code should
+ jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
- "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped: trampoline
- will return directly to machine code, returning the boolean.  So the code should jump back to the
- retry point. This is the return address of the non-inlined method that yields the boolean to be tested.
- If ceCounterTripped: does not return it will examine the branch to retry to reposition the PC to that point."
  self annotateBytecode: self Label.
  self Jump: retry.
  ok jmpTarget: self Label.
  ^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  "This can be entered in one of two states, depending on SendNumArgsReg. See
  e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
  the initial test of the counter in the jump executed count (i.e. the counter has
  tripped).  In this case TempReg contains the boolean to be tested and should not
  be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
  If SendNumArgsReg is zero then this has been entered for must-be-boolean
  processing. TempReg has been offset by boolean and must be corrected and
  ceSendMustBeBoolean: invoked with the corrected value."
  <var: #trampolineName type: #'char *'>
  | jumpMBB |
  <var: #jumpMBB type: #'AbstractInstruction *'>
  <inline: false>
  opcodeIndex := 0.
  self CmpCq: 0 R: SendNumArgsReg.
  jumpMBB := self JumpZero: 0.
  self compileTrampolineFor: #ceCounterTripped:
  callJumpBar: true
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  saveRegs: false
  resultReg: nil.
  "For the case where the ceCounterTripped: call returns (e.g. because there's no callback selector
  installed), the call to the ceSendMustBeBooleanAddTrue/FalseTrampoline is followed by a jump
+ back to the start of the counter/condition test sequence.  For this case copy the C result to
+ TempReg (the register that is tested), to reload it with the boolean to be tested."
+ backEnd cResultRegister ~= TempReg ifTrue:
+ [self MoveR: backEnd cResultRegister R: TempReg].
- back to the return address of the send that yields the boolean to be tested.  For this case copy
- the C result to ReceiverResultReg, to reload it with the boolean to be tested."
- backEnd cResultRegister ~= ReceiverResultReg ifTrue:
- [self MoveR: backEnd cResultRegister R: ReceiverResultReg].
  "If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
  ^self genTrampolineFor: #ceSendMustBeBoolean:
  called: trampolineName
  callJumpBar: true
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  saveRegs: false
  resultReg: nil
  appendOpcodes: true!