#4952: Typechecking regression
----------------------------------------+-----------------------------------
    Reporter:  igloo                    |        Owner:              
        Type:  bug                      |       Status:  new         
    Priority:  highest                  |    Milestone:  7.0.2       
   Component:  Compiler (Type checker)  |      Version:  7.0.1       
    Keywords:                           |     Testcase:              
   Blockedby:                           |   Difficulty:              
          Os:  Unknown/Multiple         |     Blocking:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------
 7.0.1 accepts this module (cut down from hashed-storage-0.5.4):
 {{{
 {-# LANGUAGE UndecidableInstances,
              MultiParamTypeClasses,
              KindSignatures,
              FlexibleInstances,
              FunctionalDependencies #-}

 module Storage.Hashed.Monad () where

 class Monad m => TreeRO m where
     withDirectory :: (MonadError e m) => Int -> m a -> m a
     expandTo :: (MonadError e m) => Int -> m Int

 instance (Monad m, MonadError e m) => TreeRO (M m) where
     expandTo = undefined
     withDirectory dir _ = do
       _ <- expandTo dir
       undefined

 data M (m :: * -> *) a

 instance Monad m => Monad (M m) where
     (>>=) = undefined
     return = undefined

 instance MonadError e m => MonadError e (M m)

 class Monad m => MonadError e m | m -> e
 }}}
 but 7.0 branch says:
 {{{
 [1 of 1] Compiling Storage.Hashed.Monad ( Storage/Hashed/Monad.hs,
 interpreted )

 Storage/Hashed/Monad.hs:17:12:
     Could not deduce (MonadError e1 m) arising from a use of `expandTo'
     from the context (Monad m, MonadError e m)
       bound by the instance declaration
       at Storage/Hashed/Monad.hs:14:10-50
     or from (MonadError e1 (M m))
       bound by the type signature for
                  withDirectory :: MonadError e1 (M m) => Int -> M m a -> M
 m a
       at Storage/Hashed/Monad.hs:(16,5)-(18,15)
     Possible fix:
       add (MonadError e1 m) to the context of
         the type signature for
           withDirectory :: MonadError e1 (M m) => Int -> M m a -> M m a
         or the instance declaration
     In a stmt of a 'do' expression: _ <- expandTo dir
     In the expression:
       do { _ <- expandTo dir;
            undefined }
     In an equation for `withDirectory':
         withDirectory dir _
           = do { _ <- expandTo dir;
                  undefined }
 Failed, modules loaded: none.
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4952>
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

Reply via email to