
#15052: DeriveAnyClass instances may skip TypeError constraints -------------------------------------+------------------------------------- Reporter: jcpetruzza | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jcpetruzza): I don't disagree with anything you are saying. The issue is that `deriving` is behaving differently from `instance` and from `deriving instance`. Consider this hopefully more clear example: {{{#!haskell {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} module T2 where import Data.Kind(Constraint) import GHC.TypeLits(TypeError, ErrorMessage(..)) class D a where f :: a default f :: DeferError a => a f = error "unreachable" type family DeferError a :: Constraint where DeferError a = TypeError ('Text "Boom") data X deriving D -- < -- ACCEPTED data Y instance D Y -- < -- REJECTED data Z deriving instance D Z -- < -- REJECTED }}} Do you aggree that either the three instances should be accepted here or the three instances should be rejected? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15052#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler