| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Tc.Validity
Synopsis
- data Rank
 - data UserTypeCtxt
- = FunSigCtxt Name ReportRedundantConstraints
 - | InfSigCtxt Name
 - | ExprSigCtxt ReportRedundantConstraints
 - | KindSigCtxt
 - | StandaloneKindSigCtxt Name
 - | TypeAppCtxt
 - | ConArgCtxt Name
 - | TySynCtxt Name
 - | PatSynCtxt Name
 - | PatSigCtxt
 - | RuleSigCtxt FastString Name
 - | ForSigCtxt Name
 - | DefaultDeclCtxt
 - | InstDeclCtxt Bool
 - | SpecInstCtxt
 - | GenSigCtxt
 - | GhciCtxt Bool
 - | ClassSCCtxt Name
 - | SigmaCtxt
 - | DataTyCtxt Name
 - | DerivClauseCtxt
 - | TyVarBndrKindCtxt Name
 - | DataKindCtxt Name
 - | TySynKindCtxt Name
 - | TyFamResKindCtxt Name
 
 - checkValidType :: UserTypeCtxt -> Type -> TcM ()
 - checkValidMonoType :: Type -> TcM ()
 - checkValidTheta :: UserTypeCtxt -> ThetaType -> TcM ()
 - checkValidInstance :: UserTypeCtxt -> LHsSigType GhcRn -> Type -> TcM ()
 - checkValidInstHead :: UserTypeCtxt -> Class -> [Type] -> TcM ()
 - validDerivPred :: PatersonSize -> PredType -> Bool
 - checkTySynRhs :: UserTypeCtxt -> TcType -> TcM ()
 - checkEscapingKind :: Type -> TcM ()
 - checkValidCoAxiom :: CoAxiom Branched -> TcM ()
 - checkValidCoAxBranch :: TyCon -> CoAxBranch -> TcM ()
 - checkValidTyFamEqn :: TyCon -> [Var] -> [Type] -> Type -> TcM ()
 - checkValidAssocTyFamDeflt :: TyCon -> [Type] -> TcM ()
 - checkConsistentFamInst :: AssocInstInfo -> TyCon -> CoAxBranch -> TcM ()
 - checkTyConTelescope :: TyCon -> TcM ()
 
Documentation
Constructors
| ArbitraryRank | |
| LimitedRank Bool Rank | |
| MonoTypeRankZero | |
| MonoTypeTyConArg | |
| MonoTypeSynArg | |
| MonoTypeConstraint | |
| MustBeMonoType | 
Instances
data UserTypeCtxt Source #
UserTypeCtxt describes the origin of the polymorphic type in the places where we need an expression to have that type
Constructors
Instances
| Eq UserTypeCtxt Source # | |
Defined in GHC.Tc.Types.Origin  | |
checkValidType :: UserTypeCtxt -> Type -> TcM () Source #
checkValidMonoType :: Type -> TcM () Source #
checkValidTheta :: UserTypeCtxt -> ThetaType -> TcM () Source #
checkValidInstance :: UserTypeCtxt -> LHsSigType GhcRn -> Type -> TcM () Source #
checkValidInstHead :: UserTypeCtxt -> Class -> [Type] -> TcM () Source #
validDerivPred :: PatersonSize -> PredType -> Bool Source #
checkTySynRhs :: UserTypeCtxt -> TcType -> TcM () Source #
checkEscapingKind :: Type -> TcM () Source #
checkValidCoAxBranch :: TyCon -> CoAxBranch -> TcM () Source #
Arguments
| :: TyCon | of the type family  | 
| -> [Var] | Bound variables in the equation  | 
| -> [Type] | Type patterns  | 
| -> Type | Rhs  | 
| -> TcM () | 
Do validity checks on a type family equation, including consistency with any enclosing class instance head, termination, and lack of polytypes.
checkValidAssocTyFamDeflt Source #
Checks that an associated type family default:
- Only consists of arguments that are bare type variables, and
 - Has a distinct type variable in each argument.
 
See Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
checkConsistentFamInst Source #
Arguments
| :: AssocInstInfo | |
| -> TyCon | Family tycon  | 
| -> CoAxBranch | |
| -> TcM () | 
checkTyConTelescope :: TyCon -> TcM () Source #