Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data DerivSpec theta = DS {
- ds_loc :: SrcSpan
- ds_name :: Name
- ds_tvs :: [TyVar]
- ds_theta :: theta
- ds_cls :: Class
- ds_tys :: [Type]
- ds_tc :: TyCon
- ds_overlap :: Maybe OverlapMode
- ds_mechanism :: DerivSpecMechanism
- pprDerivSpec :: Outputable theta => DerivSpec theta -> SDoc
- data DerivSpecMechanism
- = DerivSpecStock (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds RdrName, BagDerivStuff))
- | DerivSpecNewtype Type
- | DerivSpecAnyClass
- isDerivSpecStock :: DerivSpecMechanism -> Bool
- isDerivSpecNewtype :: DerivSpecMechanism -> Bool
- isDerivSpecAnyClass :: DerivSpecMechanism -> Bool
- type DerivContext = Maybe ThetaType
- data DerivStatus
- data PredOrigin = PredOrigin PredType CtOrigin TypeOrKind
- data ThetaOrigin = ThetaOrigin {
- to_tvs :: [TyVar]
- to_givens :: ThetaType
- to_wanted_origins :: [PredOrigin]
- mkPredOrigin :: CtOrigin -> TypeOrKind -> PredType -> PredOrigin
- mkThetaOrigin :: CtOrigin -> TypeOrKind -> [TyVar] -> ThetaType -> ThetaType -> ThetaOrigin
- mkThetaOriginFromPreds :: [PredOrigin] -> ThetaOrigin
- substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin
- checkSideConditions :: DynFlags -> DerivContext -> Class -> [TcType] -> TyCon -> DerivStatus
- hasStockDeriving :: Class -> Maybe (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds RdrName, BagDerivStuff))
- 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
DS | |
|
Outputable theta => Outputable (DerivSpec theta) # | |
pprDerivSpec :: Outputable theta => DerivSpec theta -> SDoc Source #
data DerivSpecMechanism Source #
DerivSpecStock (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds RdrName, BagDerivStuff)) | |
DerivSpecNewtype Type | The newtype rep type |
DerivSpecAnyClass |
type DerivContext = Maybe ThetaType Source #
data DerivStatus Source #
data PredOrigin Source #
data ThetaOrigin Source #
A list of wanted PredOrigin
constraints (to_wanted_origins
) alongside
any corresponding given constraints (to_givens
) and locally quantified
type variables (to_tvs
).
In most cases, to_givens
will be empty, as most deriving mechanisms (e.g.,
stock and newtype deriving) do not require given constraints. The exception
is DeriveAnyClass
, which can involve given constraints. For example,
if you tried to derive an instance for the following class using
DeriveAnyClass
:
class Foo a where bar :: a -> b -> String default bar :: (Show a, Ix b) => a -> b -> String bar = show baz :: Eq a => a -> a -> Bool default baz :: Ord a => a -> a -> Bool baz x y = compare x y == EQ
Then it would generate two ThetaOrigin
s, one for each method:
[ ThetaOrigin { to_tvs = [b] , to_givens = [] , to_wanted_origins = [Show a, Ix b] } , ThetaOrigin { to_tvs = [] , to_givens = [Eq a] , to_wanted_origins = [Ord a] } ]
ThetaOrigin | |
|
mkPredOrigin :: CtOrigin -> TypeOrKind -> PredType -> PredOrigin Source #
mkThetaOrigin :: CtOrigin -> TypeOrKind -> [TyVar] -> ThetaType -> ThetaType -> ThetaOrigin Source #
substPredOrigin :: HasCallStack => TCvSubst -> PredOrigin -> PredOrigin Source #
checkSideConditions :: DynFlags -> DerivContext -> Class -> [TcType] -> TyCon -> DerivStatus Source #
hasStockDeriving :: Class -> Maybe (SrcSpan -> TyCon -> [Type] -> TcM (LHsBinds RdrName, BagDerivStuff)) Source #
canDeriveAnyClass :: DynFlags -> Validity Source #
std_class_via_coercible :: Class -> Bool Source #
non_coercible_class :: Class -> Bool Source #