
#15868: Standard deriving should be less conservative when `UndecidableInstances` is enabled -------------------------------------+------------------------------------- Reporter: edsko | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Exp where type family F a data T a = MkT (F a) deriving instance Eq (F a) => Eq (T a) data T2 a = T2 (T a) deriving (Eq) }}} results in a type error {{{ • No instance for (Eq (F a)) arising from the first field of ‘T2’ (type ‘T a’) }}} According the manual this is expected behaviour (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts... #inferred-context-for-deriving-clauses), but it is unfortunate; it seems to me that there is no deep reason that this instance should be rejected, other than an overly conservative check in the deriving machinery; I propose that this check is relaxed when the `UndecidableInstances` extension is enabled. Mind that I'm ''not'' proposing that it should also be able to infer the right constraints for `T` itself; but once I write such an explicit context myself once (for `T`), it seems to me that deriving the ''same'' constraints also for `T2` should be easy. Note that right now we can work-around this problem using {{{#!hs class Eq (F a) => EqF a deriving instance EqF a => Eq (T a) data T2 a = T2 (T a) deriving (Eq) }}} Normally however for such a class synonym we would then provide a single "authoritative" instance: {{{#!hs class Eq (F a) => EqF a instance Eq (F a) => EqF a }}} but if we do that then we are back at the same error for `T2`, because ghc will go from the `EqF a` constraint to the `Eq (F a)` constraint, and then refuse to add that constraint. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15868 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler