Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Typecheck some Matches
Synopsis
- tcMatchesFun :: LocatedN Name -> MatchGroup GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (HsWrapper, MatchGroup GhcTc (LHsExpr GhcTc))
- tcGRHS :: TcMatchCtxt body -> ExpRhoType -> GRHS GhcRn (LocatedA (body GhcRn)) -> TcM (GRHS GhcTc (LocatedA (body GhcTc)))
- tcGRHSsPat :: GRHSs GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (GRHSs GhcTc (LHsExpr GhcTc))
- tcMatchesCase :: AnnoBody body => TcMatchCtxt body -> Scaled TcSigmaTypeFRR -> MatchGroup GhcRn (LocatedA (body GhcRn)) -> ExpRhoType -> TcM (MatchGroup GhcTc (LocatedA (body GhcTc)))
- tcMatchLambda :: ExpectedFunTyOrigin -> TcMatchCtxt HsExpr -> MatchGroup GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (HsWrapper, MatchGroup GhcTc (LHsExpr GhcTc))
- data TcMatchCtxt body = MC {
- mc_what :: HsMatchContext GhcTc
- mc_body :: LocatedA (body GhcRn) -> ExpRhoType -> TcM (LocatedA (body GhcTc))
- type TcStmtChecker body rho_type = forall thing. HsStmtContext GhcTc -> Stmt GhcRn (LocatedA (body GhcRn)) -> rho_type -> (rho_type -> TcM thing) -> TcM (Stmt GhcTc (LocatedA (body GhcTc)), thing)
- type TcExprStmtChecker = TcStmtChecker HsExpr ExpRhoType
- type TcCmdStmtChecker = TcStmtChecker HsCmd TcRhoType
- tcStmts :: AnnoBody body => HsStmtContext GhcTc -> TcStmtChecker body rho_type -> [LStmt GhcRn (LocatedA (body GhcRn))] -> rho_type -> TcM [LStmt GhcTc (LocatedA (body GhcTc))]
- tcStmtsAndThen :: AnnoBody body => HsStmtContext GhcTc -> TcStmtChecker body rho_type -> [LStmt GhcRn (LocatedA (body GhcRn))] -> rho_type -> (rho_type -> TcM thing) -> TcM ([LStmt GhcTc (LocatedA (body GhcTc))], thing)
- tcDoStmts :: HsDoFlavour -> LocatedL [LStmt GhcRn (LHsExpr GhcRn)] -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcBody :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc)
- tcDoStmt :: TcExprStmtChecker
- tcGuardStmt :: TcExprStmtChecker
- checkArgCounts :: AnnoBody body => HsMatchContext GhcTc -> MatchGroup GhcRn (LocatedA (body GhcRn)) -> TcM ()
Documentation
tcMatchesFun :: LocatedN Name -> MatchGroup GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (HsWrapper, MatchGroup GhcTc (LHsExpr GhcTc)) Source #
tcGRHS :: TcMatchCtxt body -> ExpRhoType -> GRHS GhcRn (LocatedA (body GhcRn)) -> TcM (GRHS GhcTc (LocatedA (body GhcTc))) Source #
tcGRHSsPat :: GRHSs GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (GRHSs GhcTc (LHsExpr GhcTc)) Source #
:: AnnoBody body | |
=> TcMatchCtxt body | Case context |
-> Scaled TcSigmaTypeFRR | Type of scrutinee |
-> MatchGroup GhcRn (LocatedA (body GhcRn)) | The case alternatives |
-> ExpRhoType | Type of the whole case expression |
-> TcM (MatchGroup GhcTc (LocatedA (body GhcTc))) |
tcMatchLambda :: ExpectedFunTyOrigin -> TcMatchCtxt HsExpr -> MatchGroup GhcRn (LHsExpr GhcRn) -> ExpRhoType -> TcM (HsWrapper, MatchGroup GhcTc (LHsExpr GhcTc)) Source #
data TcMatchCtxt body Source #
type TcStmtChecker body rho_type = forall thing. HsStmtContext GhcTc -> Stmt GhcRn (LocatedA (body GhcRn)) -> rho_type -> (rho_type -> TcM thing) -> TcM (Stmt GhcTc (LocatedA (body GhcTc)), thing) Source #
tcStmts :: AnnoBody body => HsStmtContext GhcTc -> TcStmtChecker body rho_type -> [LStmt GhcRn (LocatedA (body GhcRn))] -> rho_type -> TcM [LStmt GhcTc (LocatedA (body GhcTc))] Source #
tcStmtsAndThen :: AnnoBody body => HsStmtContext GhcTc -> TcStmtChecker body rho_type -> [LStmt GhcRn (LocatedA (body GhcRn))] -> rho_type -> (rho_type -> TcM thing) -> TcM ([LStmt GhcTc (LocatedA (body GhcTc))], thing) Source #
tcDoStmts :: HsDoFlavour -> LocatedL [LStmt GhcRn (LHsExpr GhcRn)] -> ExpRhoType -> TcM (HsExpr GhcTc) Source #
checkArgCounts :: AnnoBody body => HsMatchContext GhcTc -> MatchGroup GhcRn (LocatedA (body GhcRn)) -> TcM () Source #
checkArgCounts
takes a [RenamedMatch]
and decides whether the same
number of args are used in each equation.