pandora-0.2.8: 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:
* Interpreted: (.) <$> 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

(<**>) :: Applicative u => ((t :. u) := (a -> b)) -> ((t :. u) := a) -> (t :. u) := b Source #

Infix versions of apply with various nesting levels

(<***>) :: (Applicative u, Applicative v) => ((t :. (u :. v)) := (a -> b)) -> ((t :. (u :. v)) := a) -> (t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((t :. (u :. (v :. w))) := (a -> b)) -> ((t :. (u :. (v :. w))) := a) -> (t :. (u :. (v :. w))) := b Source #

Instances
Applicative Delta Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Delta

Methods

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

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

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

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

forever :: Delta a -> Delta b Source #

(<**>) :: Applicative u => ((Delta :. u) := (a -> b)) -> ((Delta :. u) := a) -> (Delta :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Delta :. (u :. v)) := (a -> b)) -> ((Delta :. (u :. v)) := a) -> (Delta :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Delta :. (u :. (v :. w))) := (a -> b)) -> ((Delta :. (u :. (v :. w))) := a) -> (Delta :. (u :. (v :. w))) := b Source #

Applicative Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.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 u => ((Identity :. u) := (a -> b)) -> ((Identity :. u) := a) -> (Identity :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Identity :. (u :. v)) := (a -> b)) -> ((Identity :. (u :. v)) := a) -> (Identity :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Identity :. (u :. (v :. w))) := (a -> b)) -> ((Identity :. (u :. (v :. w))) := a) -> (Identity :. (u :. (v :. w))) := b Source #

Applicative Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.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 u => ((Maybe :. u) := (a -> b)) -> ((Maybe :. u) := a) -> (Maybe :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Maybe :. (u :. v)) := (a -> b)) -> ((Maybe :. (u :. v)) := a) -> (Maybe :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Maybe :. (u :. (v :. w))) := (a -> b)) -> ((Maybe :. (u :. (v :. w))) := a) -> (Maybe :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Functor.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 #

(<**>) :: Applicative u => ((Proxy :. u) := (a -> b)) -> ((Proxy :. u) := a) -> (Proxy :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Proxy :. (u :. v)) := (a -> b)) -> ((Proxy :. (u :. v)) := a) -> (Proxy :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Proxy :. (u :. (v :. w))) := (a -> b)) -> ((Proxy :. (u :. (v :. w))) := a) -> (Proxy :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Functor.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 u => ((Validation e :. u) := (a -> b)) -> ((Validation e :. u) := a) -> (Validation e :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Validation e :. (u :. v)) := (a -> b)) -> ((Validation e :. (u :. v)) := a) -> (Validation e :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Validation e :. (u :. (v :. w))) := (a -> b)) -> ((Validation e :. (u :. (v :. w))) := a) -> (Validation e :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.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 u => ((Yoneda t :. u) := (a -> b)) -> ((Yoneda t :. u) := a) -> (Yoneda t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Yoneda t :. (u :. v)) := (a -> b)) -> ((Yoneda t :. (u :. v)) := a) -> (Yoneda t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Yoneda t :. (u :. (v :. w))) := (a -> b)) -> ((Yoneda t :. (u :. (v :. w))) := a) -> (Yoneda t :. (u :. (v :. w))) := b Source #

Applicative (Outline f) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

(<*>) :: Outline f (a -> b) -> Outline f a -> Outline f b Source #

apply :: Outline f (a -> b) -> Outline f a -> Outline f b Source #

(*>) :: Outline f a -> Outline f b -> Outline f b Source #

(<*) :: Outline f a -> Outline f b -> Outline f a Source #

forever :: Outline f a -> Outline f b Source #

(<**>) :: Applicative u => ((Outline f :. u) := (a -> b)) -> ((Outline f :. u) := a) -> (Outline f :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Outline f :. (u :. v)) := (a -> b)) -> ((Outline f :. (u :. v)) := a) -> (Outline f :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Outline f :. (u :. (v :. w))) := (a -> b)) -> ((Outline f :. (u :. (v :. w))) := a) -> (Outline f :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.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 u => ((Jack t :. u) := (a -> b)) -> ((Jack t :. u) := a) -> (Jack t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Jack t :. (u :. v)) := (a -> b)) -> ((Jack t :. (u :. v)) := a) -> (Jack t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Jack t :. (u :. (v :. w))) := (a -> b)) -> ((Jack t :. (u :. (v :. w))) := a) -> (Jack t :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Instruction t :. u) := (a -> b)) -> ((Instruction t :. u) := a) -> (Instruction t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Instruction t :. (u :. v)) := (a -> b)) -> ((Instruction t :. (u :. v)) := a) -> (Instruction t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Instruction t :. (u :. (v :. w))) := (a -> b)) -> ((Instruction t :. (u :. (v :. w))) := a) -> (Instruction t :. (u :. (v :. w))) := b Source #

Applicative (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.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 u => ((Conclusion e :. u) := (a -> b)) -> ((Conclusion e :. u) := a) -> (Conclusion e :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Conclusion e :. (u :. v)) := (a -> b)) -> ((Conclusion e :. (u :. v)) := a) -> (Conclusion e :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Conclusion e :. (u :. (v :. w))) := (a -> b)) -> ((Conclusion e :. (u :. (v :. w))) := a) -> (Conclusion e :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Accumulator e :. u) := (a -> b)) -> ((Accumulator e :. u) := a) -> (Accumulator e :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Accumulator e :. (u :. v)) := (a -> b)) -> ((Accumulator e :. (u :. v)) := a) -> (Accumulator e :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Accumulator e :. (u :. (v :. w))) := (a -> b)) -> ((Accumulator e :. (u :. (v :. w))) := a) -> (Accumulator e :. (u :. (v :. w))) := b Source #

Applicative (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

apply :: State s (a -> b) -> State s a -> State s b Source #

(*>) :: State s a -> State s b -> State s b Source #

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

forever :: State s a -> State s b Source #

(<**>) :: Applicative u => ((State s :. u) := (a -> b)) -> ((State s :. u) := a) -> (State s :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((State s :. (u :. v)) := (a -> b)) -> ((State s :. (u :. v)) := a) -> (State s :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((State s :. (u :. (v :. w))) := (a -> b)) -> ((State s :. (u :. (v :. w))) := a) -> (State s :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Construction t :. u) := (a -> b)) -> ((Construction t :. u) := a) -> (Construction t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Construction t :. (u :. v)) := (a -> b)) -> ((Construction t :. (u :. v)) := a) -> (Construction t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Construction t :. (u :. (v :. w))) := (a -> b)) -> ((Construction t :. (u :. (v :. w))) := a) -> (Construction t :. (u :. (v :. w))) := b Source #

Applicative (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Environment e :. u) := (a -> b)) -> ((Environment e :. u) := a) -> (Environment e :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Environment e :. (u :. v)) := (a -> b)) -> ((Environment e :. (u :. v)) := a) -> (Environment e :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Environment e :. (u :. (v :. w))) := (a -> b)) -> ((Environment e :. (u :. (v :. w))) := a) -> (Environment e :. (u :. (v :. w))) := b Source #

