Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- dsLit :: HsLit GhcRn -> DsM CoreExpr
- dsOverLit :: HsOverLit GhcTc -> DsM CoreExpr
- hsLitKey :: Platform -> HsLit GhcTc -> Literal
- tidyLitPat :: HsLit GhcTc -> Pat GhcTc
- tidyNPat :: HsOverLit GhcTc -> Maybe (SyntaxExpr GhcTc) -> SyntaxExpr GhcTc -> Type -> Pat GhcTc
- matchLiterals :: NonEmpty Id -> Type -> NonEmpty (NonEmpty EquationInfo) -> DsM (MatchResult CoreExpr)
- matchNPlusKPats :: NonEmpty Id -> Type -> NonEmpty EquationInfo -> DsM (MatchResult CoreExpr)
- matchNPats :: NonEmpty Id -> Type -> NonEmpty EquationInfo -> DsM (MatchResult CoreExpr)
- warnAboutIdentities :: DynFlags -> CoreExpr -> Type -> DsM ()
- warnAboutOverflowedOverLit :: HsOverLit GhcTc -> DsM ()
- warnAboutOverflowedLit :: HsLit GhcTc -> DsM ()
- warnAboutEmptyEnumerations :: FamInstEnvs -> DynFlags -> LHsExpr GhcTc -> Maybe (LHsExpr GhcTc) -> LHsExpr GhcTc -> DsM ()
Documentation
tidyNPat :: HsOverLit GhcTc -> Maybe (SyntaxExpr GhcTc) -> SyntaxExpr GhcTc -> Type -> Pat GhcTc Source #
:: NonEmpty Id | |
-> Type | Type of the whole case expression |
-> NonEmpty (NonEmpty EquationInfo) | All PgLits |
-> DsM (MatchResult CoreExpr) |
matchNPlusKPats :: NonEmpty Id -> Type -> NonEmpty EquationInfo -> DsM (MatchResult CoreExpr) Source #
matchNPats :: NonEmpty Id -> Type -> NonEmpty EquationInfo -> DsM (MatchResult CoreExpr) Source #
warnAboutOverflowedOverLit :: HsOverLit GhcTc -> DsM () Source #
Emit warnings on overloaded integral literals which overflow the bounds implied by their type.