[Haskell-cafe] rewrite rules
Sjoerd Visscher
sjoerd at w3future.com
Mon Jun 22 05:41:33 EDT 2009
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
More information about the Haskell-Cafe
mailing list