[GHC] #13353: foldr/nil rule not applied consistently

GHC ghc-devs at haskell.org
Tue Feb 28 20:13:53 UTC 2017


#13353: foldr/nil rule not applied consistently
-------------------------------------+-------------------------------------
        Reporter:  nomeata           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by nomeata):

 Ok, so here is the deal. I get this core in the end:
 {{{
 test1
 test1
   = \ @ a_aYA x_s1dJ xs_s1dK ->
       let {
         sat_s1dT
         sat_s1dT
           = let {
               z_s1dL
               z_s1dL = map id xs_s1dK } in
             letrec {
               go_s1dM
               go_s1dM
                 = \ ds_s1dN ->
                     case ds_s1dN of {
                       [] -> z_s1dL;
                       : y_s1dP ys_s1dQ ->
                         let {
                           sat_s1dS
                           sat_s1dS = go_s1dM ys_s1dQ } in
                         let {
                           sat_s1dR
                           sat_s1dR = y_s1dP x_s1dJ } in
                         : sat_s1dR sat_s1dS
                     }; } in
             go_s1dM [] } in
       (x_s1dJ, sat_s1dT)
 }}}
 Note the useless application of what used to be `foldr` to `[]`. Also note
 that `foo1` was obviously inlined.

 If I explicitly `INLINE foo1`, then I get:
 {{{
 test1
 test1
   = \ @ a_aYA x_s1dh xs_s1di ->
       let {
         sat_s1dj
         sat_s1dj = map id xs_s1di } in
       (x_s1dh, sat_s1dj)
 }}}

 So despite GHC deciding to inline `foo1` (eventually), making it inline it
 early makes a big difference.

 With the `INLINE` pragma, GHC first considers to inline `foo1` in
 simplifier phase 2, after float out.
 {{{
 Considering inlining: foo1
   arg infos [ValueArg, ValueArg]
   interesting continuation BoringCtxt
   some_benefit True
   is exp: True
   is work-free: True
   guidance ALWAYS_IF(arity=2,unsat_ok=False,boring_ok=False)
   ANSWER = YES
 }}}

 Without we make a difference decision at this point:
 {{{
 Considering inlining: foo1
   arg infos [ValueArg, ValueArg]
   interesting continuation BoringCtxt
   some_benefit True
   is exp: True
   is work-free: True
   guidance IF_ARGS [20 20] 240 30
   discounted size = 150
   ANSWER = NO
 }}}
 but later, when foo1 has been w/w’ed, we inline it (i.e. the wrapper) in
 the post-w/w simplifer phase 0.
 {{{
 Considering inlining: foo1
   arg infos [ValueArg, ValueArg]
   interesting continuation BoringCtxt
   some_benefit True
   is exp: True
   is work-free: True
   guidance ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
   ANSWER = YES
 Inlining done: foo1
     Inlined fn:  \ @ a @ a w_s12e w_s12f ->
                    case w_s12e of { (ww_s12i, ww_s12j) ->
                    case w_s12f of { (ww_s12n, ww_s12o) ->
                    case $wfoo1 ww_s12i ww_s12j ww_s12n ww_s12o of
                    { (# ww_s12u, ww_s12v #) ->
                    (ww_s12u, ww_s12v)
                    }
                    }
                    }
     Cont:   ApplyToTy a
             ApplyToTy a
             ApplyToVal nodup lvl_s11y
             ApplyToVal nodup (x, xs)
             Stop[BoringCtxt] (a, [a])
 }}}
 and shortly after, we inline the worker:
 {{{
 Considering inlining: $wfoo1_s12t
   arg infos [ValueArg, ValueArg, TrivArg, TrivArg]
   interesting continuation CaseCtxt
   some_benefit True
   is exp: True
   is work-free: True
   guidance IF_ARGS [60 0 0 0] 180 30
   discounted size = -5
   ANSWER = YES
 Inlining done: $wfoo1
     Inlined fn:  \ @ a @ a ww_s12i ww_s12j ww_s12n ww_s12o ->
                    let {
                      ww_s12v
                      ww_s12v
                        = let {
                            z
                            z = map ww_s12i ww_s12o } in
                          letrec {
                            go
                            go
                              = \ ds ->
                                  case ds of {
                                    [] -> z;
                                    : y ys -> : (y ww_s12n) (go ys)
                                  }; } in
                          go ww_s12j } in
                    (# ww_s12i ww_s12n, ww_s12v #)
     Cont:   ApplyToTy a
             ApplyToTy a
             ApplyToVal nodup ww_s12i
             ApplyToVal nodup ww_s12j
             ApplyToVal nodup ww_s12n
             ApplyToVal nodup ww_s12o
             Select nodup ww_s12s
             Stop[BoringCtxt] (a, [a])
 }}}

 So it seems that after splitting the function into two pieces, it is small
 enough(?) so that both pieces inline? But that seems to be suboptimal: If
 we are going to inline both pieces anyways, can we not do it earlier, and
 thus enable useful fusion?

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


More information about the ghc-tickets mailing list