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

GHC.Tc.Deriv.Utils

Description

Error-checking and other utilities for deriving clauses or declarations.

Synopsis

Documentation

type DerivM = ReaderT DerivEnv TcRn Source #

To avoid having to manually plumb everything in DerivEnv throughout various functions in GHC.Tc.Deriv and GHC.Tc.Deriv.Infer, we use DerivM, which is a simple reader around TcRn.

data DerivEnv Source #

Contains all of the information known about a derived instance when determining what its EarlyDerivSpec should be. See Note [DerivEnv and DerivSpecMechanism].

Constructors

DerivEnv 

Fields

Instances

Instances details
Outputable DerivEnv Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivEnv -> SDoc #

data DerivSpec theta Source #

Instances

Instances details
Outputable theta => Outputable (DerivSpec theta) Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivSpec theta -> SDoc #

setDerivSpecTheta :: theta' -> DerivSpec theta -> DerivSpec theta' Source #

Set the ds_theta in a DerivSpec.

zonkDerivSpec :: DerivSpec ThetaType -> TcM (DerivSpec ThetaType) Source #

Zonk the TcTyVars in a DerivSpec 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.

data DerivSpecMechanism Source #

What action to take in order to derive a class instance. See Note [DerivEnv and DerivSpecMechanism], as well as Note [Deriving strategies] in GHC.Tc.Deriv.

Constructors

DerivSpecStock

"Standard" classes

Fields

  • dsm_stock_dit :: DerivInstTys

    Information about the arguments to the class in the derived instance, including what type constructor the last argument is headed by. See Note [DerivEnv and DerivSpecMechanism].

  • dsm_stock_gen_fns :: StockGenFns

    How to generate the instance bindings and associated type family instances.

DerivSpecNewtype
GeneralizedNewtypeDeriving

Fields

  • dsm_newtype_dit :: DerivInstTys

    Information about the arguments to the class in the derived instance, including what type constructor the last argument is headed by. See Note [DerivEnv and DerivSpecMechanism].

  • dsm_newtype_rep_ty :: Type

    The newtype rep type.

DerivSpecAnyClass
DeriveAnyClass
DerivSpecVia
DerivingVia

Fields

Instances

Instances details
Outputable DerivSpecMechanism Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

zonkDerivSpecMechanism :: ZonkEnv -> DerivSpecMechanism -> TcM DerivSpecMechanism Source #

Zonk the TcTyVars in a DerivSpecMechanism 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.

data DerivContext Source #

Whether GHC is processing a deriving clause or a standalone deriving declaration.

Constructors

InferContext (Maybe SrcSpan)

