Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- checkSingle :: DynFlags -> DsMatchContext -> Id -> Pat GhcTc -> DsM ()
- checkMatches :: DsMatchContext -> [Id] -> [LMatch GhcTc (LHsExpr GhcTc)] -> DsM [Deltas]
- checkGuardMatches :: HsMatchContext GhcRn -> GRHSs GhcTc (LHsExpr GhcTc) -> DsM [Deltas]
- isMatchContextPmChecked :: DynFlags -> Origin -> HsMatchContext id -> Bool
- addTyCsDs :: Origin -> Bag EvVar -> DsM a -> DsM a
- addScrutTmCs :: Maybe (LHsExpr GhcTc) -> [Id] -> DsM a -> DsM a
Documentation
checkSingle :: DynFlags -> DsMatchContext -> Id -> Pat GhcTc -> DsM () Source #
Check a single pattern binding (let) for exhaustiveness.
:: DsMatchContext | Match context, for warnings messages |
-> [Id] | Match variables, i.e. x and y above |
-> [LMatch GhcTc (LHsExpr GhcTc)] | List of matches |
-> DsM [Deltas] | One covered |
Check a list of syntactic matches (part of case, functions, etc.), each with a pat and one or more grhss:
f x y | x == y = 1 -- match on x and y with two guarded RHSs | otherwise = 2 f _ _ = 3 -- clause with a single, un-guarded RHS
Returns one Deltas
for each GRHS, representing its covered values, or the
incoming uncovered Deltas
(from getPmDeltas
) if the GRHS is inaccessible.
Since there is at least one grhs per match, the list of Deltas
is at
least as long as the list of matches.
:: HsMatchContext GhcRn | Match context, for warning messages |
-> GRHSs GhcTc (LHsExpr GhcTc) | The GRHSs to check |
-> DsM [Deltas] | Covered |
Exhaustive for guard matches, is used for guards in pattern bindings and
in MultiIf
expressions. Returns the Deltas
covered by the RHSs.
isMatchContextPmChecked :: DynFlags -> Origin -> HsMatchContext id -> Bool Source #
Check whether any part of pattern match checking is enabled for this
HsMatchContext
(does not matter whether it is the redundancy check or the
exhaustiveness check).
addTyCsDs :: Origin -> Bag EvVar -> DsM a -> DsM a Source #
Add in-scope type constraints if the coverage checker might run and then run the given action.
addScrutTmCs :: Maybe (LHsExpr GhcTc) -> [Id] -> DsM a -> DsM a Source #
Add equalities for the scrutinee to the local DsM
environment when
checking a case expression:
case e of x { matches }
When checking matches we record that (x ~ e) where x is the initial
uncovered. All matches will have to satisfy this equality.