[Haskell-cafe] rewrite rules
Ryan Ingram
ryani.spam at gmail.com
Mon Jun 22 12:38:41 EDT 2009
Not 100% sure (especially without source/core), but my guess is that
the higher-rank types make the rule unlikely to fire.
Try -ddump-simpl to see the core output, and look for places where you
expect the rule to fire. I suspect you will find that the types of f
and g are not "forall" at that point in the code, but have already
been specialized.
Is there a reason you cannot use this simpler rule?
{-# RULES "transform/tranform" forall f g l. transform f (transform g
l) = transform (g.f) l #-}
-- ryan
On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd Visscher<sjoerd at w3future.com> 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