Simon Peyton Jones pushed to branch wip/T26425 at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Core/Opt/OccurAnal.hs
    ... ... @@ -659,13 +659,13 @@ through A, so it should have ManyOcc. Bear this case in mind!
    659 659
     * In occ_env, the new (occ_join_points :: IdEnv OccInfoEnv) maps
    
    660 660
       each in-scope non-recursive join point, such as `j` above, to
    
    661 661
       a "zeroed form" of its RHS's usage details. The "zeroed form"
    
    662
    -    * has only occ_nested_lets in its domain  (see (W5) below)
    
    662
    +    * has only occ_nested_lets in its domain  (see (W4) below)
    
    663 663
         * deletes ManyOccs
    
    664 664
         * maps a OneOcc to OneOcc{ occ_n_br = 0 }
    
    665 665
       In our example, assuming `v` is locally-let-bound, occ_join_points will
    
    666 666
       be extended with
    
    667 667
           [j :-> [v :-> OneOcc{occ_n_br=0}]]
    
    668
    -  See `addJoinPoint` and (W5) below.
    
    668
    +  See `addJoinPoint` and (W4) below.
    
    669 669
     
    
    670 670
     * At an occurrence of a join point, we do everything as normal, but add in the
    
    671 671
       UsageDetails from the occ_join_points.  See mkOneOcc.
    
    ... ... @@ -686,7 +686,7 @@ through A, so it should have ManyOcc. Bear this case in mind!
    686 686
            from j's RHS.
    
    687 687
     
    
    688 688
       The only reason for `occ_nested_lets` is to reduce the size of the info
    
    689
    -  duplicate at each tail call; see (W5). It would sound to put *all* variables
    
    689
    +  duplicate at each tail call; see (W4). It would sound to put *all* variables
    
    690 690
       into `occ_nested_lets`.
    
    691 691
     
    
    692 692
     Here are the consequences
    
    ... ... @@ -751,12 +751,7 @@ Wrinkles (W1) and (W2) are very similar to Note [Binder swap] (BS3).
    751 751
          NB: this is just about efficiency: it is always safe /not/ to zap the
    
    752 752
          occ_join_points.
    
    753 753
     
    
    754
    -(W4) What if the join point binding has a stable unfolding, or RULES?
    
    755
    -     They are just alternative right-hand sides, and at each call site we
    
    756
    -     will use only one of them. So again, we can use `combineJoinPointUDs`
    
    757
    -     to combine usage info from all these alternatives RHSs.
    
    758
    -
    
    759
    -(W5) Other things being equal, we want keep the OccInfoEnv stored in
    
    754
    +(W4) Other things being equal, we want keep the OccInfoEnv stored in
    
    760 755
       `occ_join_points` as small as possible, because it is /duplicated/ at
    
    761 756
       /every occurrence/ of the join point.  We really only want to include
    
    762 757
       OccInfo for
    
    ... ... @@ -1002,6 +997,22 @@ of both functions, serving as a specification:
    1002 997
          Cyclic Recursive case:   'tagRecBinders'
    
    1003 998
          Acyclic Recursive case:  'adjustNonRecRhs'
    
    1004 999
          Non-recursive case:      'adjustNonRecRhs'
    
    1000
    +
    
    1001
    +Note [Unfoldings and RULES]
    
    1002
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1003
    +For let-bindings we treat (stable) unfoldings and RULES as "alternative right hand
    
    1004
    +sides".  That is, it's as if we had
    
    1005
    +  f = case <hiatus> of
    
    1006
    +         1 -> <the-rhs>
    
    1007
    +         2 -> <the-stable-unfolding>
    
    1008
    +         3 -> <rhs of rule1>
    
    1009
    +         4 -> <rhs of rule2>
    
    1010
    +So we combine all these with `orUDs`.  But actually it makes very
    
    1011
    +little difference whether we use `andUDs` or `orUDs` because of
    
    1012
    +Note [Occurrences in stable unfoldings and RULES]: occurrences in an unfolding
    
    1013
    +or RULE are treated as ManyOcc anyway.
    
    1014
    +
    
    1015
    +But NB that tail-call info is preserved so that we don't thereby lose join points.
    
    1005 1016
     -}
    
    1006 1017
     
    
    1007 1018
     ------------------------------------------------------------------
    
    ... ... @@ -1101,7 +1112,7 @@ occAnalNonRecRhs !env lvl imp_rule_edges mb_join bndr rhs
    1101 1112
         , final_bndr_with_rules, final_rhs )
    
    1102 1113
     
    
    1103 1114
         -- orUDs: Combine the RHS, (stable) unfolding, and RULES with orUDs
    
    1104
    -    --  See (W4) of Note [Occurrence analysis for join points]
    
    1115
    +    --        See Note [Unfoldings and RULES]
    
    1105 1116
       where
    
    1106 1117
         --------- Right hand side ---------
    
    1107 1118
         -- For join points, set occ_encl to OccVanilla, via setTailCtxt.  If we have
    
    ... ... @@ -3777,7 +3788,7 @@ andUDs = combineUsageDetailsWith (\_uniq -> andLocalOcc)
    3777 3788
     orUDs  = combineUsageDetailsWith (\_uniq -> orLocalOcc)
    
    3778 3789
     
    
    3779 3790
     combineJoinPointUDs :: OccEnv -> UsageDetails -> UsageDetails -> UsageDetails
    
    3780
    --- See (W5) in Note [Occurrence analysis for join points]
    
    3791
    +-- See (W4) in Note [Occurrence analysis for join points]
    
    3781 3792
     combineJoinPointUDs (OccEnv { occ_nested_lets = nested_lets }) uds1 uds2
    
    3782 3793
       = combineUsageDetailsWith combine uds1 uds2
    
    3783 3794
       where