“Ambiguous type variable in the constraint” error in rewrite rule

Tsuyoshi Ito tsuyoshi.ito.2006 at gmail.com
Wed Jul 11 05:39:56 CEST 2012


Hello,

Why does GHC 7.4.1 reject the rewrite rule in the following code?

> module Test where
>
> import Data.Monoid
> import Control.Monad.Writer.Strict
>
> f :: Monad m => a -> m a
> f = return
>
> g :: Monoid w => a -> Writer w a
> g = return
>
> {-# RULES
> "f->g" f = g
>   #-}

On the line containing the rewrite rule, GHC shows the following error message:

Test.hs:13:12:
    Ambiguous type variable `w0' in the constraint:
      (Monoid w0) arising from a use of `g'
    Probable fix: add a type signature that fixes these type variable(s)
    In the expression: g
    When checking the transformation rule "f->g"

Interestingly, the code compiles if the rewrite rule is replaced with
the following SPECIALIZE pragma:

> {-# SPECIALIZE f :: Monoid w => a -> Writer w a #-}

I find this strange because if I am not mistaken, this specialization
is handled by using a rewrite rule of the same type as the one which
GHC rejects.

The following ticket might be related, but I am not sure:
    Subclass Specialization in Rewrite Rules
    http://hackage.haskell.org/trac/ghc/ticket/6102

Best regards,
  Tsuyoshi



More information about the Glasgow-haskell-users mailing list