[Haskell-cafe] Failure deriving MonadRWS when using a type-family for the State part
Nicolas Trangez
nicolas at incubaid.com
Tue May 21 00:08:08 CEST 2013
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
More information about the Haskell-Cafe
mailing list