
I'm having a problem with a simple monad transformer stack that has me stumped. Here's the sample code: {-# LANGUAGE GeneralizedNewtypeDeriving #-} import Control.Monad.Error import Control.Monad.State import Data.Typeable data SomeError = Error1 | Error2 | ErrorFail deriving (Eq, Show, Typeable) data MyData a = MyData [a] instance Error SomeError where noMsg = ErrorFail {- This works: -} {- newtype StateError e s a = StateError ((StateT s (Either e) a)) deriving (Monad, MonadState s, MonadError e, Typeable) type MyMonad a = StateError SomeError (MyData a) a -} {- This doesn't work: -} newtype MyMonad a = MyMonad ((StateT (MyData a) (Either SomeError) a)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable) ---------- Basically, the more abstracted (commented-out) version works, but the more specific one gives this error: Weird.hs:33:12: Can't make a derived instance of `Monad MyMonad' (even with cunning newtype deriving): cannot eta-reduce the representation type enough In the newtype declaration for `MyMonad' Weird.hs:34:12: Cannot eta-reduce to an instance of form instance (...) => MonadState (MyData a) MyMonad In the newtype declaration for `MyMonad' Weird.hs:35:12: Can't make a derived instance of `MonadError SomeError MyMonad' (even with cunning newtype deriving): cannot eta-reduce the representation type enough In the newtype declaration for `MyMonad' These error messages mean nothing to me. What's going on? Can the more specific code be made to work? This is with ghc 6.12.3. Thanks, Mike