On Jun 22, 2009, at 6:38 PM, Ryan Ingram wrote:

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 #-}


Yes, this is the reason:

    Inferred type is less polymorphic than expected
      Quantified type variable `m' is mentioned in the environment:
        f :: (a -> m) -> b -> m (bound at Data/FMList.hs:124:29)
    In the first argument of `transform', namely `f'
    In the expression: transform f (transform g l)
    When checking the transformation rule "transform/transform"

This is the function:

transform :: (forall m. Monoid m => (a -> m) -> (b -> m)) -> FMList b - > FMList a
transform t l = FM $ \f -> unFM l (t f)

I'll have to clean things up before the core output becomes manageable.

Sjoerd

 -- ryan

On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd Visscher<sjo...@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
sjo...@w3future.com



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



--
Sjoerd Visscher
sjo...@w3future.com



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to