Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Rank
- data UserTypeCtxt
- checkValidType :: UserTypeCtxt -> Type -> TcM ()
- checkValidMonoType :: Type -> TcM ()
- expectedKindInCtxt :: UserTypeCtxt -> Maybe Kind
- checkValidTheta :: UserTypeCtxt -> ThetaType -> TcM ()
- checkValidFamPats :: TyCon -> [TyVar] -> [Type] -> TcM ()
- checkValidInstance :: UserTypeCtxt -> LHsType Name -> Type -> TcM ([TyVar], ThetaType, Class, [Type])
- validDerivPred :: TyVarSet -> PredType -> Bool
- checkInstTermination :: [TcType] -> ThetaType -> TcM ()
- checkValidTyFamInst :: Maybe (Class, VarEnv Type) -> TyCon -> CoAxBranch -> TcM ()
- checkTyFamFreeness :: Type -> TcM ()
- checkValidTyFamEqn :: Maybe ClsInfo -> TyCon -> [TyVar] -> [Type] -> Type -> SrcSpan -> TcM ()
- checkConsistentFamInst :: Maybe (Class, VarEnv Type) -> TyCon -> [TyVar] -> [Type] -> TcM ()
- arityErr :: Outputable a => String -> a -> Int -> Int -> SDoc
- badATErr :: Name -> Name -> SDoc
- type ClsInfo = (Class, VarEnv Type)
Documentation
data UserTypeCtxt Source
checkValidType :: UserTypeCtxt -> Type -> TcM () Source
checkValidMonoType :: Type -> TcM () Source
checkValidTheta :: UserTypeCtxt -> ThetaType -> TcM () Source
checkValidInstance :: UserTypeCtxt -> LHsType Name -> Type -> TcM ([TyVar], ThetaType, Class, [Type]) Source
validDerivPred :: TyVarSet -> PredType -> Bool Source
checkInstTermination :: [TcType] -> ThetaType -> TcM () Source
checkValidTyFamInst :: Maybe (Class, VarEnv Type) -> TyCon -> CoAxBranch -> TcM () Source
checkTyFamFreeness :: Type -> TcM () Source
:: Maybe ClsInfo | |
-> TyCon | of the type family |
-> [TyVar] | bound tyvars in the equation |
-> [Type] | type patterns |
-> Type | rhs |
-> SrcSpan | |
-> TcM () |
Do validity checks on a type family equation, including consistency with any enclosing class instance head, termination, and lack of polytypes.