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<mvanie...@gmail.com> 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.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe