Extending fold/build fusion

Akio Takano tkn.akio at gmail.com
Sat Feb 1 07:52:01 UTC 2014


On Sat, Feb 1, 2014 at 12:17 AM, Joachim Breitner
<mail at joachim-breitner.de> wrote:
> Dar Akio,
>
> I just noticed that even with your approach, the code for foldl-as-foldr
> is not automatically beautiful. Consider this:
>
> I modified the eft function to do to some heavy work at each step (or at
> least to look like that):
>
> myEft :: Int -> Int -> [Int]
> myEft = \from to -> buildW (myEftFB from to)
> {-# INLINE myEft #-}
>
> expensive :: Int -> Int
> expensive = (1+)
> {-# NOINLINE expensive #-}
>
> myEftFB
>   :: Int
>   -> Int
>   -> (Wrap f r)
>   -> (Int -> r -> r)
>   -> r
>   -> r
> myEftFB from to (Wrap wrap unwrap) cons nil = wrap go from nil
>   where
>     go = unwrap $ \i rest -> if i <= to
>       then cons i $ wrap go (expensive i) rest
>       else rest
> {-# INLINE[0] myEftFB #-}
>
> Then I wanted to see if "sum [f..t]" using this code is good:
>
> sumUpTo :: Int -> Int -> Int
> sumUpTo f t = WW.foldl' (+) 0 (myEft f t)
>
> And this is the core I get for the inner loop:
>
>     letrec {
>       $wa :: GHC.Prim.Int# -> GHC.Types.Int -> GHC.Types.Int
>       [LclId, Arity=1, Str=DmdType L]
>       $wa =
>         \ (ww2 :: GHC.Prim.Int#) ->
>           case GHC.Prim.<=# ww2 ww1 of _ {
>             GHC.Types.False -> GHC.Base.id @ GHC.Types.Int;
>             GHC.Types.True ->
>               let {
>                 e [Dmd=Just D(L)] :: GHC.Types.Int
>                 [LclId, Str=DmdType]
>                 e = F.expensive (GHC.Types.I# ww2) } in
>               \ (acc :: GHC.Types.Int) ->
>                 case acc of _ { GHC.Types.I# x ->
>                 case e of _ { GHC.Types.I# ww3 ->
>                 $wa ww3 (GHC.Types.I# (GHC.Prim.+# x ww2))
>                 }
>                 }
>           }; } in
>     $wa ww F.sumUpTo1
>
> (GHC 7.6.3, -O).
>
> See how it is still building up partial applications. So I am a bit
> confused now: I thought the (or one) motivation for your proposal is to
> produce good code in these cases. Or am I using your code wrongly?

Yes, this is supposed to work. Fortunately it was an easy fix:

https://github.com/takano-akio/ww-fusion/commit/ae26b18b135d92e0df7513e5efc0388e085698bf

Thank you for pointing this out!

-- Akio

>
> Greetings,
> Joachim
>
> --
> Joachim "nomeata" Breitner
>   mail at joachim-breitner.de * http://www.joachim-breitner.de/
>   Jabber: nomeata at joachim-breitner.de  * GPG-Key: 0x4743206C
>   Debian Developer: nomeata at debian.org


More information about the ghc-devs mailing list