Safe Haskell | None |
---|---|
Language | Haskell2010 |
Error-checking and other utilities for deriving
clauses or declarations.
Synopsis
- type DerivM = ReaderT DerivEnv TcRn
- data DerivEnv = DerivEnv {
- denv_overlap_mode :: Maybe OverlapMode
- denv_tvs :: [TyVar]
- denv_cls :: Class
- denv_inst_tys :: [Type]
- denv_ctxt :: DerivContext
- denv_strat :: Maybe (DerivStrategy GhcTc)
- data DerivSpec theta = DS {
- ds_loc :: SrcSpan
- ds_name :: Name
- ds_tvs :: [TyVar]
- ds_theta :: theta
- ds_cls :: Class
- ds_tys :: [Type]
- ds_overlap :: Maybe OverlapMode
- ds_standalone_wildcard :: Maybe SrcSpan
- ds_mechanism :: DerivSpecMechanism
- pprDerivSpec :: Outputable theta => DerivSpec theta -> SDoc
- data DerivInstTys = DerivInstTys {
- dit_cls_tys :: [Type]
- dit_tc :: TyCon
- dit_tc_args :: [Type]
- dit_rep_tc :: TyCon
- dit_rep_tc_args :: [Type]
- data DerivSpecMechanism
- = DerivSpecStock {
- dsm_stock_dit :: DerivInstTys
- dsm_stock_gen_fn :: SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
- | DerivSpecNewtype { }
- | DerivSpecAnyClass
- | DerivSpecVia {
- dsm_via_cls_tys :: [Type]
- dsm_via_inst_ty :: Type
- dsm_via_ty :: Type
- = DerivSpecStock {
- derivSpecMechanismToStrategy :: DerivSpecMechanism -> DerivStrategy GhcTc
- isDerivSpecStock :: DerivSpecMechanism -> Bool
- isDerivSpecNewtype :: DerivSpecMechanism -> Bool
- isDerivSpecAnyClass :: DerivSpecMechanism -> Bool
- isDerivSpecVia :: DerivSpecMechanism -> Bool
- data DerivContext
- data OriginativeDerivStatus
- = CanDeriveStock (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
- | StockClassError SDoc
- | CanDeriveAnyClass
- | NonDerivableClass SDoc
- isStandaloneDeriv :: DerivM Bool
- isStandaloneWildcardDeriv :: DerivM Bool
- mkDerivOrigin :: Bool -> CtOrigin
- data PredOrigin = PredOrigin PredType CtOrigin TypeOrKind
- data ThetaOrigin = ThetaOrigin {}
- mkPredOrigin :: CtOrigin -> TypeOrKind -> PredType -> PredOrigin
- mkThetaOrigin :: CtOrigin -> TypeOrKind -> [TyVar] -> [TyVar] -> ThetaType -> ThetaType -> ThetaOrigin
- mkThetaOriginFromPreds :: [PredOrigin] -> ThetaOrigin
- substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin
- checkOriginativeSideConditions :: DynFlags -> DerivContext -> Class -> [TcType] -> TyCon -> TyCon -> OriginativeDerivStatus
- hasStockDeriving :: Class -> Maybe (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
- canDeriveAnyClass :: DynFlags -> Validity
- std_class_via_coercible :: Class -> Bool
- non_coercible_class :: Class -> Bool
- newDerivClsInst :: ThetaType -> DerivSpec theta -> TcM ClsInst
- extendLocalInstEnv :: [ClsInst] -> TcM a -> TcM a
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
.
Contains all of the information known about a derived instance when
determining what its EarlyDerivSpec
should be.
See Note [DerivEnv and DerivSpecMechanism]
.
DerivEnv | |
|
DS | |
|
pprDerivSpec :: Outputable theta => DerivSpec theta -> SDoc Source #
data DerivInstTys Source #
Information about the arguments to the class in a stock- or
newtype-derived instance.
See Note [DerivEnv and DerivSpecMechanism]
.
DerivInstTys | |
|
Instances
Outputable DerivInstTys # | |
Defined in GHC.Tc.Deriv.Utils |
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.
DerivSpecStock | "Standard" classes |
| |
DerivSpecNewtype | GeneralizedNewtypeDeriving |
| |
DerivSpecAnyClass | DeriveAnyClass |
DerivSpecVia | DerivingVia |
|
Instances
Outputable DerivSpecMechanism # | |
Defined in GHC.Tc.Deriv.Utils |
derivSpecMechanismToStrategy :: DerivSpecMechanism -> DerivStrategy GhcTc Source #
Convert a DerivSpecMechanism
to its corresponding DerivStrategy
.
data DerivContext Source #
Whether GHC is processing a deriving
clause or a standalone deriving
declaration.
InferContext (Maybe SrcSpan) |
GHC should infer the context. |
SupplyContext ThetaType |
|
Instances
Outputable DerivContext # | |
Defined in GHC.Tc.Deriv.Utils |
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.
CanDeriveStock (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])) | |
StockClassError SDoc | |
CanDeriveAnyClass | |
NonDerivableClass SDoc |
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)
)
mkDerivOrigin :: Bool -> CtOrigin Source #
returns mkDerivOrigin
wcStandAloneDerivOrigin
if wc
is True
,
and DerivClauseOrigin
if wc
is False
. Useful for error-reporting.
data PredOrigin Source #
A PredType
annotated with the origin of the constraint CtOrigin
,
and whether or the constraint deals in types or kinds.
Instances
Outputable PredOrigin # | |
Defined in GHC.Tc.Deriv.Utils |
data ThetaOrigin Source #
A list of wanted PredOrigin
constraints (to_wanted_origins
) to
simplify when inferring a derived instance's context. These are used in all
deriving strategies, but in the particular case of DeriveAnyClass
, we
need extra information. In particular, we need:
to_anyclass_skols
, the list of type variables bound by a class method's regular type signature, which should be rigid.to_anyclass_metas
, the list of type variables bound by a class method's default type signature. These can be unified as necessary.to_anyclass_givens
, the list of constraints from a class method's regular type signature, which can be used to help solve constraints in theto_wanted_origins
.
(Note that to_wanted_origins
will likely contain type variables from the
derived type class or data type, neither of which will appear in
to_anyclass_skols
or to_anyclass_metas
.)
For all other deriving strategies, it is always the case that
to_anyclass_skols
, to_anyclass_metas
, and to_anyclass_givens
are
empty.
Here is an example to illustrate this:
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 ThetaOrigin
s, one for each method:
[ ThetaOrigin { to_anyclass_skols = [b] , to_anyclass_metas = [y] , to_anyclass_givens = [Ix b] , to_wanted_origins = [ Show (Quux q), Ix y , (Quux q -> b -> String) ~ (Quux q -> y -> String) ] } , ThetaOrigin { to_anyclass_skols = [] , to_anyclass_metas = [] , to_anyclass_givens = [Eq (Quux q)] , to_wanted_origins = [ Ord (Quux q) , (Quux q -> Quux q -> Bool) ~ (Quux q -> Quux q -> Bool) ] } ]
(Note that the type variable q
is bound by the data type Quux
, and thus
it appears in neither to_anyclass_skols
nor to_anyclass_metas
.)
See Note [Gathering and simplifying constraints for DeriveAnyClass]
in GHC.Tc.Deriv.Infer for an explanation of how to_wanted_origins
are
determined in DeriveAnyClass
, as well as how to_anyclass_skols
,
to_anyclass_metas
, and to_anyclass_givens
are used.
ThetaOrigin | |
|
Instances
Outputable ThetaOrigin # | |
Defined in GHC.Tc.Deriv.Utils |
mkPredOrigin :: CtOrigin -> TypeOrKind -> PredType -> PredOrigin Source #
mkThetaOrigin :: CtOrigin -> TypeOrKind -> [TyVar] -> [TyVar] -> ThetaType -> ThetaType -> ThetaOrigin Source #
substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin Source #
checkOriginativeSideConditions :: DynFlags -> DerivContext -> Class -> [TcType] -> TyCon -> TyCon -> OriginativeDerivStatus Source #
hasStockDeriving :: Class -> Maybe (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])) Source #
canDeriveAnyClass :: DynFlags -> Validity Source #
std_class_via_coercible :: Class -> Bool Source #
non_coercible_class :: Class -> Bool Source #