Applicative (Schematic Monad t u) => Applicative (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Joint.Transformer.Monadic

Methods

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

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

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

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

forever :: (t :> u) a -> (t :> u) b Source #

(<**>) :: Applicative u0 => (((t :> u) :. u0) := (a -> b)) -> (((t :> u) :. u0) := a) -> ((t :> u) :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => (((t :> u) :. (u0 :. v)) := (a -> b)) -> (((t :> u) :. (u0 :. v)) := a) -> ((t :> u) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => (((t :> u) :. (u0 :. (v :. w))) := (a -> b)) -> (((t :> u) :. (u0 :. (v :. w))) := a) -> ((t :> u) :. (u0 :. (v :. w))) := b Source #

Applicative (Schematic Comonad t u) => Applicative (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Joint.Transformer.Comonadic

Methods

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

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

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

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

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

(<**>) :: Applicative u0 => (((t :< u) :. u0) := (a -> b)) -> (((t :< u) :. u0) := a) -> ((t :< u) :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => (((t :< u) :. (u0 :. v)) := (a -> b)) -> (((t :< u) :. (u0 :. v)) := a) -> ((t :< u) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => (((t :< u) :. (u0 :. (v :. w))) := (a -> b)) -> (((t :< u) :. (u0 :. (v :. w))) := a) -> ((t :< u) :. (u0 :. (v :. w))) := b Source #

Applicative (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.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 u => ((Tagged tag :. u) := (a -> b)) -> ((Tagged tag :. u) := a) -> (Tagged tag :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tagged tag :. (u :. v)) := (a -> b)) -> ((Tagged tag :. (u :. v)) := a) -> (Tagged tag :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tagged tag :. (u :. (v :. w))) := (a -> b)) -> ((Tagged tag :. (u :. (v :. w))) := a) -> (Tagged tag :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Backwards t :. u) := (a -> b)) -> ((Backwards t :. u) := a) -> (Backwards t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Backwards t :. (u :. v)) := (a -> b)) -> ((Backwards t :. (u :. v)) := a) -> (Backwards t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Backwards t :. (u :. (v :. w))) := (a -> b)) -> ((Backwards t :. (u :. (v :. w))) := a) -> (Backwards t :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

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

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

(<**>) :: Applicative u => ((Reverse t :. u) := (a -> b)) -> ((Reverse t :. u) := a) -> (Reverse t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Reverse t :. (u :. v)) := (a -> b)) -> ((Reverse t :. (u :. v)) := a) -> (Reverse t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Reverse t :. (u :. (v :. w))) := (a -> b)) -> ((Reverse t :. (u :. (v :. w))) := a) -> (Reverse t :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Pattern.Functor.Applicative

Methods

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

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

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

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

forever :: (e -> a) -> e -> b Source #

(<**>) :: Applicative u => (((->) e :. u) := (a -> b)) -> (((->) e :. u) := a) -> ((->) e :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => (((->) e :. (u :. v)) := (a -> b)) -> (((->) e :. (u :. v)) := a) -> ((->) e :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => (((->) e :. (u :. (v :. w))) := (a -> b)) -> (((->) e :. (u :. (v :. w))) := a) -> ((->) e :. (u :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.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 u => ((Continuation r t :. u) := (a -> b)) -> ((Continuation r t :. u) := a) -> (Continuation r t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Continuation r t :. (u :. v)) := (a -> b)) -> ((Continuation r t :. (u :. v)) := a) -> (Continuation r t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Continuation r t :. (u :. (v :. w))) := (a -> b)) -> ((Continuation r t :. (u :. (v :. w))) := a) -> (Continuation r t :. (u :. (v :. w))) := b Source #

Applicative u => Applicative (UT Covariant Covariant ((->) e :: Type -> Type) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(<*>) :: UT Covariant Covariant ((->) e) u (a -> b) -> UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b Source #

apply :: UT Covariant Covariant ((->) e) u (a -> b) -> UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b Source #

(*>) :: UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b -> UT Covariant Covariant ((->) e) u b Source #

(<*) :: UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b -> UT Covariant Covariant ((->) e) u a Source #

forever :: UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b Source #

(<**>) :: Applicative u0 => ((UT Covariant Covariant ((->) e) u :. u0) := (a -> b)) -> ((UT Covariant Covariant ((->) e) u :. u0) := a) -> (UT Covariant Covariant ((->) e) u :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((UT Covariant Covariant ((->) e) u :. (u0 :. v)) := (a -> b)) -> ((UT Covariant Covariant ((->) e) u :. (u0 :. v)) := a) -> (UT Covariant Covariant ((->) e) u :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((UT Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := (a -> b)) -> ((UT Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := a) -> (UT Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := b Source #

(Semigroup e, Applicative u) => Applicative (UT Covariant Covariant ((:*:) e) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

(<*>) :: UT Covariant Covariant ((:*:) e) u (a -> b) -> UT Covariant Covariant ((:*:) e) u a -> UT Covariant Covariant ((:*:) e) u b Source #

apply :: UT Covariant Covariant ((:*:) e) u (a -> b) -> UT Covariant Covariant ((:*:) e) u a -> UT Covariant Covariant ((:*:) e) u b Source #

(*>) :: UT Covariant Covariant ((:*:) e) u a -> UT Covariant Covariant ((:*:) e) u b -> UT Covariant Covariant ((:*:) e) u b Source #

(<*) :: UT Covariant Covariant ((:*:) e) u a -> UT Covariant Covariant ((:*:) e) u b -> UT Covariant Covariant ((:*:) e) u a Source #

forever :: UT Covariant Covariant ((:*:) e) u a -> UT Covariant Covariant ((:*:) e) u b Source #

(<**>) :: Applicative u0 => ((UT Covariant Covariant ((:*:) e) u :. u0) := (a -> b)) -> ((UT Covariant Covariant ((:*:) e) u :. u0) := a) -> (UT Covariant Covariant ((:*:) e) u :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((UT Covariant Covariant ((:*:) e) u :. (u0 :. v)) := (a -> b)) -> ((UT Covariant Covariant ((:*:) e) u :. (u0 :. v)) := a) -> (UT Covariant Covariant ((:*:) e) u :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((UT Covariant Covariant ((:*:) e) u :. (u0 :. (v :. w))) := (a -> b)) -> ((UT Covariant Covariant ((:*:) e) u :. (u0 :. (v :. w))) := a) -> (UT Covariant Covariant ((:*:) e) u :. (u0 :. (v :. w))) := b Source #

Applicative u => Applicative (UT Covariant Covariant Maybe u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Applicative u => Applicative (UT Covariant Covariant (Conclusion e) u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Applicative u => Applicative (TU Covariant Covariant ((->) e :: Type -> Type) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

(<*>) :: TU Covariant Covariant ((->) e) u (a -> b) -> TU Covariant Covariant ((->) e) u a -> TU Covariant Covariant ((->) e) u b Source #

apply :: TU Covariant Covariant ((->) e) u (a -> b) -> TU Covariant Covariant ((->) e) u a -> TU Covariant Covariant ((->) e) u b Source #

(*>) :: TU Covariant Covariant ((->) e) u a -> TU Covariant Covariant ((->) e) u b -> TU Covariant Covariant ((->) e) u b Source #

(<*) :: TU Covariant Covariant ((->) e) u a -> TU Covariant Covariant ((->) e) u b -> TU Covariant Covariant ((->) e) u a Source #

forever :: TU Covariant Covariant ((->) e) u a -> TU Covariant Covariant ((->) e) u b Source #

(<**>) :: Applicative u0 => ((TU Covariant Covariant ((->) e) u :. u0) := (a -> b)) -> ((TU Covariant Covariant ((->) e) u :. u0) := a) -> (TU Covariant Covariant ((->) e) u :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((TU Covariant Covariant ((->) e) u :. (u0 :. v)) := (a -> b)) -> ((TU Covariant Covariant ((->) e) u :. (u0 :. v)) := a) -> (TU Covariant Covariant ((->) e) u :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((TU Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := (a -> b)) -> ((TU Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := a) -> (TU Covariant Covariant ((->) e) u :. (u0 :. (v :. w))) := b Source #

(Applicative t, Applicative u) => Applicative (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(<*>) :: TU Covariant Covariant u (Construction t) (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

apply :: TU Covariant Covariant u (Construction t) (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

(*>) :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b -> TU Covariant Covariant u (Construction t) b Source #

(<*) :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b -> TU Covariant Covariant u (Construction t) a Source #

forever :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

(<**>) :: Applicative u0 => ((TU Covariant Covariant u (Construction t) :. u0) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. u0) := a) -> (TU Covariant Covariant u (Construction t) :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((TU Covariant Covariant u (Construction t) :. (u0 :. v)) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. (u0 :. v)) := a) -> (TU Covariant Covariant u (Construction t) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := a) -> (TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := b Source #

Bindable u => Applicative (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

(<*>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

apply :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(*>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<*) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a Source #

forever :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<**>) :: Applicative u0 => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := b Source #