ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
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 DerivStuff Source #

Constructors

DerivAuxBind AuxBindSpec

A new, top-level auxiliary binding. Used for deriving Eq, Ord, Enum, Ix, and Data. See Note [Auxiliary binders].

DerivFamInst FamInst

A new type family instance. Used for:

  • DeriveGeneric, which generates instances of Rep(1)
  • DeriveAnyClass, which can fill in associated type family defaults
  • GeneralizedNewtypeDeriving, which generates instances of associated type families for newtypes

gen_Eq_binds :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Ord_binds :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Enum_binds :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Bounded_binds :: SrcSpan -> TyCon -> [Type] -> (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Ix_binds :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Show_binds :: (Name -> Fixity) -> SrcSpan -> TyCon -> [Type] -> (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Read_binds :: (Name -> Fixity) -> SrcSpan -> TyCon -> [Type] -> (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Data_binds :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Lift_binds :: SrcSpan -> TyCon -> [Type] -> (LHsBinds GhcPs, BagDerivStuff) Source #

gen_Newtype_binds :: SrcSpan -> Class -> [TyVar] -> [Type] -> Type -> TcM (LHsBinds GhcPs, [LSig GhcPs], BagDerivStuff) Source #

mkCoerceClassMethEqn :: Class -> [TyVar] -> [Type] -> Type -> Id -> Pair Type Source #

genAuxBinds :: DynFlags -> SrcSpan -> BagDerivStuff -> SeparateBagsDerivStuff Source #

Take a BagDerivStuff and partition it into SeparateBagsDerivStuff. Also generate the code for auxiliary bindings based on the declarative descriptions in the supplied AuxBindSpecs. See Note [Auxiliary binders].

boxConTbl :: [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)] Source #

litConTbl :: [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)] Source #

mkRdrFunBind :: Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsBind GhcPs Source #

mkRdrFunBindEC :: Arity -> (LHsExpr GhcPs -> LHsExpr GhcPs) -> Located 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 -> Located 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.

error_Expr :: String -> LHsExpr GhcPs Source #

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]

tyConInstArgTys :: TyCon -> [Type] -> [Type] Source #

Given a type constructor tycon of arity n and a list of argument types tycon_args of length m,

tyConInstArgTys tycon tycon_args

returns

[tycon_arg_{1}, tycon_arg_{2}, ..., tycon_arg_{m}, extra_arg_{m+1}, ..., extra_arg_{n}]

where extra_args are distinct type variables.

Examples:

  • Given tycon: Foo a b and tycon_args: [Int, Bool], return [Int, Bool].
  • Given tycon: Foo a b and tycon_args: [Int], return [Int, b].