
#10753: Type checker fails to recognize equality -------------------------------------+------------------------------------- Reporter: ljli | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE KindSignatures #-} module Test where import qualified Control.Monad.State as S class HasConns (m :: * -> *) where type Conn m foo :: (HasConns m, Monad m) => S.StateT (Conn m) m () foo = do _ <- S.get return () }}} This fails to compile with GHC 7.10.2: {{{ Could not deduce (S.MonadState (Conn m) (S.StateT (Conn m) m)) arising from a use of ‘S.get’ from the context (HasConns m, Monad m) bound by the type signature for foo :: (HasConns m, Monad m) => S.StateT (Conn m) m () }}} It compiles with GHC 7.8.4, though. Adding "Conn m ~ Conn m" to the type context of foo lets it compile again. This seems not right to me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10753 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler