ghc-lib-9.4.4.20221225: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Tc.Deriv.Generate

Description

Generating derived instance declarations

This module is nominally `subordinate' to GHC.Tc.Deriv, which is the `official' interface to deriving-related things.

This is where we do all the grimy bindings' generation.

Synopsis

Documentation

data AuxBindSpec Source #

A declarative description of an auxiliary binding that should be generated. See Note [Auxiliary binders] for a more detailed description of how these are used.

Constructors

DerivTag2Con TyCon RdrName

$tag2con: Given a tag, computes the corresponding data constructor

DerivMaxTag TyCon RdrName

$maxtag: The maximum possible tag value among a data type's constructors

DerivDataDataType TyCon RdrName [RdrName]

$t: The DataType representation for a Data instance

DerivDataConstr DataCon RdrName RdrName

$c: The Constr representation for a Data instance

genAuxBinds :: DynFlags -> SrcSpan -> Bag AuxBindSpec -> Bag (LHsBind GhcPs, LSig GhcPs) Source #

Take a Bag of AuxBindSpecs and generate the code for auxiliary bindings based on the declarative descriptions in the supplied AuxBindSpecs. See Note [Auxiliary binders].

mkRdrFunBindEC :: Arity -> (LHsExpr GhcPs -> LHsExpr GhcPs) -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsBind GhcPs Source #

Produces a function binding. When no equations are given, it generates a binding of the given arity and an empty case expression for the last argument that it passes to the given function to produce the right-hand side.

mkRdrFunBindSE :: Arity -> LocatedN RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsBind GhcPs Source #

Produces a function binding. When there are no equations, it generates a binding with the given arity that produces an error based on the name of the type of the last argument.

getPossibleDataCons :: TyCon -> [Type] -> [DataCon] Source #

getPossibleDataCons tycon tycon_args returns the constructors of tycon whose return types match when checked against tycon_args.

See Note [Filter out impossible GADT data constructors]

data DerivInstTys Source #

Information about the arguments to the class in a stock- or newtype-derived instance. For a deriving-generated instance declaration such as this one:

instance Ctx => Cls cls_ty_1 ... cls_ty_m (TC tc_arg_1 ... tc_arg_n) where ...

See Note [DerivEnv and DerivSpecMechanism] in GHC.Tc.Deriv.Utils for a more in-depth explanation, including the relationship between dit_tcdit_rep_tc and dit_tc_argsdit_rep_tc_args.

A DerivInstTys value can be seen as a more structured representation of the denv_inst_tys in a DerivEnv, as the denv_inst_tys is equal to dit_cls_tys ++ [mkTyConApp dit_tc dit_tc_args]. Other parts of the instance declaration can be found in the DerivEnv. For example, the Cls in the example above corresponds to the denv_cls field of DerivEnv.

Similarly, the type variables that appear in a DerivInstTys value are the same type variables as the denv_tvs in the parent DerivEnv. Accordingly, if we are inferring an instance context, the type variables will be TcTyVar skolems. Otherwise, they will be ordinary TyVars. See Note [Overlap and deriving] in GHC.Tc.Deriv.Infer.

Constructors

DerivInstTys 

Fields

Instances

Instances details
Outputable DerivInstTys Source # 
Instance details

Defined in GHC.Tc.Deriv.Generate

Methods

ppr :: DerivInstTys -> SDoc #

buildDataConInstArgEnv :: TyCon -> [Type] -> DataConEnv [Type] Source #

buildDataConInstArgEnv tycon arg_tys constructs a cache that maps each of tycon's data constructors to their field types, with are to be instantiated with arg_tys. See Note [Instantiating field types in stock deriving].

derivDataConInstArgTys :: DataCon -> DerivInstTys -> [Type] Source #

Look up a data constructor's instantiated field types in a DerivInstTys. See Note [Instantiating field types in stock deriving].

substDerivInstTys :: TCvSubst -> DerivInstTys -> DerivInstTys Source #

Apply a substitution to all of the Types contained in a DerivInstTys. See Note [Instantiating field types in stock deriving] for why we need to substitute into a DerivInstTys in the first place.

zonkDerivInstTys :: ZonkEnv -> DerivInstTys -> TcM DerivInstTys Source #

Zonk the TcTyVars in a DerivInstTys value to TyVars. See Note [What is zonking?] in GHC.Tc.Utils.TcMType.

This is only used in the final zonking step when inferring the context for a derived instance. See Note [Overlap and deriving] in GHC.Tc.Deriv.Infer.