[Haskell-cafe] rewrite rules

Daniel Schüssler anotheraddress at gmx.de
Mon Jun 22 13:13:46 EDT 2009


Hi Sjoerd,

I don't know the cause of the problem, but if I add this rule, it works:

{-# RULES
   "inline_map" forall g x. map g x = transform (. g) x
 -#}

maybe, for whatever reason, the 'map' is inlined "too late" for the 
transform/transform rule to see it?


Greetings,
Daniel

On Monday 22 June 2009 11:41:33 Sjoerd Visscher wrote:
> Hi all,
>
> I have a rewrite rule as follows:
>
> {-# RULES
> "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -
>
>  > m))
>
>                               (g::forall m. Monoid m => (b -> m) -> (c
> -> m))
>                               (l::FMList c). transform f (transform g
> l) = transform (g.f) l
>    #-}
>
> It fires on this code:
>
>    print $ transform (. (*2)) (transform (. (+1)) (upto 10))
>
> But it doesn't fire on this code:
>
>    print $ map (*2) (map (+1) (upto 10)))
>
> with
>
>    map g x = transform (. g) x
>
> and with or without {-# INLINE map #-}.
>
> What am I doing wrong?
>
> --
> Sjoerd Visscher
> sjoerd at w3future.com
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list