pandora-0.1.5: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Applicative

Synopsis

Documentation

class Covariant t => Applicative t where Source #

When providing a new instance, you should ensure it satisfies the three laws:
* Composition: (.) <$> u <*> v <*> w ≡ u <*> (v <*> w)
* Left interchange: x <*> (f <$> y) ≡ (. f) <$> x <*> y
* Right interchange: f <$> (x <*> y) ≡ (f .) <$> x <*> y

Minimal complete definition

(<*>)

Methods

(<*>) :: t (a -> b) -> t a -> t b infixl 4 Source #

Infix version of apply

apply :: t (a -> b) -> t a -> t b Source #

Prefix version of <*>

(*>) :: t a -> t b -> t b infixl 4 Source #

Sequence actions, discarding the value of the first argument

(<*) :: t a -> t b -> t a infixl 4 Source #

Sequence actions, discarding the value of the second argument

forever :: t a -> t b Source #

Repeat an action indefinitely

Instances
Applicative Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Maybe

Methods

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b Source #

apply :: Maybe (a -> b) -> Maybe a -> Maybe b Source #

(*>) :: Maybe a -> Maybe b -> Maybe b Source #

(<*) :: Maybe a -> Maybe b -> Maybe a Source #

forever :: Maybe a -> Maybe b Source #

Applicative Identity Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Identity

Methods

(<*>) :: Identity (a -> b) -> Identity a -> Identity b Source #

apply :: Identity (a -> b) -> Identity a -> Identity b Source #

(*>) :: Identity a -> Identity b -> Identity b Source #

(<*) :: Identity a -> Identity b -> Identity a Source #

forever :: Identity a -> Identity b Source #

