
#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics 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: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: @@ -7,0 +7,6 @@ + {-# LANGUAGE DefaultSignatures #-} + {-# LANGUAGE DeriveAnyClass #-} + {-# LANGUAGE DeriveGeneric #-} + {-# LANGUAGE FlexibleContexts #-} + {-# LANGUAGE ScopedTypeVariables #-} + {-# LANGUAGE TypeFamilies #-} New description: I was writing up an example to show off how `DeriveAnyClass` has improved since 639e702b6129f501c539b158b982ed8489e3d09c, and wouldn't you know it, the example doesn't actually compile anymore post- 639e702b6129f501c539b158b982ed8489e3d09c. Oopsie. {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module TypeName where import GHC.Generics class TypeName a where typeName :: forall proxy. proxy a -> String default typeName :: forall proxy d f. (Generic a, Rep a ~ D1 d f, Datatype d) => proxy a -> String typeName _ = gtypeName $ from (undefined :: a) gtypeName :: Datatype d => D1 d f p -> String gtypeName = datatypeName data T a = MkT a deriving (Generic, TypeName) }}} This compiles before that commit. After it, however, it fails with the error: {{{ [1 of 1] Compiling TypeName ( Bug.hs, interpreted ) Bug.hs:23:22: error: • Couldn't match type ‘f’ with ‘C1 ('MetaCons "MkT" 'PrefixI 'False) (S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))’ arising from the 'deriving' clause of a data type declaration ‘f’ is a rigid type variable bound by the deriving clause for ‘TypeName (T a)’ at Bug.hs:14:38 • When deriving the instance for (TypeName (T a)) | 23 | deriving (Generic, TypeName) | ^^^^^^^^ }}} I'm not sure why it's complaining only about `f` and not, say, `d`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler