
I'm 90% sure you have MonadIO and RWST imported from different versions of
transformers. Try to load the code into ghci and check ':i MonadIO' and ':i
RWST'. If you'll see fully qualified (including package name and version)
names somewhere, then that is the issue.
See also
http://stackoverflow.com/questions/11068272/acid-state-monadstate-instance-f...
07.07.2014 6:19 пользователь "Kazu Yamamoto"
Hi cafe,
I noticed that strange behavior of GHC 7.8.2. Consider the following example which requires the "ghc" package:
---- {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module A where
import GHC import MonadUtils import Control.Monad.Trans.RWS.Lazy (RWST(..))
newtype M a = M (RWST () () () IO a) deriving (Functor,Applicative,Monad,MonadIO) ----
The "ghc" library depends on "transformers" 0.3.0.0. If "transformers" *0.4.1.0* is NOT installed, GHCi can handle the code above well:
---- % ghci -package ghc A.hs ... Loading package transformers-0.3.0.0 ... linking ... done. ... Ok, modules loaded: A. [*A]
----
However, if "transformers" *0.4.1.0* is installed, an error happens:
---- % cabal install transformers % ghci -package ghc A.hs ... Loading package transformers-0.3.0.0 ... linking ... done. ... [1 of 1] Compiling A ( A.hs, interpreted )
A.hs:10:49: No instance for (MonadIO (RWST () () () IO)) 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 (MonadIO M) Failed, modules loaded: none. [Prelude]
----
A you can see, "transformers" 0.3.0.0 is certainly linked. How can I interpret this behavior?
If this is a bug of GHC 7.8.2, I will file this to GHC's trac.
P.S.
We noticed this because "doctest" of ghc-mod fails only for GHC 7.8.2.
--Kazu
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe