Well it's debatable. Suppose we have

  newtype Foo = MkFoo String deriving( Num )

Do you want to generate

  instance Num String => Num Foo

?  I suspect not -- usually we generate an error message right away if we need 
a Num String instance and one is not available.

Now you could argue that

|      MonadError String m => MonadError String (MyMonad m)

is more plausible because the 'm' is somehow the important bit.  But it gets 
into undecidable-instance territory, and at that point you (now) just have to 
write the instance declaration yourself.

The manual is misleading on this point.  It says "for each ci, the derived 
instance declaration is: instance ci t => ci (T v1...vk)".  But actually GHC 
tries to figure out the context, just as for other derived instance decls, and 
insists (for the reasons above) that it reduces to type variables only.

Does that make sense?  I'll update the documentation if so.

Simon

-----Original Message-----
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of
| Twan van Laarhoven
| Sent: 03 November 2007 18:08
| To: glasgow-haskell-users@haskell.org
| Subject: Generalized newtype deriving 6.6 vs. 6.8
|
| Hello,
|
| I noticed there is a difference in generalized newtype deriving between
| 6.6 and 6.8. In GHC 6.4.1 the following:
|
|  > {-# LANGUAGE GeneralizedNewtypeDeriving #-}
|  >
|  > import Control.Monad.Error
|  >
|  > newtype MyMonad m a = MyMonad (m a)
|  >   deriving (Monad, MonadError String)
|
| correctly gives a derived instance
|
|      MonadError String m => MonadError String (MyMonad m)
|
| The new GHC 6.8.1 complains with:
|
|      No instance for (MonadError String m)
|        arising from the 'deriving' clause of a data type declaration
|                     at DeriveTest.hs:(5,0)-(6,36)
|      Possible fix: add an instance declaration for (MonadError String m)
|      When deriving the instance for (MonadError String (MyMonad m))
|
| Generalizing the instance to
|
|      MonadError e m => MonadError e (MyMonad m)
|
| works in both versions.
|
| Twan
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to