Failure deriving MonadRWS when using a type-family for the State part

All, The following code results in a compilation error (I tried GHC 7.4.1 & a 7.7.20130430 build): {-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving, StandaloneDeriving #-} module Main where import Control.Applicative import Control.Monad.RWS data C = C data E = E data S1 = S1 Int type family I a :: * type instance I S1 = Int newtype T a s m r = T { unT :: RWST C [E] (I s) m r } deriving ( Functor , Applicative , Monad , MonadReader C , MonadWriter [E] , MonadState (I s) , MonadRWS C [E] (I s) , MonadTrans ) Error: No instance for (MonadState (I s) (T a s m)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (MonadRWS C [E] (I s) (T a s m)) Commenting out the MonadRWS line from the derivings list (i.e. the line pointed at by the error) works as expected. I was somehow unable to get a suitable standalone-deriving clause working, so didn't test that. Is this expected? Regards, Nicolas

The mistake might be on my side, since I expected the following to work (but it doesn't, most likely for good reason, I didn't read any TypeFamilies papers yet): {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} module Main where import Control.Monad.State data S = S T data T = T type family F s :: * type instance F S = T newtype MT s m r = MT { unMT :: StateT (F s) m r } deriving (Monad, MonadState (F s)) -- foo :: Monad m => MT S m T -- foo = get {- Could not deduce (MonadState T (MT S m)) arising from a use of `get' from the context (Monad m) bound by the type signature for foo :: Monad m => MT S m T at tf2.hs:17:1-9 Possible fix: add (MonadState T (MT S m)) to the context of the type signature for foo :: Monad m => MT S m T or add an instance declaration for (MonadState T (MT S m)) In the expression: get In an equation for `foo': foo = get while GHCi says, as expected: λ :i MT newtype MT s m r = MT {unMT :: StateT (F s) m r} -- Defined at tf2.hs:13:9 instance Monad m => Monad (MT s m) -- Defined at tf2.hs:14:13 instance Monad m => MonadState (F s) (MT s m) -- Defined at tf2.hs:14:20 and λ :t undefined :: F S undefined :: F S :: T -} Nicolas On Tue, 2013-05-21 at 00:08 +0200, Nicolas Trangez wrote:
All,
The following code results in a compilation error (I tried GHC 7.4.1 & a 7.7.20130430 build):
{-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving, StandaloneDeriving #-}
module Main where
import Control.Applicative import Control.Monad.RWS
data C = C data E = E
data S1 = S1 Int
type family I a :: * type instance I S1 = Int
newtype T a s m r = T { unT :: RWST C [E] (I s) m r } deriving ( Functor , Applicative , Monad , MonadReader C , MonadWriter [E] , MonadState (I s) , MonadRWS C [E] (I s) , MonadTrans )
Error:
No instance for (MonadState (I s) (T a s m)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (MonadRWS C [E] (I s) (T a s m))
Commenting out the MonadRWS line from the derivings list (i.e. the line pointed at by the error) works as expected. I was somehow unable to get a suitable standalone-deriving clause working, so didn't test that.
Is this expected?
Regards,
Nicolas
participants (1)
-
Nicolas Trangez