
#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: 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): Ok, here is a better example. Class `C` should have a default implementation for every generic type that is not a sum. Instead of omitting the instance for `:+:`, I use a `TypeError` in the head of the instance for `:+:` to provide a more clear error message. {{{#!haskell {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeOperators #-} module T where import GHC.TypeLits(TypeError, ErrorMessage(..)) import qualified GHC.Generics as Gen class C a where f :: a -> () default f :: (Gen.Generic a, GC (Gen.Rep a)) => a -> () f = gf . Gen.from class GC b where gf :: b x -> () instance GC x => GC (Gen.M1 i c x) where gf (Gen.M1 x) = gf x instance GC Gen.V1 where gf _ = () instance GC Gen.U1 where gf _ = () instance GC (Gen.K1 i t) where gf _ = () instance GC (l Gen.:*: r) where gf _ = () instance TypeError ('Text "Can't derive C for sums") => GC (l Gen.:+: r) where gf _ = error "unreachable" data TV deriving (Gen.Generic, C) data TU = TU deriving (Gen.Generic, C) data TK = TK Int deriving (Gen.Generic, C) data TP = TP Int Int deriving (Gen.Generic, C) data TS = TSL | TSR deriving (Gen.Generic, C) -- should reject right away }}} This program is accepted, but any attempt to use the instance will fail at compile time. I find this surprising and less useful than rejecting the program right away. If one instead uses one of: {{{#!haskell instance C TS -- or deriving instance C TS }}} the program is rejected (with the intended error message). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15052#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler