
#8053: unification error with ghc head --------------------------------------------+------------------------------ Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by carter): {{{ [28 of 96] Compiling Control.Monad.AnyCont.Class ( src/Control/Monad/AnyCont/Class.hs, dist/build/Control/Monad/AnyCont/Class.o ) src/Control/Monad/AnyCont/Class.hs:29:16: Cannot instantiate unification variable ‛a1’ with a type involving foralls: forall r. (a -> b r) -> b r Perhaps you want -XImpredicativeTypes In the expression: lift . anyContToM In an equation for ‛anyContToM’: anyContToM = lift . anyContToM In the instance declaration for ‛MonadAnyCont b (StateT s m)’ src/Control/Monad/AnyCont/Class.hs:29:23: Cannot instantiate unification variable ‛a1’ with a type involving foralls: forall r. (a -> b1 r) -> b1 r Perhaps you want -XImpredicativeTypes In the second argument of ‛(.)’, namely ‛anyContToM’ In the expression: lift . anyContToM src/Control/Monad/AnyCont/Class.hs:36:16: Cannot instantiate unification variable ‛a0’ with a type involving foralls: forall r. (a -> b r) -> b r Perhaps you want -XImpredicativeTypes In the expression: lift . anyContToM In an equation for ‛anyContToM’: anyContToM = lift . anyContToM In the instance declaration for ‛MonadAnyCont b (ErrorT e m)’ src/Control/Monad/AnyCont/Class.hs:36:23: Cannot instantiate unification variable ‛a0’ with a type involving foralls: forall r. (a -> b0 r) -> b0 r Perhaps you want -XImpredicativeTypes In the second argument of ‛(.)’, namely ‛anyContToM’ In the expression: lift . anyContToM Failed to install llvm-general-3.4.0.0 }}} the relevant modules are {{{ {-# LANGUAGE RankNTypes, MultiParamTypeClasses, UndecidableInstances #-} module Control.Monad.AnyCont.Class where import Control.Monad.Trans.Class import Control.Monad.Trans.AnyCont (AnyContT) import qualified Control.Monad.Trans.AnyCont as AnyCont import Control.Monad.Trans.Error as Error import Control.Monad.Trans.State as State class ScopeAnyCont m where scopeAnyCont :: m a -> m a class MonadAnyCont b m where anyContToM :: (forall r . (a -> b r) -> b r) -> m a instance MonadTransAnyCont b m => MonadAnyCont b (AnyContT m) where anyContToM c = AnyCont.anyContT (liftAnyCont c) instance Monad m => ScopeAnyCont (AnyContT m) where scopeAnyCont = lift . flip AnyCont.runAnyContT return instance (Monad m, MonadAnyCont b m) => MonadAnyCont b (StateT s m) where anyContToM = lift . anyContToM instance ScopeAnyCont m => ScopeAnyCont (StateT s m) where scopeAnyCont = StateT . (scopeAnyCont .) . runStateT instance (Error e, Monad m, MonadAnyCont b m) => MonadAnyCont b (ErrorT e m) where anyContToM = lift . anyContToM instance ScopeAnyCont m => ScopeAnyCont (ErrorT e m) where scopeAnyCont = mapErrorT scopeAnyCont class MonadTransAnyCont b m where liftAnyCont :: (forall r . (a -> b r) -> b r) -> (forall r . (a -> m r) -> m r) instance MonadTransAnyCont b b where liftAnyCont c = c instance MonadTransAnyCont b m => MonadTransAnyCont b (StateT s m) where liftAnyCont c = (\c q -> StateT $ \s -> c $ ($ s) . runStateT . q) (liftAnyCont c) instance MonadTransAnyCont b m => MonadTransAnyCont b (ErrorT e m) where liftAnyCont c = (\c q -> ErrorT . c $ runErrorT . q) (liftAnyCont c) }}} and {{{ {-# LANGUAGE RankNTypes #-} module Control.Monad.Trans.AnyCont where import Control.Applicative import Control.Monad.Cont newtype AnyContT m a = AnyContT { unAnyContT :: forall r . ContT r m a } instance Functor (AnyContT m) where fmap f p = AnyContT $ fmap f . unAnyContT $ p instance Applicative (AnyContT m) where pure a = AnyContT $ pure a f <*> v = AnyContT $ unAnyContT f <*> unAnyContT v instance Monad m => Monad (AnyContT m) where AnyContT f >>= k = AnyContT $ f >>= unAnyContT . k return a = AnyContT $ return a fail s = AnyContT (ContT (\_ -> fail s)) instance MonadIO m => MonadIO (AnyContT m) where liftIO = lift . liftIO instance MonadTrans AnyContT where lift ma = AnyContT (lift ma) runAnyContT :: AnyContT m a -> (forall r . (a -> m r) -> m r) runAnyContT = runContT . unAnyContT anyContT :: (forall r . (a -> m r) -> m r) -> AnyContT m a anyContT f = AnyContT (ContT f) withAnyContT :: (forall r . (b -> m r) -> (a -> m r)) -> AnyContT m a -> AnyContT m b withAnyContT f m = anyContT $ runAnyContT m . f mapAnyContT :: (forall r . m r -> m r) -> AnyContT m a -> AnyContT m a mapAnyContT f m = anyContT $ f . runAnyContT m }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8053#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler