
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

On 4 October 2010 03:40, Michael Vanier
newtype MyMonad a = MyMonad ((StateT (MyData a) (Either SomeError) a)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable)
I think it's the `a'. I think it needs to be a concrete type. E.g. the following is OK: newtype MyMonad a = MyMonad ((StateT (MyData ()) (Either SomeError) a)) deriving (Monad, MonadState (MyData ()), MonadError SomeError, Typeable) But newtype MyMonad a = MyMonad ((StateT (MyData ()) (Either SomeError) [a])) deriving (Monad, MonadState (MyData ()), MonadError SomeError, Typeable) is not. This reminds me of the restriction that impredicative types remove, but I don't think it's related.
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.
It seems like eta-reducing `X' or `x' is "enough", but Foo x,, i.e. a parametrized type with a type variable isn't "enough". I think that's what's going on, but I don't know why.

Hmm, it seems like MonadState can be derived even with a non-concrete type, for instance: ---------- {-# 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 newtype MyMonad a b = MyMonad ((StateT (MyData a) (Either SomeError) b)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable) ---------- This compiles without errors. So it looks to me like the real problem was the implicit dependency between the type 'a' in MyData and the return type 'b' of the monad, which the deriving mechanism couldn't enforce if 'b' was 'a'. I'm finding it hard to get a good conceptual understanding of what's really going on here. Mike On 10/3/10 7:03 PM, Christopher Done wrote:
On 4 October 2010 03:40, Michael Vanier
wrote: newtype MyMonad a = MyMonad ((StateT (MyData a) (Either SomeError) a)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable) I think it's the `a'. I think it needs to be a concrete type. E.g. the following is OK:
newtype MyMonad a = MyMonad ((StateT (MyData ()) (Either SomeError) a)) deriving (Monad, MonadState (MyData ()), MonadError SomeError, Typeable)
But
newtype MyMonad a = MyMonad ((StateT (MyData ()) (Either SomeError) [a])) deriving (Monad, MonadState (MyData ()), MonadError SomeError, Typeable)
is not. This reminds me of the restriction that impredicative types remove, but I don't think it's related.
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. It seems like eta-reducing `X' or `x' is "enough", but Foo x,, i.e. a parametrized type with a type variable isn't "enough". I think that's what's going on, but I don't know why.

On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier
{- This doesn't work: -} newtype MyMonad a = MyMonad ((StateT (MyData a) (Either SomeError) a)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable)
This simply isn't allowed by the generalised newtype derivation machinery, because the type variable "a" appears in one of the classes you're deriving. In fact, I'm not sure how you're hoping for your type to actually work as a monad. If you try using (>>=) on your type synonym that currently appears to typecheck, you'll find that the only value that can inhabit the state parameter is bottom. Try writing out and using a definition of (>>=) by hand to understand your confusion.

On 10/3/10 7:06 PM, Bryan O'Sullivan wrote:
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier
mailto:mvanier42@gmail.com> wrote: {- This doesn't work: -} newtype MyMonad a = MyMonad ((StateT (MyData a) (Either SomeError) a)) deriving (Monad, MonadState (MyData a), MonadError SomeError, Typeable)
This simply isn't allowed by the generalised newtype derivation machinery, because the type variable "a" appears in one of the classes you're deriving.
In fact, I'm not sure how you're hoping for your type to actually work as a monad. If you try using (>>=) on your type synonym that currently appears to typecheck, you'll find that the only value that can inhabit the state parameter is bottom. Try writing out and using a definition of (>>=) by hand to understand your confusion. I disagree with your second point. I have this in working code:
---------- newtype StateErrorIO e s a = StateErrorIO { runS :: (StateT s (ErrorT e IO) a) } deriving (Monad, MonadIO, MonadState s, MonadError e, Typeable) ---------- I can assure you that it works on non-bottom types. As for the first point, that makes sense. So if I do this: ---------- newtype MyMonadS s a = MyMonad ((StateT s (Either SomeError) a)) deriving (Monad, MonadState s, MonadError SomeError, Typeable) type MyMonad a = MyMonadS (MyData a) a ---------- it type checks. And yeah, writing out the instances by hand is the best way to understand what's going on. Mike
participants (3)
-
Bryan O'Sullivan
-
Christopher Done
-
Michael Vanier