Safe Haskell | None |
---|---|
Language | Haskell2010 |
Coverage checking, case splitting, and splitting for refine tactics.
- data SplitClause = SClause {}
- clauseToSplitClause :: Clause -> SplitClause
- fixTarget :: SplitClause -> TCM (Telescope, SplitClause)
- data Covering = Covering {
- covSplitArg :: Arg Nat
- covSplitClauses :: [(QName, SplitClause)]
- splitClauses :: Covering -> [SplitClause]
- coverageCheck :: QName -> Type -> [Clause] -> TCM SplitTree
- isCovered :: QName -> [Clause] -> SplitClause -> TCM Bool
- splitClauseWithAbsurd :: SplitClause -> Nat -> TCM (Either SplitError (Either SplitClause Covering))
- splitLast :: Induction -> Telescope -> [NamedArg DeBruijnPattern] -> TCM (Either SplitError Covering)
- splitResult :: QName -> SplitClause -> TCM (Maybe Covering)
- normaliseProjP :: (NormaliseProjP a, HasConstInfo m) => a -> m a
Documentation
data SplitClause Source #
SClause | |
|
PrettyTCM SplitClause Source # | For debugging only. |
clauseToSplitClause :: Clause -> SplitClause Source #
Create a split clause from a clause in internal syntax. Used by make-case.
fixTarget :: SplitClause -> TCM (Telescope, SplitClause) Source #
Update the target type, add more patterns to split clause if target becomes a function type. Returns the domains of the function type (if any).
A Covering
is the result of splitting a SplitClause
.
Covering | |
|
splitClauses :: Covering -> [SplitClause] Source #
Project the split clauses out of a covering.
coverageCheck :: QName -> Type -> [Clause] -> TCM SplitTree Source #
Top-level function for checking pattern coverage.
Effects:
- Marks unreachable clauses as such in the signature.
- Adds missing instances clauses to the signature.
isCovered :: QName -> [Clause] -> SplitClause -> TCM Bool Source #
Top-level function for eliminating redundant clauses in the interactive case splitter
splitClauseWithAbsurd :: SplitClause -> Nat -> TCM (Either SplitError (Either SplitClause Covering)) Source #
Entry point from Interaction.MakeCase
.
splitLast :: Induction -> Telescope -> [NamedArg DeBruijnPattern] -> TCM (Either SplitError Covering) Source #
Entry point from TypeChecking.Empty
and Interaction.BasicOps
.
splitLast CoInductive
is used in the refine
tactics.
splitResult :: QName -> SplitClause -> TCM (Maybe Covering) Source #
splitResult f sc = return res
If the target type of sc
is a record type, a covering set of
split clauses is returned (sc
extended by all valid projection patterns),
otherwise res == Nothing
.
Note that the empty set of split clauses is returned if the record has no fields.
normaliseProjP :: (NormaliseProjP a, HasConstInfo m) => a -> m a Source #