Applicative t => Applicative (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Yoneda

Methods

(<*>) :: Yoneda t (a -> b) -> Yoneda t a -> Yoneda t b Source #

apply :: Yoneda t (a -> b) -> Yoneda t a -> Yoneda t b Source #

(*>) :: Yoneda t a -> Yoneda t b -> Yoneda t b Source #

(<*) :: Yoneda t a -> Yoneda t b -> Yoneda t a Source #

forever :: Yoneda t a -> Yoneda t b Source #

Applicative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Proxy

Methods

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b Source #

apply :: Proxy (a -> b) -> Proxy a -> Proxy b Source #

(*>) :: Proxy a -> Proxy b -> Proxy b Source #

(<*) :: Proxy a -> Proxy b -> Proxy a Source #

forever :: Proxy a -> Proxy b Source #

Covariant t => Applicative (Free t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Free

Methods

(<*>) :: Free t (a -> b) -> Free t a -> Free t b Source #

apply :: Free t (a -> b) -> Free t a -> Free t b Source #

(*>) :: Free t a -> Free t b -> Free t b Source #

(<*) :: Free t a -> Free t b -> Free t a Source #

forever :: Free t a -> Free t b Source #

Semigroup e => Applicative (Validation e) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Validation

Methods

(<*>) :: Validation e (a -> b) -> Validation e a -> Validation e b Source #

apply :: Validation e (a -> b) -> Validation e a -> Validation e b Source #

(*>) :: Validation e a -> Validation e b -> Validation e b Source #

(<*) :: Validation e a -> Validation e b -> Validation e a Source #

forever :: Validation e a -> Validation e b Source #

Applicative t => Applicative (Twister t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Twister

Methods

(<*>) :: Twister t (a -> b) -> Twister t a -> Twister t b Source #

apply :: Twister t (a -> b) -> Twister t a -> Twister t b Source #

(*>) :: Twister t a -> Twister t b -> Twister t b Source #

(<*) :: Twister t a -> Twister t b -> Twister t a Source #

forever :: Twister t a -> Twister t b Source #

Applicative t => Applicative (Jack t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Jack

Methods

(<*>) :: Jack t (a -> b) -> Jack t a -> Jack t b Source #

apply :: Jack t (a -> b) -> Jack t a -> Jack t b Source #

(*>) :: Jack t a -> Jack t b -> Jack t b Source #

(<*) :: Jack t a -> Jack t b -> Jack t a Source #

forever :: Jack t a -> Jack t b Source #

Applicative (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Conclusion

Methods

(<*>) :: Conclusion e (a -> b) -> Conclusion e a -> Conclusion e b Source #

apply :: Conclusion e (a -> b) -> Conclusion e a -> Conclusion e b Source #

(*>) :: Conclusion e a -> Conclusion e b -> Conclusion e b Source #

(<*) :: Conclusion e a -> Conclusion e b -> Conclusion e a Source #

forever :: Conclusion e a -> Conclusion e b Source #

Applicative (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Tagged

Methods

(<*>) :: Tagged tag (a -> b) -> Tagged tag a -> Tagged tag b Source #

apply :: Tagged tag (a -> b) -> Tagged tag a -> Tagged tag b Source #

(*>) :: Tagged tag a -> Tagged tag b -> Tagged tag b Source #

(<*) :: Tagged tag a -> Tagged tag b -> Tagged tag a Source #

forever :: Tagged tag a -> Tagged tag b Source #

Applicative t => Applicative (Storage p t) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Storage

Methods

(<*>) :: Storage p t (a -> b) -> Storage p t a -> Storage p t b Source #

apply :: Storage p t (a -> b) -> Storage p t a -> Storage p t b Source #

(*>) :: Storage p t a -> Storage p t b -> Storage p t b Source #

(<*) :: Storage p t a -> Storage p t b -> Storage p t a Source #

forever :: Storage p t a -> Storage p t b Source #

Bindable t => Applicative (Stateful s t) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

(<*>) :: Stateful s t (a -> b) -> Stateful s t a -> Stateful s t b Source #

apply :: Stateful s t (a -> b) -> Stateful s t a -> Stateful s t b Source #

(*>) :: Stateful s t a -> Stateful s t b -> Stateful s t b Source #

(<*) :: Stateful s t a -> Stateful s t b -> Stateful s t a Source #

forever :: Stateful s t a -> Stateful s t b Source #

Covariant t => Applicative (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Continuation

Methods

(<*>) :: Continuation r t (a -> b) -> Continuation r t a -> Continuation r t b Source #

apply :: Continuation r t (a -> b) -> Continuation r t a -> Continuation r t b Source #

(*>) :: Continuation r t a -> Continuation r t b -> Continuation r t b Source #

(<*) :: Continuation r t a -> Continuation r t b -> Continuation r t a Source #

forever :: Continuation r t a -> Continuation r t b Source #

Applicative t => Applicative (Environmental e t) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environmental

Methods

(<*>) :: Environmental e t (a -> b) -> Environmental e t a -> Environmental e t b Source #

apply :: Environmental e t (a -> b) -> Environmental e t a -> Environmental e t b Source #

(*>) :: Environmental e t a -> Environmental e t b -> Environmental e t b Source #

(<*) :: Environmental e t a -> Environmental e t b -> Environmental e t a Source #

forever :: Environmental e t a -> Environmental e t b Source #

(Applicative (t u), Applicative u) => Applicative (Y t u) Source # 
Instance details

Defined in Pandora.Paradigm.Junction.Transformer

Methods

(<*>) :: Y t u (a -> b) -> Y t u a -> Y t u b Source #

apply :: Y t u (a -> b) -> Y t u a -> Y t u b Source #

(*>) :: Y t u a -> Y t u b -> Y t u b Source #

(<*) :: Y t u a -> Y t u b -> Y t u a Source #

forever :: Y t u a -> Y t u b Source #

(Applicative t, Applicative u) => Applicative (T t u) Source # 
Instance details

Defined in Pandora.Paradigm.Junction.Transformer

Methods

(<*>) :: T t u (a -> b) -> T t u a -> T t u b Source #

apply :: T t u (a -> b) -> T t u a -> T t u b Source #

(*>) :: T t u a -> T t u b -> T t u b Source #

(<*) :: T t u a -> T t u b -> T t u a Source #

forever :: T t u a -> T t u b Source #

(Applicative t, Applicative u) => Applicative (U Co Co t u) Source # 
Instance details

Defined in Pandora.Paradigm.Junction.Composition

Methods

(<*>) :: U Co Co t u (a -> b) -> U Co Co t u a -> U Co Co t u b Source #

apply :: U Co Co t u (a -> b) -> U Co Co t u a -> U Co Co t u b Source #

(*>) :: U Co Co t u a -> U Co Co t u b -> U Co Co t u b Source #

(<*) :: U Co Co t u a -> U Co Co t u b -> U Co Co t u a Source #

forever :: U Co Co t u a -> U Co Co t u b Source #

(Applicative t, Applicative u, Applicative v) => Applicative (UU Co Co Co t u v) Source # 
Instance details

Defined in Pandora.Paradigm.Junction.Composition

Methods

(<*>) :: UU Co Co Co t u v (a -> b) -> UU Co Co Co t u v a -> UU Co Co Co t u v b Source #

apply :: UU Co Co Co t u v (a -> b) -> UU Co Co Co t u v a -> UU Co Co Co t u v b Source #

(*>) :: UU Co Co Co t u v a -> UU Co Co Co t u v b -> UU Co Co Co t u v b Source #

(<*) :: UU Co Co Co t u v a -> UU Co Co Co t u v b -> UU Co Co Co t u v a Source #

forever :: UU Co Co Co t u v a -> UU Co Co Co t u v b Source #

(Applicative t, Applicative u, Applicative v, Applicative w) => Applicative (UUU Co Co Co Co t u v w) Source # 
Instance details

Defined in Pandora.Paradigm.Junction.Composition

Methods

(<*>) :: UUU Co Co Co Co t u v w (a -> b) -> UUU Co Co Co Co t u v w a -> UUU Co Co Co Co t u v w b Source #

apply :: UUU Co Co Co Co t u v w (a -> b) -> UUU Co Co Co Co t u v w a -> UUU Co Co Co Co t u v w b Source #

(*>) :: UUU Co Co Co Co t u v w a -> UUU Co Co Co Co t u v w b -> UUU Co Co Co Co t u v w b Source #

(<*) :: UUU Co Co Co Co t u v w a -> UUU Co Co Co Co t u v w b -> UUU Co Co Co Co t u v w a Source #

forever :: UUU Co Co Co Co t u v w a -> UUU Co Co Co Co t u v w b Source #