Typechecker regression in GHC 8.0.2 involving DefaultSignatures
This code compiles without issue on GHC 8.0.1 and earlier, but not with GHC 8.0.2 or HEAD. This was adapted from the monad-logger library (which fails to build with GHC 8.0.2 and HEAD due to the same issue):
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE GADTs #-}
module MonadLogger where
import Control.Monad.IO.Class
import qualified Control.Monad.Trans.Class as Trans
import Control.Monad.Trans.Identity
data Loc
data LogSource
data LogLevel
data LogStr
class ToLogStr msg
class Monad m => MonadLogger m
class (MonadLogger m, MonadIO m) => MonadLoggerIO m where
askLoggerIO :: m (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
default askLoggerIO :: (Trans.MonadTrans t, MonadLogger (t m), MonadIO (t m))
=> t m (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
askLoggerIO = Trans.lift askLoggerIO
instance MonadLogger m => MonadLogger (IdentityT m)
instance MonadLoggerIO m => MonadLoggerIO (IdentityT m)
On GHC HEAD, this fails with:
[1 of 1] Compiling MonadLogger ( MonadLogger.hs, interpreted )
MonadLogger.hs:23:10: error:
• Couldn't match type ‘m’ with ‘IdentityT m’
‘m’ is a rigid type variable bound by
the instance declaration at MonadLogger.hs:23:10-55
Expected type: IdentityT
m (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
Actual type: IdentityT
(IdentityT m) (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
• In the expression: MonadLogger.$dmaskLoggerIO @IdentityT m
In an equation for ‘askLoggerIO’:
askLoggerIO = MonadLogger.$dmaskLoggerIO @IdentityT m
In the instance declaration for ‘MonadLoggerIO (IdentityT m)’
• Relevant bindings include
askLoggerIO :: IdentityT
m (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
(bound at MonadLogger.hs:23:10)
This stopped typechecking after d2958bd0 (i.e, #12220 (closed)).
As a workaround, you can change the default signature to:
default askLoggerIO :: (Trans.MonadTrans t, MonadLoggerIO n, t n ~ m)
=> t n (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
And it'll work.
Any thoughts on this, Simon?
Trac metadata
Trac field | Value |
---|---|
Version | 8.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | highest |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | simonpj |
Operating system | |
Architecture |