[GHC] #14816: Missed Called Arity opportunity?

GHC ghc-devs at haskell.org
Wed Feb 21 18:49:51 UTC 2018


#14816: Missed Called Arity opportunity?
-------------------------------------+-------------------------------------
        Reporter:  dfeuer            |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by sgraf):

 OK, that didn't work, but for reasons I didn't expect. If we apply that
 change, suddenly some bindings get *worse* *strictness* annotations,
 although it should only make for *less conservative* (possibly unsound)
 *usage* annotations, as `reuseEnv` will only affect usage information.

 It turns out that this is due to the interaction between the lazy fv hack
 and the fix-pointing algorithm. An example is adapted from T876:

 {{{
 foo :: Int -> Int
 foo n = sum [ length [i..n] | i <- [1..n] ]

 main = print (foo 100)
 }}}

 The variant that does get rid of the call to `reuseEnv` altogether will
 produce something like this code:

 {{{
 foo
   = \ (n_aYV [Dmd=<L,U(U)>] :: Int) ->
       joinrec {
         go_a2c3 [Occ=LoopBreaker] :: [Int] -> Int -> Int
         [LclId[JoinId(2)],
          Arity=2,
          Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True,
                  WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 20]
 137 0}]
         go_a2c3 (ds_a2c4 [Dmd=<S,1*U>] :: [Int])
                 (eta_B1 [Dmd=<L,1*U(U)>] :: Int)
           = case ds_a2c4 of {
               [] -> eta_B1;
               : y_a2c9 [Dmd=<L,1*U(U)>] ys_a2ca ->
                 jump go_a2c3
                   ys_a2ca
                   (case eta_B1 of { GHC.Types.I# x_a3ii [Dmd=<S,U>] ->
                    case y_a2c9 of { GHC.Types.I# x_a3jq [Dmd=<S,U>] ->
                    case n_aYV of { GHC.Types.I# y_a3jz [Dmd=<S,U>] ->
                    case GHC.List.$wlenAcc @ Int (GHC.Enum.eftInt x_a3jq
 y_a3jz) 0#
                    of ww2_a4JP [Dmd=<S,U>]
                    { __DEFAULT ->
                    GHC.Types.I# (GHC.Prim.+# x_a3ii ww2_a4JP)
                    }
                    }
                    }
                    })
             }; } in
       jump go_a2c3
         (case n_aYV of { GHC.Types.I# y_a3jz [Dmd=<S,U>] ->
          GHC.Enum.eftInt 1# y_a3jz
          })
         lvl_s4Jd
 }}}

 Note that `go` is clearly strict in `n` (that's what HEAD finds out), but
 this variant is too conservative. Some printfs revealed that's due to
 abortion of fix-pointing. This is a log for the `lazy_fv`s and the
 `sig_fv` envs:

 {{{
 dmdAnalRhsLetDown go_a2c3 [] []
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown go_a2c3 [aYV :-> <L,U(U)>] []
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown go_a2c3 [aYV :-> <L,U(U)>] []
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown go_a2c3 [aYV :-> <L,U(U)>] []
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown go_a2c3 [aYV :-> <L,U(U)>] []
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown go_a2c3 [] [aYV :-> <L,1*U(U)>]
 dmdAnalRhsLetDown foo [] []
 }}}

 It flip flops between putting `n`s demand into the `sig_fv` and the
 `lazy_fv`. That's decided by `isWeakDmd`, which amounts to checking if the
 demand is equivalent to `<L,U>` and will thus no longer change during fix-
 pointing. After the initial iteration, we find that `n` is called once and
 gets tagged onto the strictness signature. The second iteration sees that
 `n` is called an additional time, demand `<L,U(U)>`. This means it no
 longer has an interesting demand and goes into `lazy_fv`. But here's the
 culprit: The fix-pointer only compares the strictness signature for
 changes! It will start a third iteration, completely forget about any
 `lazy_fv` and flop back to the state of the first iteration.

 There's two ways out:

 1. Also check `lazy_fvs` for changes. This is the thing we wanted to avoid
 in the first place. Also this is LetUp in disguise, which purposefully
 isn't equipped to deal with recursive bindings.
 2. Don't check `lazy_fvs`. These are outer bindings only, so they don't
 actually need to play a role in fix-pointing. Also everything in
 `lazy_fvs` is already top-ish, so it suffices to check if a variable in a
 prior signature is now part of `lazy_fvs` and exclude them from the check.

 I'll try 2. tomorrow.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14816#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list