| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Agda.TypeChecking.Rewriting.NonLinPattern
Contents
Description
Various utility functions dealing with the non-linear, higher-order patterns used for rewrite rules.
Synopsis
- class PatternFrom t a b where- patternFrom :: Relevance -> Int -> t -> a -> TCM b
 
- class NLPatToTerm p a where- nlPatToTerm :: PureTCM m => p -> m a
 
- class NLPatVars a where- nlPatVarsUnder :: Int -> a -> IntSet
- nlPatVars :: a -> IntSet
 
- class GetMatchables a where- getMatchables :: a -> [QName]
 
Documentation
class PatternFrom t a b where Source #
Turn a term into a non-linear pattern, treating the free variables as pattern variables. The first argument indicates the relevance we are working under: if this is Irrelevant, then we construct a pattern that never fails to match. The second argument is the number of bound variables (from pattern lambdas). The third argument is the type of the term.
Instances
| PatternFrom Type Term NLPat Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom () Level NLPat Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom () Sort NLPSort Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom () Type NLPType Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom t a b => PatternFrom t (Dom a) (Dom b) Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom t a b => PatternFrom (Dom t) (Arg a) (Arg b) Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| PatternFrom (Type, Term) Elims [Elim' NLPat] Source # | |
class NLPatToTerm p a where Source #
Convert from a non-linear pattern to a term.
Minimal complete definition
Nothing
Methods
nlPatToTerm :: PureTCM m => p -> m a Source #
default nlPatToTerm :: (NLPatToTerm p' a', Traversable f, p ~ f p', a ~ f a', PureTCM m) => p -> m a Source #
Instances
class NLPatVars a where Source #
Gather the set of pattern variables of a non-linear pattern
Minimal complete definition
Instances
| NLPatVars NLPSort Source # | |
| NLPatVars NLPType Source # | |
| NLPatVars NLPat Source # | |
| NLPatVars a => NLPatVars (Abs a) Source # | |
| (Foldable f, NLPatVars a) => NLPatVars (f a) Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
| (NLPatVars a, NLPatVars b) => NLPatVars (a, b) Source # | |
| Defined in Agda.TypeChecking.Rewriting.NonLinPattern | |
class GetMatchables a where Source #
Get all symbols that a non-linear pattern matches against
Minimal complete definition
Nothing
Methods
getMatchables :: a -> [QName] Source #
default getMatchables :: (Foldable f, GetMatchables a', a ~ f a') => a -> [QName] Source #