{-# LANGUAGE TypeFamilies #-}
module GHC.Tc.Deriv.Utils (
DerivM, DerivEnv(..),
DerivSpec(..), pprDerivSpec, DerivInstTys(..),
DerivSpecMechanism(..), derivSpecMechanismToStrategy, isDerivSpecStock,
isDerivSpecNewtype, isDerivSpecAnyClass, isDerivSpecVia,
DerivContext(..), OriginativeDerivStatus(..),
isStandaloneDeriv, isStandaloneWildcardDeriv, mkDerivOrigin,
PredOrigin(..), ThetaOrigin(..), mkPredOrigin,
mkThetaOrigin, mkThetaOriginFromPreds, substPredOrigin,
checkOriginativeSideConditions, hasStockDeriving,
canDeriveAnyClass,
std_class_via_coercible, non_coercible_class,
newDerivClsInst, extendLocalInstEnv
) where
import GHC.Prelude
import GHC.Data.Bag
import GHC.Types.Basic
import GHC.Core.Class
import GHC.Core.DataCon
import GHC.Driver.Session
import GHC.Utils.Error
import GHC.Driver.Types (lookupFixity, mi_fix)
import GHC.Hs
import GHC.Tc.Utils.Instantiate
import GHC.Core.InstEnv
import GHC.Iface.Load (loadInterfaceForName)
import GHC.Unit.Module (getModule)
import GHC.Types.Name
import GHC.Utils.Outputable
import GHC.Builtin.Names
import GHC.Types.SrcLoc
import GHC.Tc.Deriv.Generate
import GHC.Tc.Deriv.Functor
import GHC.Tc.Deriv.Generics
import GHC.Tc.Types.Origin
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.TcType
import GHC.Builtin.Names.TH (liftClassKey)
import GHC.Core.TyCon
import GHC.Core.Multiplicity
import GHC.Core.TyCo.Ppr (pprSourceTyCon)
import GHC.Core.Type
import GHC.Utils.Misc
import GHC.Types.Var.Set
import Control.Monad.Trans.Reader
import Data.Maybe
import qualified GHC.LanguageExtensions as LangExt
import GHC.Data.List.SetOps (assocMaybe)
type DerivM = ReaderT DerivEnv TcRn
isStandaloneDeriv :: DerivM Bool
isStandaloneDeriv :: DerivM Bool
isStandaloneDeriv = (DerivEnv -> Bool) -> DerivM Bool
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks (DerivContext -> Bool
go (DerivContext -> Bool)
-> (DerivEnv -> DerivContext) -> DerivEnv -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DerivEnv -> DerivContext
denv_ctxt)
where
go :: DerivContext -> Bool
go :: DerivContext -> Bool
go (InferContext Maybe SrcSpan
wildcard) = Maybe SrcSpan -> Bool
forall a. Maybe a -> Bool
isJust Maybe SrcSpan
wildcard
go (SupplyContext {}) = Bool
True
isStandaloneWildcardDeriv :: DerivM Bool
isStandaloneWildcardDeriv :: DerivM Bool
isStandaloneWildcardDeriv = (DerivEnv -> Bool) -> DerivM Bool
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks (DerivContext -> Bool
go (DerivContext -> Bool)
-> (DerivEnv -> DerivContext) -> DerivEnv -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DerivEnv -> DerivContext
denv_ctxt)
where
go :: DerivContext -> Bool
go :: DerivContext -> Bool
go (InferContext Maybe SrcSpan
wildcard) = Maybe SrcSpan -> Bool
forall a. Maybe a -> Bool
isJust Maybe SrcSpan
wildcard
go (SupplyContext {}) = Bool
False
mkDerivOrigin :: Bool -> CtOrigin
mkDerivOrigin :: Bool -> CtOrigin
mkDerivOrigin Bool
standalone_wildcard
| Bool
standalone_wildcard = CtOrigin
StandAloneDerivOrigin
| Bool
otherwise = CtOrigin
DerivClauseOrigin
data DerivEnv = DerivEnv
{ DerivEnv -> Maybe OverlapMode
denv_overlap_mode :: Maybe OverlapMode
, DerivEnv -> [TyVar]
denv_tvs :: [TyVar]
, DerivEnv -> Class
denv_cls :: Class
, DerivEnv -> [Type]
denv_inst_tys :: [Type]
, DerivEnv -> DerivContext
denv_ctxt :: DerivContext
, DerivEnv -> Maybe (DerivStrategy GhcTc)
denv_strat :: Maybe (DerivStrategy GhcTc)
}
instance Outputable DerivEnv where
ppr :: DerivEnv -> SDoc
ppr (DerivEnv { denv_overlap_mode :: DerivEnv -> Maybe OverlapMode
denv_overlap_mode = Maybe OverlapMode
overlap_mode
, denv_tvs :: DerivEnv -> [TyVar]
denv_tvs = [TyVar]
tvs
, denv_cls :: DerivEnv -> Class
denv_cls = Class
cls
, denv_inst_tys :: DerivEnv -> [Type]
denv_inst_tys = [Type]
inst_tys
, denv_ctxt :: DerivEnv -> DerivContext
denv_ctxt = DerivContext
ctxt
, denv_strat :: DerivEnv -> Maybe (DerivStrategy GhcTc)
denv_strat = Maybe (DerivStrategy GhcTc)
mb_strat })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DerivEnv")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"denv_overlap_mode" SDoc -> SDoc -> SDoc
<+> Maybe OverlapMode -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe OverlapMode
overlap_mode
, String -> SDoc
text String
"denv_tvs" SDoc -> SDoc -> SDoc
<+> [TyVar] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TyVar]
tvs
, String -> SDoc
text String
"denv_cls" SDoc -> SDoc -> SDoc
<+> Class -> SDoc
forall a. Outputable a => a -> SDoc
ppr Class
cls
, String -> SDoc
text String
"denv_inst_tys" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
inst_tys
, String -> SDoc
text String
"denv_ctxt" SDoc -> SDoc -> SDoc
<+> DerivContext -> SDoc
forall a. Outputable a => a -> SDoc
ppr DerivContext
ctxt
, String -> SDoc
text String
"denv_strat" SDoc -> SDoc -> SDoc
<+> Maybe (DerivStrategy GhcTc) -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe (DerivStrategy GhcTc)
mb_strat ])
data DerivSpec theta = DS { forall theta. DerivSpec theta -> SrcSpan
ds_loc :: SrcSpan
, forall theta. DerivSpec theta -> Name
ds_name :: Name
, forall theta. DerivSpec theta -> [TyVar]
ds_tvs :: [TyVar]
, forall theta. DerivSpec theta -> theta
ds_theta :: theta
, forall theta. DerivSpec theta -> Class
ds_cls :: Class
, forall theta. DerivSpec theta -> [Type]
ds_tys :: [Type]
, forall theta. DerivSpec theta -> Maybe OverlapMode
ds_overlap :: Maybe OverlapMode
, forall theta. DerivSpec theta -> Maybe SrcSpan
ds_standalone_wildcard :: Maybe SrcSpan
, forall theta. DerivSpec theta -> DerivSpecMechanism
ds_mechanism :: DerivSpecMechanism }
pprDerivSpec :: Outputable theta => DerivSpec theta -> SDoc
pprDerivSpec :: forall theta. Outputable theta => DerivSpec theta -> SDoc
pprDerivSpec (DS { ds_loc :: forall theta. DerivSpec theta -> SrcSpan
ds_loc = SrcSpan
l, ds_name :: forall theta. DerivSpec theta -> Name
ds_name = Name
n, ds_tvs :: forall theta. DerivSpec theta -> [TyVar]
ds_tvs = [TyVar]
tvs, ds_cls :: forall theta. DerivSpec theta -> Class
ds_cls = Class
c,
ds_tys :: forall theta. DerivSpec theta -> [Type]
ds_tys = [Type]
tys, ds_theta :: forall theta. DerivSpec theta -> theta
ds_theta = theta
rhs,
ds_standalone_wildcard :: forall theta. DerivSpec theta -> Maybe SrcSpan
ds_standalone_wildcard = Maybe SrcSpan
wildcard, ds_mechanism :: forall theta. DerivSpec theta -> DerivSpecMechanism
ds_mechanism = DerivSpecMechanism
mech })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DerivSpec")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"ds_loc =" SDoc -> SDoc -> SDoc
<+> SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr SrcSpan
l
, String -> SDoc
text String
"ds_name =" SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
n
, String -> SDoc
text String
"ds_tvs =" SDoc -> SDoc -> SDoc
<+> [TyVar] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TyVar]
tvs
, String -> SDoc
text String
"ds_cls =" SDoc -> SDoc -> SDoc
<+> Class -> SDoc
forall a. Outputable a => a -> SDoc
ppr Class
c
, String -> SDoc
text String
"ds_tys =" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
tys
, String -> SDoc
text String
"ds_theta =" SDoc -> SDoc -> SDoc
<+> theta -> SDoc
forall a. Outputable a => a -> SDoc
ppr theta
rhs
, String -> SDoc
text String
"ds_standalone_wildcard =" SDoc -> SDoc -> SDoc
<+> Maybe SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe SrcSpan
wildcard
, String -> SDoc
text String
"ds_mechanism =" SDoc -> SDoc -> SDoc
<+> DerivSpecMechanism -> SDoc
forall a. Outputable a => a -> SDoc
ppr DerivSpecMechanism
mech ])
instance Outputable theta => Outputable (DerivSpec theta) where
ppr :: DerivSpec theta -> SDoc
ppr = DerivSpec theta -> SDoc
forall theta. Outputable theta => DerivSpec theta -> SDoc
pprDerivSpec
data DerivInstTys = DerivInstTys
{ DerivInstTys -> [Type]
dit_cls_tys :: [Type]
, DerivInstTys -> TyCon
dit_tc :: TyCon
, DerivInstTys -> [Type]
dit_tc_args :: [Type]
, DerivInstTys -> TyCon
dit_rep_tc :: TyCon
, DerivInstTys -> [Type]
dit_rep_tc_args :: [Type]
}
instance Outputable DerivInstTys where
ppr :: DerivInstTys -> SDoc
ppr (DerivInstTys { dit_cls_tys :: DerivInstTys -> [Type]
dit_cls_tys = [Type]
cls_tys, dit_tc :: DerivInstTys -> TyCon
dit_tc = TyCon
tc, dit_tc_args :: DerivInstTys -> [Type]
dit_tc_args = [Type]
tc_args
, dit_rep_tc :: DerivInstTys -> TyCon
dit_rep_tc = TyCon
rep_tc, dit_rep_tc_args :: DerivInstTys -> [Type]
dit_rep_tc_args = [Type]
rep_tc_args })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DITTyConHead")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"dit_cls_tys" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
cls_tys
, String -> SDoc
text String
"dit_tc" SDoc -> SDoc -> SDoc
<+> TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
tc
, String -> SDoc
text String
"dit_tc_args" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
tc_args
, String -> SDoc
text String
"dit_rep_tc" SDoc -> SDoc -> SDoc
<+> TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
rep_tc
, String -> SDoc
text String
"dit_rep_tc_args" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
rep_tc_args ])
data DerivSpecMechanism
= DerivSpecStock
{ DerivSpecMechanism -> DerivInstTys
dsm_stock_dit :: DerivInstTys
, DerivSpecMechanism
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
dsm_stock_gen_fn ::
SrcSpan -> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
}
| DerivSpecNewtype
{ DerivSpecMechanism -> DerivInstTys
dsm_newtype_dit :: DerivInstTys
, DerivSpecMechanism -> Type
dsm_newtype_rep_ty :: Type
}
| DerivSpecAnyClass
| DerivSpecVia
{ DerivSpecMechanism -> [Type]
dsm_via_cls_tys :: [Type]
, DerivSpecMechanism -> Type
dsm_via_inst_ty :: Type
, DerivSpecMechanism -> Type
dsm_via_ty :: Type
}
derivSpecMechanismToStrategy :: DerivSpecMechanism -> DerivStrategy GhcTc
derivSpecMechanismToStrategy :: DerivSpecMechanism -> DerivStrategy GhcTc
derivSpecMechanismToStrategy DerivSpecStock{} = DerivStrategy GhcTc
forall pass. DerivStrategy pass
StockStrategy
derivSpecMechanismToStrategy DerivSpecNewtype{} = DerivStrategy GhcTc
forall pass. DerivStrategy pass
NewtypeStrategy
derivSpecMechanismToStrategy DerivSpecMechanism
DerivSpecAnyClass = DerivStrategy GhcTc
forall pass. DerivStrategy pass
AnyclassStrategy
derivSpecMechanismToStrategy (DerivSpecVia{dsm_via_ty :: DerivSpecMechanism -> Type
dsm_via_ty = Type
t}) = XViaStrategy GhcTc -> DerivStrategy GhcTc
forall pass. XViaStrategy pass -> DerivStrategy pass
ViaStrategy Type
XViaStrategy GhcTc
t
isDerivSpecStock, isDerivSpecNewtype, isDerivSpecAnyClass, isDerivSpecVia
:: DerivSpecMechanism -> Bool
isDerivSpecStock :: DerivSpecMechanism -> Bool
isDerivSpecStock (DerivSpecStock{}) = Bool
True
isDerivSpecStock DerivSpecMechanism
_ = Bool
False
isDerivSpecNewtype :: DerivSpecMechanism -> Bool
isDerivSpecNewtype (DerivSpecNewtype{}) = Bool
True
isDerivSpecNewtype DerivSpecMechanism
_ = Bool
False
isDerivSpecAnyClass :: DerivSpecMechanism -> Bool
isDerivSpecAnyClass DerivSpecMechanism
DerivSpecAnyClass = Bool
True
isDerivSpecAnyClass DerivSpecMechanism
_ = Bool
False
isDerivSpecVia :: DerivSpecMechanism -> Bool
isDerivSpecVia (DerivSpecVia{}) = Bool
True
isDerivSpecVia DerivSpecMechanism
_ = Bool
False
instance Outputable DerivSpecMechanism where
ppr :: DerivSpecMechanism -> SDoc
ppr (DerivSpecStock{dsm_stock_dit :: DerivSpecMechanism -> DerivInstTys
dsm_stock_dit = DerivInstTys
dit})
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DerivSpecStock")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"dsm_stock_dit" SDoc -> SDoc -> SDoc
<+> DerivInstTys -> SDoc
forall a. Outputable a => a -> SDoc
ppr DerivInstTys
dit ])
ppr (DerivSpecNewtype { dsm_newtype_dit :: DerivSpecMechanism -> DerivInstTys
dsm_newtype_dit = DerivInstTys
dit, dsm_newtype_rep_ty :: DerivSpecMechanism -> Type
dsm_newtype_rep_ty = Type
rep_ty })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DerivSpecNewtype")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"dsm_newtype_dit" SDoc -> SDoc -> SDoc
<+> DerivInstTys -> SDoc
forall a. Outputable a => a -> SDoc
ppr DerivInstTys
dit
, String -> SDoc
text String
"dsm_newtype_rep_ty" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
rep_ty ])
ppr DerivSpecMechanism
DerivSpecAnyClass = String -> SDoc
text String
"DerivSpecAnyClass"
ppr (DerivSpecVia { dsm_via_cls_tys :: DerivSpecMechanism -> [Type]
dsm_via_cls_tys = [Type]
cls_tys, dsm_via_inst_ty :: DerivSpecMechanism -> Type
dsm_via_inst_ty = Type
inst_ty
, dsm_via_ty :: DerivSpecMechanism -> Type
dsm_via_ty = Type
via_ty })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"DerivSpecVia")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"dsm_via_cls_tys" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
cls_tys
, String -> SDoc
text String
"dsm_via_inst_ty" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
inst_ty
, String -> SDoc
text String
"dsm_via_ty" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
via_ty ])
data DerivContext
= InferContext (Maybe SrcSpan)
| SupplyContext ThetaType
instance Outputable DerivContext where
ppr :: DerivContext -> SDoc
ppr (InferContext Maybe SrcSpan
standalone) = String -> SDoc
text String
"InferContext" SDoc -> SDoc -> SDoc
<+> Maybe SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe SrcSpan
standalone
ppr (SupplyContext [Type]
theta) = String -> SDoc
text String
"SupplyContext" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
theta
data OriginativeDerivStatus
= CanDeriveStock
(SrcSpan -> TyCon -> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
| StockClassError SDoc
| CanDeriveAnyClass
| NonDerivableClass SDoc
data PredOrigin = PredOrigin PredType CtOrigin TypeOrKind
data ThetaOrigin
= ThetaOrigin { ThetaOrigin -> [TyVar]
to_anyclass_skols :: [TyVar]
, ThetaOrigin -> [TyVar]
to_anyclass_metas :: [TyVar]
, ThetaOrigin -> [Type]
to_anyclass_givens :: ThetaType
, ThetaOrigin -> [PredOrigin]
to_wanted_origins :: [PredOrigin] }
instance Outputable PredOrigin where
ppr :: PredOrigin -> SDoc
ppr (PredOrigin Type
ty CtOrigin
_ TypeOrKind
_) = Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
ty
instance Outputable ThetaOrigin where
ppr :: ThetaOrigin -> SDoc
ppr (ThetaOrigin { to_anyclass_skols :: ThetaOrigin -> [TyVar]
to_anyclass_skols = [TyVar]
ac_skols
, to_anyclass_metas :: ThetaOrigin -> [TyVar]
to_anyclass_metas = [TyVar]
ac_metas
, to_anyclass_givens :: ThetaOrigin -> [Type]
to_anyclass_givens = [Type]
ac_givens
, to_wanted_origins :: ThetaOrigin -> [PredOrigin]
to_wanted_origins = [PredOrigin]
wanted_origins })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"ThetaOrigin")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"to_anyclass_skols =" SDoc -> SDoc -> SDoc
<+> [TyVar] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TyVar]
ac_skols
, String -> SDoc
text String
"to_anyclass_metas =" SDoc -> SDoc -> SDoc
<+> [TyVar] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TyVar]
ac_metas
, String -> SDoc
text String
"to_anyclass_givens =" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Type]
ac_givens
, String -> SDoc
text String
"to_wanted_origins =" SDoc -> SDoc -> SDoc
<+> [PredOrigin] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [PredOrigin]
wanted_origins ])
mkPredOrigin :: CtOrigin -> TypeOrKind -> PredType -> PredOrigin
mkPredOrigin :: CtOrigin -> TypeOrKind -> Type -> PredOrigin
mkPredOrigin CtOrigin
origin TypeOrKind
t_or_k Type
pred = Type -> CtOrigin -> TypeOrKind -> PredOrigin
PredOrigin Type
pred CtOrigin
origin TypeOrKind
t_or_k
mkThetaOrigin :: CtOrigin -> TypeOrKind
-> [TyVar] -> [TyVar] -> ThetaType -> ThetaType
-> ThetaOrigin
mkThetaOrigin :: CtOrigin
-> TypeOrKind
-> [TyVar]
-> [TyVar]
-> [Type]
-> [Type]
-> ThetaOrigin
mkThetaOrigin CtOrigin
origin TypeOrKind
t_or_k [TyVar]
skols [TyVar]
metas [Type]
givens
= [TyVar] -> [TyVar] -> [Type] -> [PredOrigin] -> ThetaOrigin
ThetaOrigin [TyVar]
skols [TyVar]
metas [Type]
givens ([PredOrigin] -> ThetaOrigin)
-> ([Type] -> [PredOrigin]) -> [Type] -> ThetaOrigin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Type -> PredOrigin) -> [Type] -> [PredOrigin]
forall a b. (a -> b) -> [a] -> [b]
map (CtOrigin -> TypeOrKind -> Type -> PredOrigin
mkPredOrigin CtOrigin
origin TypeOrKind
t_or_k)
mkThetaOriginFromPreds :: [PredOrigin] -> ThetaOrigin
mkThetaOriginFromPreds :: [PredOrigin] -> ThetaOrigin
mkThetaOriginFromPreds = [TyVar] -> [TyVar] -> [Type] -> [PredOrigin] -> ThetaOrigin
ThetaOrigin [] [] []
substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin
substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin
substPredOrigin TCvSubst
subst (PredOrigin Type
pred CtOrigin
origin TypeOrKind
t_or_k)
= Type -> CtOrigin -> TypeOrKind -> PredOrigin
PredOrigin (HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
pred) CtOrigin
origin TypeOrKind
t_or_k
hasStockDeriving
:: Class -> Maybe (SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
hasStockDeriving :: Class
-> Maybe
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
hasStockDeriving Class
clas
= Assoc
Unique
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
-> Unique
-> Maybe
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
forall a b. Eq a => Assoc a b -> a -> Maybe b
assocMaybe Assoc
Unique
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
gen_list (Class -> Unique
forall a. Uniquable a => a -> Unique
getUnique Class
clas)
where
gen_list
:: [(Unique, SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))]
gen_list :: Assoc
Unique
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
gen_list = [ (Unique
eqClassKey, (SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff)
gen_Eq_binds)
, (Unique
ordClassKey, (SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff)
gen_Ord_binds)
, (Unique
enumClassKey, (SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff)
gen_Enum_binds)
, (Unique
boundedClassKey, (SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Bounded_binds)
, (Unique
ixClassKey, (SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff)
gen_Ix_binds)
, (Unique
showClassKey, ((Name -> Fixity)
-> SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {t} {a} {b} {p}.
((Name -> Fixity) -> t -> TyCon -> (a, b))
-> t -> TyCon -> p -> IOEnv (Env TcGblEnv TcLclEnv) (a, b, [Name])
read_or_show (Name -> Fixity)
-> SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Show_binds)
, (Unique
readClassKey, ((Name -> Fixity)
-> SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {t} {a} {b} {p}.
((Name -> Fixity) -> t -> TyCon -> (a, b))
-> t -> TyCon -> p -> IOEnv (Env TcGblEnv TcLclEnv) (a, b, [Name])
read_or_show (Name -> Fixity)
-> SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Read_binds)
, (Unique
dataClassKey, (SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM SrcSpan
-> TyCon
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, BagDerivStuff)
gen_Data_binds)
, (Unique
functorClassKey, (SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Functor_binds)
, (Unique
foldableClassKey, (SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Foldable_binds)
, (Unique
traversableClassKey, (SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Traversable_binds)
, (Unique
liftClassKey, (SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {t} {a} {b} {p} {a}.
Monad m =>
(t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple SrcSpan -> TyCon -> (LHsBinds GhcPs, BagDerivStuff)
gen_Lift_binds)
, (Unique
genClassKey, (TyCon
-> [Type]
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, FamInst))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {a} {p}.
Monad m =>
(TyCon -> t -> m (a, FamInst))
-> p -> TyCon -> t -> m (a, BagDerivStuff, [Name])
generic (GenericKind
-> TyCon
-> [Type]
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, FamInst)
gen_Generic_binds GenericKind
Gen0))
, (Unique
gen1ClassKey, (TyCon
-> [Type]
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, FamInst))
-> SrcSpan
-> TyCon
-> [Type]
-> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
forall {m :: * -> *} {t} {a} {p}.
Monad m =>
(TyCon -> t -> m (a, FamInst))
-> p -> TyCon -> t -> m (a, BagDerivStuff, [Name])
generic (GenericKind
-> TyCon
-> [Type]
-> IOEnv (Env TcGblEnv TcLclEnv) (LHsBinds GhcPs, FamInst)
gen_Generic_binds GenericKind
Gen1)) ]
simple :: (t -> t -> (a, b)) -> t -> t -> p -> m (a, b, [a])
simple t -> t -> (a, b)
gen_fn t
loc t
tc p
_
= let (a
binds, b
deriv_stuff) = t -> t -> (a, b)
gen_fn t
loc t
tc
in (a, b, [a]) -> m (a, b, [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
binds, b
deriv_stuff, [])
simpleM :: (t -> t -> m (a, b)) -> t -> t -> p -> m (a, b, [a])
simpleM t -> t -> m (a, b)
gen_fn t
loc t
tc p
_
= do { (a
binds, b
deriv_stuff) <- t -> t -> m (a, b)
gen_fn t
loc t
tc
; (a, b, [a]) -> m (a, b, [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
binds, b
deriv_stuff, []) }
read_or_show :: ((Name -> Fixity) -> t -> TyCon -> (a, b))
-> t -> TyCon -> p -> IOEnv (Env TcGblEnv TcLclEnv) (a, b, [Name])
read_or_show (Name -> Fixity) -> t -> TyCon -> (a, b)
gen_fn t
loc TyCon
tc p
_
= do { Name -> Fixity
fix_env <- TyCon -> TcM (Name -> Fixity)
getDataConFixityFun TyCon
tc
; let (a
binds, b
deriv_stuff) = (Name -> Fixity) -> t -> TyCon -> (a, b)
gen_fn Name -> Fixity
fix_env t
loc TyCon
tc
field_names :: [Name]
field_names = TyCon -> [Name]
all_field_names TyCon
tc
; (a, b, [Name]) -> IOEnv (Env TcGblEnv TcLclEnv) (a, b, [Name])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
binds, b
deriv_stuff, [Name]
field_names) }
generic :: (TyCon -> t -> m (a, FamInst))
-> p -> TyCon -> t -> m (a, BagDerivStuff, [Name])
generic TyCon -> t -> m (a, FamInst)
gen_fn p
_ TyCon
tc t
inst_tys
= do { (a
binds, FamInst
faminst) <- TyCon -> t -> m (a, FamInst)
gen_fn TyCon
tc t
inst_tys
; let field_names :: [Name]
field_names = TyCon -> [Name]
all_field_names TyCon
tc
; (a, BagDerivStuff, [Name]) -> m (a, BagDerivStuff, [Name])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
binds, DerivStuff -> BagDerivStuff
forall a. a -> Bag a
unitBag (FamInst -> DerivStuff
DerivFamInst FamInst
faminst), [Name]
field_names) }
all_field_names :: TyCon -> [Name]
all_field_names = (FieldLbl Name -> Name) -> [FieldLbl Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldLbl Name -> Name
forall a. FieldLbl a -> a
flSelector ([FieldLbl Name] -> [Name])
-> (TyCon -> [FieldLbl Name]) -> TyCon -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DataCon -> [FieldLbl Name]) -> [DataCon] -> [FieldLbl Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DataCon -> [FieldLbl Name]
dataConFieldLabels
([DataCon] -> [FieldLbl Name])
-> (TyCon -> [DataCon]) -> TyCon -> [FieldLbl Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCon -> [DataCon]
tyConDataCons
getDataConFixityFun :: TyCon -> TcM (Name -> Fixity)
getDataConFixityFun :: TyCon -> TcM (Name -> Fixity)
getDataConFixityFun TyCon
tc
= do { Module
this_mod <- IOEnv (Env TcGblEnv TcLclEnv) Module
forall (m :: * -> *). HasModule m => m Module
getModule
; if Module -> Name -> Bool
nameIsLocalOrFrom Module
this_mod Name
name
then do { FixityEnv
fix_env <- TcRn FixityEnv
getFixityEnv
; (Name -> Fixity) -> TcM (Name -> Fixity)
forall (m :: * -> *) a. Monad m => a -> m a
return (FixityEnv -> Name -> Fixity
lookupFixity FixityEnv
fix_env) }
else do { ModIface
iface <- SDoc -> Name -> TcRn ModIface
loadInterfaceForName SDoc
doc Name
name
; (Name -> Fixity) -> TcM (Name -> Fixity)
forall (m :: * -> *) a. Monad m => a -> m a
return (ModIface -> OccName -> Fixity
mi_fix ModIface
iface (OccName -> Fixity) -> (Name -> OccName) -> Name -> Fixity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> OccName
nameOccName) } }
where
name :: Name
name = TyCon -> Name
tyConName TyCon
tc
doc :: SDoc
doc = String -> SDoc
text String
"Data con fixities for" SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
checkOriginativeSideConditions
:: DynFlags -> DerivContext -> Class -> [TcType]
-> TyCon -> TyCon
-> OriginativeDerivStatus
checkOriginativeSideConditions :: DynFlags
-> DerivContext
-> Class
-> [Type]
-> TyCon
-> TyCon
-> OriginativeDerivStatus
checkOriginativeSideConditions DynFlags
dflags DerivContext
deriv_ctxt Class
cls [Type]
cls_tys TyCon
tc TyCon
rep_tc
| Just Condition
cond <- DerivContext -> Class -> Maybe Condition
stockSideConditions DerivContext
deriv_ctxt Class
cls
= case (Condition
cond DynFlags
dflags TyCon
tc TyCon
rep_tc) of
NotValid SDoc
err -> SDoc -> OriginativeDerivStatus
StockClassError SDoc
err
Validity
IsValid | [Type] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TyCon -> [Type] -> [Type]
filterOutInvisibleTypes (Class -> TyCon
classTyCon Class
cls) [Type]
cls_tys)
, Just SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
gen_fn <- Class
-> Maybe
(SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
hasStockDeriving Class
cls
-> (SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name]))
-> OriginativeDerivStatus
CanDeriveStock SrcSpan
-> TyCon -> [Type] -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])
gen_fn
| Bool
otherwise -> SDoc -> OriginativeDerivStatus
StockClassError (Class -> [Type] -> SDoc
classArgsErr Class
cls [Type]
cls_tys)
| NotValid SDoc
err <- DynFlags -> Validity
canDeriveAnyClass DynFlags
dflags
= SDoc -> OriginativeDerivStatus
NonDerivableClass SDoc
err
| Bool
otherwise
= OriginativeDerivStatus
CanDeriveAnyClass
classArgsErr :: Class -> [Type] -> SDoc
classArgsErr :: Class -> [Type] -> SDoc
classArgsErr Class
cls [Type]
cls_tys = SDoc -> SDoc
quotes (Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Class -> [Type] -> Type
mkClassPred Class
cls [Type]
cls_tys)) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is not a class"
stockSideConditions :: DerivContext -> Class -> Maybe Condition
stockSideConditions :: DerivContext -> Class -> Maybe Condition
stockSideConditions DerivContext
deriv_ctxt Class
cls
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
eqClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_args Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
ordClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_args Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
showClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_args Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
readClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_args Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
enumClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Condition
cond_isEnumeration)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
ixClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_enumOrProduct Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
boundedClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Condition
cond_std Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_enumOrProduct Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
dataClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveDataTypeable Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Class -> Condition
cond_args Class
cls)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
functorClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveFunctor Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Bool -> Bool -> Condition
cond_functorOK Bool
True Bool
False)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
foldableClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveFoldable Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Bool -> Bool -> Condition
cond_functorOK Bool
False Bool
True)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
traversableClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveTraversable Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Bool -> Bool -> Condition
cond_functorOK Bool
False Bool
False)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
genClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveGeneric Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Condition
cond_RepresentableOk)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
gen1ClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveGeneric Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Condition
cond_Representable1Ok)
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
liftClassKey = Condition -> Maybe Condition
forall a. a -> Maybe a
Just (Extension -> Condition
checkFlag Extension
LangExt.DeriveLift Condition -> Condition -> Condition
`andCond`
Condition
cond_vanilla Condition -> Condition -> Condition
`andCond`
Class -> Condition
cond_args Class
cls)
| Bool
otherwise = Maybe Condition
forall a. Maybe a
Nothing
where
cls_key :: Unique
cls_key = Class -> Unique
forall a. Uniquable a => a -> Unique
getUnique Class
cls
cond_std :: Condition
cond_std = DerivContext -> Bool -> Condition
cond_stdOK DerivContext
deriv_ctxt Bool
False
cond_vanilla :: Condition
cond_vanilla = DerivContext -> Bool -> Condition
cond_stdOK DerivContext
deriv_ctxt Bool
True
canDeriveAnyClass :: DynFlags -> Validity
canDeriveAnyClass :: DynFlags -> Validity
canDeriveAnyClass DynFlags
dflags
| Bool -> Bool
not (Extension -> DynFlags -> Bool
xopt Extension
LangExt.DeriveAnyClass DynFlags
dflags)
= SDoc -> Validity
NotValid (String -> SDoc
text String
"Try enabling DeriveAnyClass")
| Bool
otherwise
= Validity
IsValid
type Condition
= DynFlags
-> TyCon
-> TyCon
-> Validity
orCond :: Condition -> Condition -> Condition
orCond :: Condition -> Condition -> Condition
orCond Condition
c1 Condition
c2 DynFlags
dflags TyCon
tc TyCon
rep_tc
= case (Condition
c1 DynFlags
dflags TyCon
tc TyCon
rep_tc, Condition
c2 DynFlags
dflags TyCon
tc TyCon
rep_tc) of
(Validity
IsValid, Validity
_) -> Validity
IsValid
(Validity
_, Validity
IsValid) -> Validity
IsValid
(NotValid SDoc
x, NotValid SDoc
y) -> SDoc -> Validity
NotValid (SDoc
x SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
" or" SDoc -> SDoc -> SDoc
$$ SDoc
y)
andCond :: Condition -> Condition -> Condition
andCond :: Condition -> Condition -> Condition
andCond Condition
c1 Condition
c2 DynFlags
dflags TyCon
tc TyCon
rep_tc
= Condition
c1 DynFlags
dflags TyCon
tc TyCon
rep_tc Validity -> Validity -> Validity
`andValid` Condition
c2 DynFlags
dflags TyCon
tc TyCon
rep_tc
cond_stdOK
:: DerivContext
-> Bool
-> Condition
cond_stdOK :: DerivContext -> Bool -> Condition
cond_stdOK DerivContext
deriv_ctxt Bool
permissive DynFlags
dflags TyCon
tc TyCon
rep_tc
= Validity
valid_ADT Validity -> Validity -> Validity
`andValid` Validity
valid_misc
where
valid_ADT, valid_misc :: Validity
valid_ADT :: Validity
valid_ADT
| TyCon -> Bool
isAlgTyCon TyCon
tc Bool -> Bool -> Bool
|| TyCon -> Bool
isDataFamilyTyCon TyCon
tc
= Validity
IsValid
| Bool
otherwise
= SDoc -> Validity
NotValid (SDoc -> Validity) -> SDoc -> Validity
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"The last argument of the instance must be a"
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"data or newtype application"
valid_misc :: Validity
valid_misc
= case DerivContext
deriv_ctxt of
SupplyContext [Type]
_ -> Validity
IsValid
InferContext Maybe SrcSpan
wildcard
| [DataCon] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [DataCon]
data_cons
, Bool -> Bool
not Bool
permissive
-> Extension -> Condition
checkFlag Extension
LangExt.EmptyDataDeriving DynFlags
dflags TyCon
tc TyCon
rep_tc Validity -> Validity -> Validity
`orValid`
SDoc -> Validity
NotValid (TyCon -> SDoc
no_cons_why TyCon
rep_tc SDoc -> SDoc -> SDoc
$$ SDoc
empty_data_suggestion)
| Bool -> Bool
not ([SDoc] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SDoc]
con_whys)
-> SDoc -> Validity
NotValid ([SDoc] -> SDoc
vcat [SDoc]
con_whys SDoc -> SDoc -> SDoc
$$ Maybe SrcSpan -> SDoc
forall {a}. Maybe a -> SDoc
possible_fix_suggestion Maybe SrcSpan
wildcard)
| Bool
otherwise
-> Validity
IsValid
empty_data_suggestion :: SDoc
empty_data_suggestion =
String -> SDoc
text String
"Use EmptyDataDeriving to enable deriving for empty data types"
possible_fix_suggestion :: Maybe a -> SDoc
possible_fix_suggestion Maybe a
wildcard
= case Maybe a
wildcard of
Just a
_ ->
String -> SDoc
text String
"Possible fix: fill in the wildcard constraint yourself"
Maybe a
Nothing ->
String -> SDoc
text String
"Possible fix: use a standalone deriving declaration instead"
data_cons :: [DataCon]
data_cons = TyCon -> [DataCon]
tyConDataCons TyCon
rep_tc
con_whys :: [SDoc]
con_whys = [Validity] -> [SDoc]
getInvalids ((DataCon -> Validity) -> [DataCon] -> [Validity]
forall a b. (a -> b) -> [a] -> [b]
map DataCon -> Validity
check_con [DataCon]
data_cons)
check_con :: DataCon -> Validity
check_con :: DataCon -> Validity
check_con DataCon
con
| Bool -> Bool
not ([EqSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [EqSpec]
eq_spec)
= String -> Validity
bad String
"is a GADT"
| Bool -> Bool
not ([TyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TyVar]
ex_tvs)
= String -> Validity
bad String
"has existential type variables in its type"
| Bool -> Bool
not ([Type] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Type]
theta)
= String -> Validity
bad String
"has constraints in its type"
| Bool -> Bool
not (Bool
permissive Bool -> Bool -> Bool
|| (Type -> Bool) -> [Type] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
isTauTy ((Scaled Type -> Type) -> [Scaled Type] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Scaled Type -> Type
forall a. Scaled a -> a
scaledThing ([Scaled Type] -> [Type]) -> [Scaled Type] -> [Type]
forall a b. (a -> b) -> a -> b
$ DataCon -> [Scaled Type]
dataConOrigArgTys DataCon
con))
= String -> Validity
bad String
"has a higher-rank type"
| Bool
otherwise
= Validity
IsValid
where
([TyVar]
_, [TyVar]
ex_tvs, [EqSpec]
eq_spec, [Type]
theta, [Scaled Type]
_, Type
_) = DataCon
-> ([TyVar], [TyVar], [EqSpec], [Type], [Scaled Type], Type)
dataConFullSig DataCon
con
bad :: String -> Validity
bad String
msg = SDoc -> Validity
NotValid (DataCon -> SDoc -> SDoc
badCon DataCon
con (String -> SDoc
text String
msg))
no_cons_why :: TyCon -> SDoc
no_cons_why :: TyCon -> SDoc
no_cons_why TyCon
rep_tc = SDoc -> SDoc
quotes (TyCon -> SDoc
pprSourceTyCon TyCon
rep_tc) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"must have at least one data constructor"
cond_RepresentableOk :: Condition
cond_RepresentableOk :: Condition
cond_RepresentableOk DynFlags
_ TyCon
_ TyCon
rep_tc = TyCon -> Validity
canDoGenerics TyCon
rep_tc
cond_Representable1Ok :: Condition
cond_Representable1Ok :: Condition
cond_Representable1Ok DynFlags
_ TyCon
_ TyCon
rep_tc = TyCon -> Validity
canDoGenerics1 TyCon
rep_tc
cond_enumOrProduct :: Class -> Condition
cond_enumOrProduct :: Class -> Condition
cond_enumOrProduct Class
cls = Condition
cond_isEnumeration Condition -> Condition -> Condition
`orCond`
(Condition
cond_isProduct Condition -> Condition -> Condition
`andCond` Class -> Condition
cond_args Class
cls)
cond_args :: Class -> Condition
cond_args :: Class -> Condition
cond_args Class
cls DynFlags
_ TyCon
_ TyCon
rep_tc
= case [Type]
bad_args of
[] -> Validity
IsValid
(Type
ty:[Type]
_) -> SDoc -> Validity
NotValid (SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Don't know how to derive" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Class -> SDoc
forall a. Outputable a => a -> SDoc
ppr Class
cls))
Int
2 (String -> SDoc
text String
"for type" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
ty)))
where
bad_args :: [Type]
bad_args = [ Type
arg_ty | DataCon
con <- TyCon -> [DataCon]
tyConDataCons TyCon
rep_tc
, Scaled Type
_ Type
arg_ty <- DataCon -> [Scaled Type]
dataConOrigArgTys DataCon
con
, HasDebugCallStack => Type -> Maybe Bool
Type -> Maybe Bool
isLiftedType_maybe Type
arg_ty Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
, Bool -> Bool
not (Type -> Bool
ok_ty Type
arg_ty) ]
cls_key :: Unique
cls_key = Class -> Unique
classKey Class
cls
ok_ty :: Type -> Bool
ok_ty Type
arg_ty
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
eqClassKey = Type
-> [(Type, (RdrName, RdrName, RdrName, RdrName, RdrName))] -> Bool
forall a. Type -> [(Type, a)] -> Bool
check_in Type
arg_ty [(Type, (RdrName, RdrName, RdrName, RdrName, RdrName))]
ordOpTbl
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
ordClassKey = Type
-> [(Type, (RdrName, RdrName, RdrName, RdrName, RdrName))] -> Bool
forall a. Type -> [(Type, a)] -> Bool
check_in Type
arg_ty [(Type, (RdrName, RdrName, RdrName, RdrName, RdrName))]
ordOpTbl
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
showClassKey = Type -> [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)] -> Bool
forall a. Type -> [(Type, a)] -> Bool
check_in Type
arg_ty [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)]
boxConTbl
| Unique
cls_key Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== Unique
liftClassKey = Bool
True
| Bool
otherwise = Bool
False
check_in :: Type -> [(Type,a)] -> Bool
check_in :: forall a. Type -> [(Type, a)] -> Bool
check_in Type
arg_ty [(Type, a)]
tbl = ((Type, a) -> Bool) -> [(Type, a)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> Type -> Bool
eqType Type
arg_ty (Type -> Bool) -> ((Type, a) -> Type) -> (Type, a) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Type, a) -> Type
forall a b. (a, b) -> a
fst) [(Type, a)]
tbl
cond_isEnumeration :: Condition
cond_isEnumeration :: Condition
cond_isEnumeration DynFlags
_ TyCon
_ TyCon
rep_tc
| TyCon -> Bool
isEnumerationTyCon TyCon
rep_tc = Validity
IsValid
| Bool
otherwise = SDoc -> Validity
NotValid SDoc
why
where
why :: SDoc
why = [SDoc] -> SDoc
sep [ SDoc -> SDoc
quotes (TyCon -> SDoc
pprSourceTyCon TyCon
rep_tc) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"must be an enumeration type"
, String -> SDoc
text String
"(an enumeration consists of one or more nullary, non-GADT constructors)" ]
cond_isProduct :: Condition
cond_isProduct :: Condition
cond_isProduct DynFlags
_ TyCon
_ TyCon
rep_tc
| TyCon -> Bool
isProductTyCon TyCon
rep_tc = Validity
IsValid
| Bool
otherwise = SDoc -> Validity
NotValid SDoc
why
where
why :: SDoc
why = SDoc -> SDoc
quotes (TyCon -> SDoc
pprSourceTyCon TyCon
rep_tc) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"must have precisely one constructor"
cond_functorOK :: Bool -> Bool -> Condition
cond_functorOK :: Bool -> Bool -> Condition
cond_functorOK Bool
allowFunctions Bool
allowExQuantifiedLastTyVar DynFlags
_ TyCon
_ TyCon
rep_tc
| [TyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TyVar]
tc_tvs
= SDoc -> Validity
NotValid (String -> SDoc
text String
"Data type" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
rep_tc)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"must have some type parameters")
| Bool -> Bool
not ([Type] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Type]
bad_stupid_theta)
= SDoc -> Validity
NotValid (String -> SDoc
text String
"Data type" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
rep_tc)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"must not have a class context:" SDoc -> SDoc -> SDoc
<+> [Type] -> SDoc
pprTheta [Type]
bad_stupid_theta)
| Bool
otherwise
= [Validity] -> Validity
allValid ((DataCon -> Validity) -> [DataCon] -> [Validity]
forall a b. (a -> b) -> [a] -> [b]
map DataCon -> Validity
check_con [DataCon]
data_cons)
where
tc_tvs :: [TyVar]
tc_tvs = TyCon -> [TyVar]
tyConTyVars TyCon
rep_tc
last_tv :: TyVar
last_tv = [TyVar] -> TyVar
forall a. [a] -> a
last [TyVar]
tc_tvs
bad_stupid_theta :: [Type]
bad_stupid_theta = (Type -> Bool) -> [Type] -> [Type]
forall a. (a -> Bool) -> [a] -> [a]
filter Type -> Bool
is_bad (TyCon -> [Type]
tyConStupidTheta TyCon
rep_tc)
is_bad :: Type -> Bool
is_bad Type
pred = TyVar
last_tv TyVar -> VarSet -> Bool
`elemVarSet` Type -> VarSet
exactTyCoVarsOfType Type
pred
data_cons :: [DataCon]
data_cons = TyCon -> [DataCon]
tyConDataCons TyCon
rep_tc
check_con :: DataCon -> Validity
check_con DataCon
con = [Validity] -> Validity
allValid (DataCon -> Validity
check_universal DataCon
con Validity -> [Validity] -> [Validity]
forall a. a -> [a] -> [a]
: FFoldType Validity -> DataCon -> [Validity]
forall a. FFoldType a -> DataCon -> [a]
foldDataConArgs (DataCon -> FFoldType Validity
ft_check DataCon
con) DataCon
con)
check_universal :: DataCon -> Validity
check_universal :: DataCon -> Validity
check_universal DataCon
con
| Bool
allowExQuantifiedLastTyVar
= Validity
IsValid
| Just TyVar
tv <- Type -> Maybe TyVar
getTyVar_maybe ([Type] -> Type
forall a. [a] -> a
last (Type -> [Type]
tyConAppArgs (DataCon -> Type
dataConOrigResTy DataCon
con)))
, TyVar
tv TyVar -> [TyVar] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DataCon -> [TyVar]
dataConUnivTyVars DataCon
con
, Bool -> Bool
not (TyVar
tv TyVar -> VarSet -> Bool
`elemVarSet` [Type] -> VarSet
exactTyCoVarsOfTypes (DataCon -> [Type]
dataConTheta DataCon
con))
= Validity
IsValid
| Bool
otherwise
= SDoc -> Validity
NotValid (DataCon -> SDoc -> SDoc
badCon DataCon
con SDoc
existential)
ft_check :: DataCon -> FFoldType Validity
ft_check :: DataCon -> FFoldType Validity
ft_check DataCon
con = FT :: forall a.
a
-> a
-> a
-> (a -> a -> a)
-> (TyCon -> [a] -> a)
-> (Type -> Type -> a -> a)
-> a
-> (TyVar -> a -> a)
-> FFoldType a
FT { ft_triv :: Validity
ft_triv = Validity
IsValid, ft_var :: Validity
ft_var = Validity
IsValid
, ft_co_var :: Validity
ft_co_var = SDoc -> Validity
NotValid (DataCon -> SDoc -> SDoc
badCon DataCon
con SDoc
covariant)
, ft_fun :: Validity -> Validity -> Validity
ft_fun = \Validity
x Validity
y -> if Bool
allowFunctions then Validity
x Validity -> Validity -> Validity
`andValid` Validity
y
else SDoc -> Validity
NotValid (DataCon -> SDoc -> SDoc
badCon DataCon
con SDoc
functions)
, ft_tup :: TyCon -> [Validity] -> Validity
ft_tup = \TyCon
_ [Validity]
xs -> [Validity] -> Validity
allValid [Validity]
xs
, ft_ty_app :: Type -> Type -> Validity -> Validity
ft_ty_app = \Type
_ Type
_ Validity
x -> Validity
x
, ft_bad_app :: Validity
ft_bad_app = SDoc -> Validity
NotValid (DataCon -> SDoc -> SDoc
badCon DataCon
con SDoc
wrong_arg)
, ft_forall :: TyVar -> Validity -> Validity
ft_forall = \TyVar
_ Validity
x -> Validity
x }
existential :: SDoc
existential = String -> SDoc
text String
"must be truly polymorphic in the last argument of the data type"
covariant :: SDoc
covariant = String -> SDoc
text String
"must not use the type variable in a function argument"
functions :: SDoc
functions = String -> SDoc
text String
"must not contain function types"
wrong_arg :: SDoc
wrong_arg = String -> SDoc
text String
"must use the type variable only as the last argument of a data type"
checkFlag :: LangExt.Extension -> Condition
checkFlag :: Extension -> Condition
checkFlag Extension
flag DynFlags
dflags TyCon
_ TyCon
_
| Extension -> DynFlags -> Bool
xopt Extension
flag DynFlags
dflags = Validity
IsValid
| Bool
otherwise = SDoc -> Validity
NotValid SDoc
why
where
why :: SDoc
why = String -> SDoc
text String
"You need " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
flag_str
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"to derive an instance for this class"
flag_str :: String
flag_str = case [ FlagSpec Extension -> String
forall flag. FlagSpec flag -> String
flagSpecName FlagSpec Extension
f | FlagSpec Extension
f <- [FlagSpec Extension]
xFlags , FlagSpec Extension -> Extension
forall flag. FlagSpec flag -> flag
flagSpecFlag FlagSpec Extension
f Extension -> Extension -> Bool
forall a. Eq a => a -> a -> Bool
== Extension
flag ] of
[String
s] -> String
s
[String]
other -> String -> SDoc -> String
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"checkFlag" ([String] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [String]
other)
std_class_via_coercible :: Class -> Bool
std_class_via_coercible :: Class -> Bool
std_class_via_coercible Class
clas
= Class -> Unique
classKey Class
clas Unique -> [Unique] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Unique
eqClassKey, Unique
ordClassKey, Unique
ixClassKey, Unique
boundedClassKey]
non_coercible_class :: Class -> Bool
non_coercible_class :: Class -> Bool
non_coercible_class Class
cls
= Class -> Unique
classKey Class
cls Unique -> [Unique] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([ Unique
readClassKey, Unique
showClassKey, Unique
dataClassKey
, Unique
genClassKey, Unique
gen1ClassKey, Unique
typeableClassKey
, Unique
traversableClassKey, Unique
liftClassKey ])
badCon :: DataCon -> SDoc -> SDoc
badCon :: DataCon -> SDoc -> SDoc
badCon DataCon
con SDoc
msg = String -> SDoc
text String
"Constructor" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (DataCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr DataCon
con) SDoc -> SDoc -> SDoc
<+> SDoc
msg
newDerivClsInst :: ThetaType -> DerivSpec theta -> TcM ClsInst
newDerivClsInst :: forall theta. [Type] -> DerivSpec theta -> TcM ClsInst
newDerivClsInst [Type]
theta (DS { ds_name :: forall theta. DerivSpec theta -> Name
ds_name = Name
dfun_name, ds_overlap :: forall theta. DerivSpec theta -> Maybe OverlapMode
ds_overlap = Maybe OverlapMode
overlap_mode
, ds_tvs :: forall theta. DerivSpec theta -> [TyVar]
ds_tvs = [TyVar]
tvs, ds_cls :: forall theta. DerivSpec theta -> Class
ds_cls = Class
clas, ds_tys :: forall theta. DerivSpec theta -> [Type]
ds_tys = [Type]
tys })
= Maybe OverlapMode
-> Name -> [TyVar] -> [Type] -> Class -> [Type] -> TcM ClsInst
newClsInst Maybe OverlapMode
overlap_mode Name
dfun_name [TyVar]
tvs [Type]
theta Class
clas [Type]
tys
extendLocalInstEnv :: [ClsInst] -> TcM a -> TcM a
extendLocalInstEnv :: forall a. [ClsInst] -> TcM a -> TcM a
extendLocalInstEnv [ClsInst]
dfuns TcM a
thing_inside
= do { TcGblEnv
env <- TcRnIf TcGblEnv TcLclEnv TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; let inst_env' :: InstEnv
inst_env' = InstEnv -> [ClsInst] -> InstEnv
extendInstEnvList (TcGblEnv -> InstEnv
tcg_inst_env TcGblEnv
env) [ClsInst]
dfuns
env' :: TcGblEnv
env' = TcGblEnv
env { tcg_inst_env :: InstEnv
tcg_inst_env = InstEnv
inst_env' }
; TcGblEnv -> TcM a -> TcM a
forall gbl lcl a. gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setGblEnv TcGblEnv
env' TcM a
thing_inside }