[GHC] #7994: Make foldl into a good consumer

GHC ghc-devs at haskell.org
Sun Jan 26 12:30:15 UTC 2014


#7994: Make foldl into a good consumer
-------------------------------------+------------------------------------
        Reporter:  simonpj           |            Owner:
            Type:  bug               |           Status:  new
        Priority:  normal            |        Milestone:
       Component:  Compiler          |          Version:  7.6.3
      Resolution:                    |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------------

Comment (by nomeata):

 The trick with `oneShot` is neat, and it works for `foo x = sum  $ [f i |
 i <- [1 .. x]]` and `foo x = sum  $ [f i | i <- [1 .. x] , odd i ]` (note
 the filter), but does not yield optimal code for nested iterations like
 `foo x = sum  $ concat [[f i | i <- [1 .. n]]| n <- [1..x]]`, where we
 get:

 {{{
         letrec {
           go_a1mU [Occ=LoopBreaker]
             :: GHC.Prim.Int#
                -> Data.Complex.Complex GHC.Types.Double
                -> Data.Complex.Complex GHC.Types.Double
           [LclId, Arity=1, Str=DmdType <L,U>]
           go_a1mU =
             \ (x_a1mV :: GHC.Prim.Int#) ->
               let {
                 n_X1nv
                   :: Data.Complex.Complex GHC.Types.Double
                      -> Data.Complex.Complex GHC.Types.Double
                 [LclId, Str=DmdType]
                 n_X1nv =
                   case GHC.Prim.tagToEnum#
                          @ GHC.Types.Bool (GHC.Prim.==# x_a1mV ww_s1ro)
                   of _ [Occ=Dead] {
                     GHC.Types.False -> go_a1mU (GHC.Prim.+# x_a1mV 1);
                     GHC.Types.True ->
                       GHC.Base.id @ (Data.Complex.Complex
 GHC.Types.Double)
                   } } in
               case GHC.Prim.tagToEnum# @ GHC.Types.Bool (GHC.Prim.># 1
 x_a1mV)
               of _ [Occ=Dead] {
                 GHC.Types.False ->
                   letrec {
                     go1_X1nG [Occ=LoopBreaker]
                       :: GHC.Prim.Int#
                          -> Data.Complex.Complex GHC.Types.Double
                          -> Data.Complex.Complex GHC.Types.Double
                     [LclId, Arity=2, Str=DmdType <L,U><L,1*U(U(U),U(U))>]
                     go1_X1nG =
                       \ (x1_X1nI :: GHC.Prim.Int#)
                         (eta_B1 :: Data.Complex.Complex GHC.Types.Double)
 ->
                         let {
                           a_s1pu [Dmd=<L,U(U(U),U(U))>]
                             :: Data.Complex.Complex GHC.Types.Double
                           [LclId, Str=DmdType]
                           a_s1pu =
                             case eta_B1 of _ [Occ=Dead] { Data.Complex.:+
 ww2_a10M ww3_a10N ->
                             case ww2_a10M of _ [Occ=Dead] { GHC.Types.D#
 ww5_s1ub ->
                             case ww3_a10N of _ [Occ=Dead] { GHC.Types.D#
 ww7_s1ud ->
                             case Foo.f (GHC.Types.I# x1_X1nI)
                             of _ [Occ=Dead] { Data.Complex.:+ ww9_a10Z
 ww10_a110 ->
                             case ww9_a10Z of _ [Occ=Dead] { GHC.Types.D#
 ww12_s1uf ->
                             case ww10_a110 of _ [Occ=Dead] { GHC.Types.D#
 ww14_s1uh ->
                             Data.Complex.:+
                               @ GHC.Types.Double
                               (GHC.Types.D# (GHC.Prim.+## ww5_s1ub
 ww12_s1uf))
                               (GHC.Types.D# (GHC.Prim.+## ww7_s1ud
 ww14_s1uh))
                             }
                             }
                             }
                             }
                             }
                             } } in
                         case GHC.Prim.tagToEnum#
                                @ GHC.Types.Bool (GHC.Prim.==# x1_X1nI
 x_a1mV)
                         of _ [Occ=Dead] {
                           GHC.Types.False -> go1_X1nG (GHC.Prim.+# x1_X1nI
 1) a_s1pu;
                           GHC.Types.True -> n_X1nv a_s1pu
                         }; } in
                   go1_X1nG 1;
                 GHC.Types.True -> n_X1nv
               }; } in
         go_a1mU 1 Foo.foo1;
 }}}

 I guess we’d want `n_X1nv` to have arity one here, and be eta-expanded, so
 that it turns into a join-point, do we?

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


More information about the ghc-tickets mailing list