| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Agda.TypeChecking.CompiledClause
Description
Case trees.
After coverage checking, pattern matching is translated to case trees, i.e., a tree of successive case splits on one variable at a time.
- data WithArity c = WithArity {}
- data Case c = Branches {
- projPatterns :: Bool
- conBranches :: Map QName (WithArity c)
- litBranches :: Map Literal c
- catchAllBranch :: Maybe c
- data CompiledClauses' a
- type CompiledClauses = CompiledClauses' Term
- litCase :: Literal -> c -> Case c
- conCase :: QName -> WithArity c -> Case c
- projCase :: QName -> c -> Case c
- catchAll :: c -> Case c
- hasCatchAll :: CompiledClauses -> Bool
- prettyMap :: (Pretty k, Pretty v) => Map k v -> [Doc]
Documentation
Instances
| Functor WithArity Source # | |
| Foldable WithArity Source # | |
| Traversable WithArity Source # | |
| Data c => Data (WithArity c) Source # | |
| Show c => Show (WithArity c) Source # | |
| Semigroup c => Semigroup (WithArity c) Source # | |
| (Semigroup c, Monoid c) => Monoid (WithArity c) Source # | |
| Pretty a => Pretty (WithArity a) Source # | |
| KillRange c => KillRange (WithArity c) Source # | |
| TermLike a => TermLike (WithArity a) Source # | |
| NamesIn a => NamesIn (WithArity a) Source # | |
| InstantiateFull a => InstantiateFull (WithArity a) Source # | |
Branches in a case tree.
Constructors
| Branches | |
Fields
| |
Instances
| Functor Case Source # | |
| Foldable Case Source # | |
| Traversable Case Source # | |
| Data c => Data (Case c) Source # | |
| Show c => Show (Case c) Source # | |
| Semigroup m => Semigroup (Case m) Source # | |
| (Semigroup m, Monoid m) => Monoid (Case m) Source # | |
| Null (Case m) Source # | |
| Pretty a => Pretty (Case a) Source # | |
| KillRange c => KillRange (Case c) Source # | |
| TermLike a => TermLike (Case a) Source # | |
| NamesIn a => NamesIn (Case a) Source # | |
| InstantiateFull a => InstantiateFull (Case a) Source # | |
data CompiledClauses' a Source #
Case tree with bodies.
Constructors
| Case (Arg Int) (Case (CompiledClauses' a)) |
|
| Done [Arg ArgName] a |
|
| Fail | Absurd case. |
Instances
| Functor CompiledClauses' Source # | |
| Foldable CompiledClauses' Source # | |
| Traversable CompiledClauses' Source # | |
| Pretty CompiledClauses Source # | |
| KillRange CompiledClauses Source # | |
| NamesIn CompiledClauses Source # | |
| InstantiateFull CompiledClauses Source # | |
| DropArgs CompiledClauses Source # | To drop the first |
| Data a => Data (CompiledClauses' a) Source # | |
| Show a => Show (CompiledClauses' a) Source # | |
| TermLike a => TermLike (CompiledClauses' a) Source # | |
type CompiledClauses = CompiledClauses' Term Source #
hasCatchAll :: CompiledClauses -> Bool Source #
Check whether a case tree has a catch-all clause.