[GHC] #14836: GHC fails to infer implied superclass constraint

GHC ghc-devs at haskell.org
Wed Feb 21 18:29:13 UTC 2018


#14836: GHC fails to infer implied superclass constraint
-------------------------------------+-------------------------------------
           Reporter:  crockeea       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code should compile, but does not.
 {{{
 {-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

 module Bug where

 class (Monad m) => RequiresMonad m where

 class (Monad m) => ImpliesMonad m where

 instance (ImpliesMonad m) => RequiresMonad m where
 }}}

 The basic idea is that I put the constraint `ImpliesMonad m` on the
 `RequiresMonad` instance, which does in fact imply `Monad m`. However, GHC
 complains:
 {{{
     • Could not deduce (Monad m)
         arising from the superclasses of an instance declaration
       from the context: ImpliesMonad m
         bound by the instance declaration
         at Bug.hs:9:10-44
       Possible fix:
         add (Monad m) to the context of the instance declaration
     • In the instance declaration for ‘RequiresMonad m’
 }}}

 Of course, GHC is perfectly happy if I replace the instance constraint
 `ImpliesMonad m` with `Monad m`.

 Possibly related to #10338 or #11948.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14836>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list