| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Symantic.Lib.Applicative
Description
Symantic for Applicative.
Synopsis
- class Sym_Functor term => Sym_Applicative term where
- tyApplicative :: Source src => Type src vs a -> Type src vs (Applicative a)
- teApplicative_pure :: TermDef Applicative '[Proxy a, Proxy f] (Applicative f #> (a -> f a))
- teApplicative_app :: TermDef Applicative '[Proxy a, Proxy b, Proxy f] (Applicative f #> (f (a -> b) -> f a -> f b))
- teApplicative_const :: TermDef Applicative '[Proxy a, Proxy b1, Proxy f] (Applicative f #> (f a -> f b1 -> f a))
- teApplicative_tsnoc :: TermDef Applicative '[Proxy a, Proxy b, Proxy f] (Applicative f #> (f a -> f b -> f b))
Class Sym_Applicative
class Sym_Functor term => Sym_Applicative term where Source #
Methods
pure :: Applicative f => term a -> term (f a) Source #
(<*>) :: Applicative f => term (f (a -> b)) -> term (f a) -> term (f b) infixl 4 Source #
(*>) :: Applicative f => term (f a) -> term (f b) -> term (f b) infixl 4 Source #
(<*) :: Applicative f => term (f a) -> term (f b) -> term (f a) infixl 4 Source #
pure :: Sym_Applicative (UnT term) => Trans term => Applicative f => term a -> term (f a) Source #
(<*>) :: Sym_Applicative (UnT term) => Trans term => Applicative f => term (f (a -> b)) -> term (f a) -> term (f b) infixl 4 Source #
(*>) :: Sym_Lambda term => Applicative f => term (f a) -> term (f b) -> term (f b) infixl 4 Source #
(<*) :: Sym_Lambda term => Applicative f => term (f a) -> term (f b) -> term (f a) infixl 4 Source #
Instances
Types
tyApplicative :: Source src => Type src vs a -> Type src vs (Applicative a) Source #
Terms
teApplicative_pure :: TermDef Applicative '[Proxy a, Proxy f] (Applicative f #> (a -> f a)) Source #
teApplicative_app :: TermDef Applicative '[Proxy a, Proxy b, Proxy f] (Applicative f #> (f (a -> b) -> f a -> f b)) Source #
teApplicative_const :: TermDef Applicative '[Proxy a, Proxy b1, Proxy f] (Applicative f #> (f a -> f b1 -> f a)) Source #
teApplicative_tsnoc :: TermDef Applicative '[Proxy a, Proxy b, Proxy f] (Applicative f #> (f a -> f b -> f b)) Source #
Orphan instances
| ClassInstancesFor Applicative Source # | |
Methods proveConstraintFor :: Source src => proxy Applicative -> Type src vs q -> Maybe (Qual q) # | |
| TypeInstancesFor Applicative Source # | |
Methods expandFamFor :: Source src => proxy Applicative -> Len vs -> Const src fam -> Types src vs ts -> Maybe (Type src vs (Fam fam ts)) # | |
| NameTyOf Applicative Source # | |
| FixityOf Applicative Source # | |
Methods fixityOf :: proxy Applicative -> Maybe Fixity # | |
| (Source src, SymInj ss Applicative) => ModuleFor src ss Applicative Source # | |
| Gram_Term_AtomsFor src ss g Applicative Source # | |
Methods g_term_atomsFor :: [CF g (AST_Term src ss)] # | |