
#15231: UndecidableInstances validity checking is wrong in the presence of QuantifiedConstraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 (Type checker) | Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this program: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE QuantifiedConstraints #-} module Bug where import Data.Kind data ECC :: Constraint -> Type -> Type class Y a class Z a instance c => Y (ECC c a) instance (c => Z a) => Z (ECC c a) }}} I would expect both of these instances to work. But while GHC accepts the `Y` instance, it rejects the `Z` instance: {{{ $ ~/Software/ghc5/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:15:10: error: • Variable ‘c’ occurs more often in the constraint ‘c’ than in the instance head (Use UndecidableInstances to permit this) • In the instance declaration for ‘Z (ECC c a)’ | 15 | instance (c => Z a) => Z (ECC c a) | ^^^^^^^^^^^^^^^^^^^^^^^^^ }}} That error message seems completely bogus to me, since `c` appears once in both the context and instance head in both instances. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15231 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler