| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Agda.TypeChecking.Coverage
Description
Coverage checking, case splitting, and splitting for refine tactics.
Synopsis
- data SplitClause = SClause {}
 - clauseToSplitClause :: Clause -> SplitClause
 - insertTrailingArgs :: SplitClause -> TCM (Telescope, SplitClause)
 - data Covering = Covering {
- covSplitArg :: Arg Nat
 - covSplitClauses :: [(SplitTag, 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 (Either SplitError [SplitClause])
 - normaliseProjP :: (NormaliseProjP a, HasConstInfo m) => a -> m a
 
Documentation
data SplitClause Source #
Constructors
| SClause | |
Fields 
  | |
Instances
| PrettyTCM SplitClause Source # | For debugging only.  | 
Defined in Agda.TypeChecking.Coverage Methods prettyTCM :: MonadPretty m => SplitClause -> m Doc Source #  | |
clauseToSplitClause :: Clause -> SplitClause Source #
Create a split clause from a clause in internal syntax. Used by make-case.
insertTrailingArgs :: SplitClause -> TCM (Telescope, SplitClause) Source #
Add more patterns to split clause if the target type is a function type. Returns the domains of the function type (if any).
A Covering is the result of splitting a SplitClause.
Constructors
| Covering | |
Fields 
  | |
splitClauses :: Covering -> [SplitClause] Source #
Project the split clauses out of a covering.
Arguments
| :: QName | Name   | 
| -> Type | Absolute type (including the full parameter telescope).  | 
| -> [Clause] | Clauses of   | 
| -> TCM SplitTree | 
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 (Either SplitError [SplitClause]) Source #
splitResult for MakeCase, tries to introduce IApply or ProjP copatterns
normaliseProjP :: (NormaliseProjP a, HasConstInfo m) => a -> m a Source #