Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Typechecking patterns
Synopsis
- tcLetPat :: (Name -> Maybe TcId) -> LetBndrSpec -> LPat GhcRn -> Scaled ExpSigmaType -> TcM a -> TcM (LPat GhcTc, a)
- newLetBndr :: LetBndrSpec -> Name -> Mult -> TcType -> TcM TcId
- data LetBndrSpec
- tcCheckPat :: HsMatchContext GhcRn -> LPat GhcRn -> Scaled TcSigmaType -> TcM a -> TcM (LPat GhcTc, a)
- tcCheckPat_O :: HsMatchContext GhcRn -> CtOrigin -> LPat GhcRn -> Scaled TcSigmaType -> TcM a -> TcM (LPat GhcTc, a)
- tcInferPat :: HsMatchContext GhcRn -> LPat GhcRn -> TcM a -> TcM ((LPat GhcTc, a), TcSigmaType)
- tcPats :: HsMatchContext GhcRn -> [LPat GhcRn] -> [Scaled ExpSigmaType] -> TcM a -> TcM ([LPat GhcTc], a)
- addDataConStupidTheta :: DataCon -> [TcType] -> TcM ()
- badFieldCon :: ConLike -> FieldLabelString -> SDoc
- polyPatSig :: TcType -> SDoc
Documentation
tcLetPat :: (Name -> Maybe TcId) -> LetBndrSpec -> LPat GhcRn -> Scaled ExpSigmaType -> TcM a -> TcM (LPat GhcTc, a) Source #
newLetBndr :: LetBndrSpec -> Name -> Mult -> TcType -> TcM TcId Source #
data LetBndrSpec Source #
Instances
Outputable LetBndrSpec Source # | |
Defined in GHC.Tc.Gen.Pat ppr :: LetBndrSpec -> SDoc Source # |
tcCheckPat :: HsMatchContext GhcRn -> LPat GhcRn -> Scaled TcSigmaType -> TcM a -> TcM (LPat GhcTc, a) Source #
:: HsMatchContext GhcRn | |
-> CtOrigin | origin to use if the type needs inst'ing |
-> LPat GhcRn | |
-> Scaled TcSigmaType | |
-> TcM a | |
-> TcM (LPat GhcTc, a) |
A variant of tcPat
that takes a custom origin
tcInferPat :: HsMatchContext GhcRn -> LPat GhcRn -> TcM a -> TcM ((LPat GhcTc, a), TcSigmaType) Source #
tcPats :: HsMatchContext GhcRn -> [LPat GhcRn] -> [Scaled ExpSigmaType] -> TcM a -> TcM ([LPat GhcTc], a) Source #
badFieldCon :: ConLike -> FieldLabelString -> SDoc Source #
polyPatSig :: TcType -> SDoc Source #