Fusion vs. inlining (Was: [Haskell-cafe] Fusion of lists and chunky sequences)

Roman Leshchinskiy rl at cse.unsw.edu.au
Tue Jan 8 00:29:31 EST 2008


Henning Thielemann wrote:
> 
> Anyway, I tried to wrap Prelude lists in a newtype and thus got GHC (still
> 6.4.1) to invoke my rules instead of the Prelude rules. But I encountered
> the following problem: I define something like
> 
>   nonFusable x y = fusable (aux x y)
> 
>  where fusion rules are defined for 'fusable', but not for 'nonFusable'. I
> hoped that 'nonFusable' will be inlined and then 'fusable' is fused with
> other expressions. This does not happen. If I state the function
> definition also as rule, then GHC fuses eagerly.

I suspect that fusable and/or aux are inlined into nonFusable when the 
latter is compiled. That's too early - you want nonFusable (with the 
simple definition above) to be inlined into the client code first. Adding

   {-# INLINE nonFusable #-}

should take care of this.

>  Analogously I observed that usage of ($) and (.) blocks fusion, and when
> I add the rules
> 
>   "unfold-dollar" forall f x.
>      f $ x = f x ;
> 
>   "unfold-dot" forall f g.
>      f . g  =  \x -> f (g x) ;
> 
>  then fusion takes place as expected.

That shouldn't be necessary, these two ought to be inlined. Do you have 
a concrete example where this happens?

Roman



More information about the Haskell-Cafe mailing list