Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The deriving code for the Generic class
Synopsis
- canDoGenerics :: DerivInstTys -> Validity' [DeriveGenericsErrReason]
- canDoGenerics1 :: DerivInstTys -> Validity' [DeriveGenericsErrReason]
- data GenericKind
- gen_Generic_binds :: GenericKind -> SrcSpan -> DerivInstTys -> TcM (LHsBinds GhcPs, [LSig GhcPs])
- gen_Generic_fam_inst :: GenericKind -> (Name -> Fixity) -> SrcSpan -> DerivInstTys -> TcM FamInst
- get_gen1_constrained_tys :: TyVar -> Type -> [Type]
Documentation
data GenericKind Source #
gen_Generic_binds :: GenericKind -> SrcSpan -> DerivInstTys -> TcM (LHsBinds GhcPs, [LSig GhcPs]) Source #
gen_Generic_fam_inst :: GenericKind -> (Name -> Fixity) -> SrcSpan -> DerivInstTys -> TcM FamInst Source #
get_gen1_constrained_tys :: TyVar -> Type -> [Type] Source #
Called by inferConstraints
; generates a list of
types, each of which must be a Functor
in order for the Generic1
instance to work. For instance, if we have:
data Foo a = MkFoo Int a (Maybe a) (Either Int (Maybe a))
Then
would return get_gen1_constrained_tys
a (f (g a))[Either Int]
,
as a derived Generic1
instance would need to call fmap
at that type.
Invoking
on any of the other fields would
return get_gen1_constrained_tys
a[]
.
get_gen1_constrained_tys
is very similar in spirit to
deepSubtypesContaining
in GHC.Tc.Deriv.Functor. Just like with
deepSubtypesContaining
, it is important that the TyVar
argument come
from dataConUnivTyVars
. (See #22167 for what goes wrong if tyConTyVars
is used.)