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

2012-07-16 Thread Simon Peyton-Jones
| > Ah! This rule will only match if the LHS is | > | > f (WriterT w Identity) ($fMonadWriterT w Identity dm | > $fMonadIdentity) | > | > So it's a nested pattern match. That makes the LHS match less often; | namely only when the dictionary argument to 'f' is an application of | $fMonadWr

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

2012-07-15 Thread Tsuyoshi Ito
's the LHS pattern. > > > So I hope that explains better what is happening. If anyone can think of > better behaviour, I'm open to suggestions! > > Simon > > > | -Original Message- > | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow- &g

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

2012-07-12 Thread Simon Peyton-Jones
ter what is happening. If anyone can think of better behaviour, I'm open to suggestions! Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow- | haskell-users-boun...@haskell.org] On Behalf Of Tsuyoshi Ito | Sent: 11 July 2012 04:40 | To: glasgow-ha

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

2012-07-10 Thread Tsuyoshi Ito
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 co