Type binders in rules

Simon Peyton-Jones simonpj at microsoft.com
Fri Sep 19 04:37:10 EDT 2008


Friends

This is a message for people who use RULES, to ask your opinion.  Have a look at
        http://hackage.haskell.org/trac/ghc/ticket/2600
and add your comments if you want.  The intro to the ticket appears below, so you can get an idea of whether you are interested.

Simon



Roman writes: I found an example I came across while working on the recycling paper and which I subsequently forgot about. Suppose we have:

{-# LANGUAGE Rank2Types #-}
module T where

class T t where
   to   :: [a] -> t a
   from :: t a -> [a]
   tmap :: (a -> a) -> t a -> t a

{-# RULES

"myrule" forall f x.
     from (tmap f (to x)) = map f (from (to x))
  #-}

Alas, this fails with:

     Ambiguous type variable `t' in the constraint:
       `T t' arising from a use of `to' at T.hs:12:40-43
     Probable fix: add a type signature that fixes these type variable(s)

Of course, I'd like the t on the rhs to be the same as on the lhs but I don't see how to tell this to GHC. Is it actually possible? The only solution I've found was to add a dummy argument to 'to':

to' :: t a -> [a] -> t a

to = to' undefined

{-# RULES

"myrule" forall f t x.
     from (tmap f (to' t x)) = map f (from (to' t x))
  #-}

That's ugly, of course. Am I missing something or is this just impossible to do with the current system?


More information about the Glasgow-haskell-users mailing list