#3660: "Var.tcTyVarDetails" exception w/ Assoc. Datatypes and Monad Transformers
---------------------------------------------------------+------------------
Reporter: jfredett | Owner:
Type: bug | Status:
closed
Priority: normal | Milestone:
Component: Compiler | Version:
6.10.4
Severity: minor | Resolution: fixed
Keywords: Monad Transformers, Associated Datatypes | Difficulty:
Unknown
Testcase: | Os: Linux
Architecture: x86 |
---------------------------------------------------------+------------------
Changes (by simonpj):
* status: new => closed
* difficulty: => Unknown
* resolution: => fixed
Comment:
Thanks. I had to add some imports thus:
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
module Foo where
import Control.Monad.State
import Control.Monad.Reader
data Email = Email
type Context = ReaderT Email
type Match t = StateT t IO
type ContextMatch t a = Context (Match t) a
newtype FilterState t => Filter t a = Filter (ContextMatch t a)
deriving (Functor, Monad, MonadReader Email, MonadState Bool,
MonadIO)
class FilterState t where
data FState t
deliver :: FState t -> IO ()
}}}
Happily this works ok in 6.12, and HEAD, saying
{{{
Foo.hs:12:51:
Couldn't match expected type `Bool' against inferred type `t'
`t' is a rigid type variable bound by
the instance declaration at Foo.hs:11:32
When using functional dependencies to combine
MonadState s (StateT s m),
arising from the dependency `m -> s'
in the instance declaration at <no location info>
MonadState Bool (StateT t IO),
arising from the instance declaration at Foo.hs:12:51-65
When checking the super-classes of an instance declaration
In the instance declaration for `MonadState Bool (Filter t)'
}}}
So I'll close the bug as fixed. Thank you for boiling it down.
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3660#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs