| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Symantic.Lib.Alternative
Description
Symantic for Alternative.
Synopsis
- class Sym_Functor term => Sym_Alternative term where
- tyAlternative :: Source src => Type src vs a -> Type src vs (Alternative a)
- teAlternative_empty :: TermDef Alternative '[Proxy a, Proxy f] (Alternative f #> f a)
- teAlternative_alt :: TermDef Alternative '[Proxy a, Proxy f] (Alternative f #> (f a -> f a -> f a))
Class Sym_Alternative
class Sym_Functor term => Sym_Alternative term where Source #
Methods
empty :: Alternative f => term (f a) Source #
(<|>) :: Alternative f => term (f a) -> term (f a) -> term (f a) infixl 3 Source #
empty :: Sym_Alternative (UnT term) => Trans term => Alternative f => term (f a) Source #
(<|>) :: Sym_Alternative (UnT term) => Trans term => Alternative f => term (f a) -> term (f a) -> term (f a) infixl 3 Source #
Instances
| Sym_Alternative View Source # | |
| Defined in Language.Symantic.Lib.Alternative | |
| Sym_Alternative Eval Source # | |
| Defined in Language.Symantic.Lib.Alternative | |
| (Sym_Lambda term, Sym_Alternative term) => Sym_Alternative (BetaT term) Source # | |
| Defined in Language.Symantic.Lib.Alternative | |
| (Sym_Alternative r1, Sym_Alternative r2) => Sym_Alternative (Dup r1 r2) Source # | |
| Defined in Language.Symantic.Lib.Alternative | |
Types
tyAlternative :: Source src => Type src vs a -> Type src vs (Alternative a) Source #
Terms
teAlternative_empty :: TermDef Alternative '[Proxy a, Proxy f] (Alternative f #> f a) Source #
teAlternative_alt :: TermDef Alternative '[Proxy a, Proxy f] (Alternative f #> (f a -> f a -> f a)) Source #
Orphan instances
| ClassInstancesFor Alternative Source # | |
| Methods proveConstraintFor :: Source src => proxy Alternative -> Type src vs q -> Maybe (Qual q) # | |
| TypeInstancesFor Alternative Source # | |
| Methods expandFamFor :: Source src => proxy Alternative -> Len vs -> Const src fam -> Types src vs ts -> Maybe (Type src vs (Fam fam ts)) # | |
| NameTyOf Alternative Source # | |
| FixityOf Alternative Source # | |
| Methods fixityOf :: proxy Alternative -> Maybe Fixity # | |
| (Source src, SymInj ss Alternative) => ModuleFor src ss Alternative Source # | |
| Gram_Term_AtomsFor src ss g Alternative Source # | |
| Methods g_term_atomsFor :: [CF g (AST_Term src ss)] # | |