GHC 9.6.1 rejects previously working code

Harendra Kumar harendra.kumar at gmail.com
Wed Apr 12 09:02:43 UTC 2023


The following code compiles with older compilers but does not compile with
GHC 9.6.1:

{-# LANGUAGE KindSignatures #-}
module A () where

import Control.Monad.IO.Class
import Control.Monad.Trans.Class

data T (m :: * -> *) a = T

instance Functor (T m) where
    fmap f T = undefined

instance Applicative (T m) where
    pure = undefined
    (<*>) = undefined

instance MonadIO m => Monad (T m) where
    return = pure
    (>>=) = undefined

instance MonadTrans T where
    lift = undefined

It fails with the following error:

xx.hs:20:10: error: [GHC-39999]
    • Could not deduce ‘MonadIO m’
        arising from the head of a quantified constraint
        arising from the superclasses of an instance declaration
      from the context: Monad m
        bound by a quantified context at xx.hs:20:10-21
      Possible fix:
        add (MonadIO m) to the context of a quantified context
    • In the instance declaration for ‘MonadTrans T’
   |
20 | instance MonadTrans T where
   |          ^^^^^^^^^^^^

What is the correct resolution for this?

-harendra
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20230412/83c1c2ab/attachment.html>


More information about the ghc-devs mailing list