'InferContext mb_wildcard is either:

  • A deriving clause (in which case mb_wildcard is Nothing).
  • A standalone deriving declaration with an extra-constraints wildcard as the context (in which case mb_wildcard is Just loc, where loc is the location of the wildcard.

GHC should infer the context.

SupplyContext ThetaType

SupplyContext theta is a standalone deriving declaration, where theta is the context supplied by the user.

Instances

Instances details
Outputable DerivContext Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivContext -> SDoc #

data OriginativeDerivStatus Source #

Records whether a particular class can be derived by way of an originative deriving strategy (i.e., stock or anyclass).

See Note [Deriving strategies] in GHC.Tc.Deriv.

data StockGenFns Source #

Describes how to generate instance bindings (stock_gen_binds) and associated type family instances (stock_gen_fam_insts) for a particular stock-derived instance.

Constructors

StockGenFns 

Fields

  • stock_gen_binds :: SrcSpan -> DerivInstTys -> TcM (LHsBinds GhcPs, [LSig GhcPs], Bag AuxBindSpec, [Name])

    Describes how to generate instance bindings for a stock-derived instance.

    This function takes two arguments:

    1. SrcSpan: the source location where the instance is being derived. This will eventually be instantiated with the ds_loc field of a DerivSpec.
    2. DerivInstTys: information about the argument types to which a class is applied in a derived instance. This will eventually be instantiated with the dsm_stock_dit field of a DerivSpecMechanism.

    This function returns four things:

    1. LHsBinds GhcPs: The derived instance's function bindings (e.g., compare (T x) (T y) = compare x y)
    2. [LSig GhcPs]: A list of instance specific signatures/pragmas. Most likely INLINE pragmas for class methods.
    3. Bag AuxBindSpec: Auxiliary bindings needed to support the derived instance. As examples, derived Eq and Ord instances sometimes require top-level con2tag functions. See Note [Auxiliary binders] in GHC.Tc.Deriv.Generate.
    4. [Name]: A list of Names for which -Wunused-binds should be suppressed. This is used to suppress unused warnings for record selectors when deriving Read, Show, or Generic. See Note [Deriving and unused record selectors].
  • stock_gen_fam_insts :: SrcSpan -> DerivInstTys -> TcM [FamInst]

    Describes how to generate associated type family instances for a stock-derived instance. This function takes the same arguments as the stock_gen_binds function but returns a list of FamInsts instead. Generating type family instances is done separately from stock_gen_binds since the type family instances must be generated before the instance bindings can be typechecked. See Note [Staging of tcDeriving] in GHC.Tc.Deriv.

isStandaloneDeriv :: DerivM Bool Source #

Is GHC processing a standalone deriving declaration?

isStandaloneWildcardDeriv :: DerivM Bool Source #

Is GHC processing a standalone deriving declaration with an extra-constraints wildcard as the context? (e.g., deriving instance _ => Eq (Foo a))

askDerivUserTypeCtxt :: DerivM UserTypeCtxt Source #

Return InstDeclCtxt if processing with a standalone deriving declaration or DerivClauseCtxt if processing a deriving clause.

mkDerivOrigin :: Bool -> CtOrigin Source #

mkDerivOrigin wc returns StandAloneDerivOrigin if wc is True, and DerivClauseOrigin if wc is False. Useful for error-reporting.

data PredSpec Source #

A PredSpec specifies a constraint to emitted when inferring the instance context for a derived instance in simplifyInfer.

Constructors

SimplePredSpec

An ordinary PredSpec that directly stores a PredType, which will be emitted as a wanted constraint in the constraint solving machinery. This is the simple case, as there are no skolems, metavariables, or given constraints involved.

Fields

SubTypePredSpec

A special PredSpec that is only used by DeriveAnyClass. This will check if stps_ty_actual is a subtype of (i.e., more polymorphic than) stps_ty_expected in the constraint solving machinery, emitting an implication constraint as a side effect. For more details on how this works, see Note [Gathering and simplifying constraints for DeriveAnyClass] in GHC.Tc.Deriv.Infer.

Fields

Instances

Instances details
Outputable PredSpec Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: PredSpec -> SDoc #

type ThetaSpec = [PredSpec] Source #

A list of PredSpec constraints to simplify when inferring a derived instance's context. For the stock, newtype, and via deriving strategies, these will consist of SimplePredSpecs, and for DeriveAnyClass, these will consist of SubTypePredSpecs. Here is an example to illustrate the latter:

class Foo a where
  bar :: forall b. Ix b => a -> b -> String
  default bar :: forall y. (Show a, Ix y) => a -> y -> String
  bar x y = show x ++ show (range (y, y))

  baz :: Eq a => a -> a -> Bool
  default baz :: Ord a => a -> a -> Bool
  baz x y = compare x y == EQ

data Quux q = Quux deriving anyclass Foo

Then it would generate two SubTypePredSpecs, one for each method:

[ SubTypePredSpec
    { stps_ty_actual   = forall y. (Show (Quux q), Ix y) => Quux q -> y -> String
    , stps_ty_expected = forall b.                (Ix b) => Quux q -> b -> String
    , stps_ty_origin   = DerivClauseCtxt
    }
, SubTypePredSpec
    { stps_ty_actual   = Ord (Quux q) => Quux q -> Quux q -> Bool
    , stps_ty_expected = Eq  (Quux q) => Quux q -> Quux q -> Bool
    , stps_ty_origin   = DerivClauseCtxt
    }
]

(Note that the type variable q is bound by the data type Quux, and thus appears free in the stps_ty_actuals and stps_ty_expecteds.)

See Note [Gathering and simplifying constraints for DeriveAnyClass] in GHC.Tc.Deriv.Infer for an explanation of how these SubTypePredSpecs are used to compute implication constraints.

mkDirectThetaSpec :: CtOrigin -> TypeOrKind -> ThetaType -> ThetaSpec Source #

Build a list of SimplePredSpecs, using the supplied CtOrigin and TypeOrKind values for each PredType.

captureThetaSpecConstraints Source #

Arguments

:: UserTypeCtxt

Used to inform error messages as to whether we are in a deriving clause or a standalone deriving declaration

-> ThetaSpec

The specs from which constraints will be created

-> TcM (TcLevel, WantedConstraints) 

Capture wanted constraints from a ThetaSpec.