Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Covariant t => Bindable t where
- (>>=) :: t a -> (a -> t b) -> t b
- (=<<) :: (a -> t b) -> t a -> t b
- bind :: (a -> t b) -> t a -> t b
- join :: ((t :. t) := a) -> t a
- (>=>) :: (a -> t b) -> (b -> t c) -> a -> t c
- (<=<) :: (b -> t c) -> (a -> t b) -> a -> t c
- ($>>=) :: Covariant u => ((u :. t) := a) -> (a -> t b) -> (u :. t) := b
- (<>>=) :: (t b -> c) -> (a -> t b) -> t a -> c
Documentation
class Covariant t => Bindable t where Source #
When providing a new instance, you should ensure it satisfies the one law: * Interchange: t >>= f = join (f <$> t)
(>>=) :: t a -> (a -> t b) -> t b infixl 1 Source #
Infix and flipped version of bind
, the dual of =>>
(=<<) :: (a -> t b) -> t a -> t b infixr 1 Source #
Flipped version of >>=
, the dual of <<=
bind :: (a -> t b) -> t a -> t b Source #
Prefix and flipped version of >>=
, the dual of extend
join :: ((t :. t) := a) -> t a Source #
Merge effects/contexts, the dual of duplicate
(>=>) :: (a -> t b) -> (b -> t c) -> a -> t c infixr 1 Source #
Left-to-right Kleisli composition
(<=<) :: (b -> t c) -> (a -> t b) -> a -> t c infixr 1 Source #
Right-to-left Kleisli composition
($>>=) :: Covariant u => ((u :. t) := a) -> (a -> t b) -> (u :. t) := b Source #
Instances
Bindable Identity Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Identity (>>=) :: Identity a -> (a -> Identity b) -> Identity b Source # (=<<) :: (a -> Identity b) -> Identity a -> Identity b Source # bind :: (a -> Identity b) -> Identity a -> Identity b Source # join :: ((Identity :. Identity) := a) -> Identity a Source # (>=>) :: (a -> Identity b) -> (b -> Identity c) -> a -> Identity c Source # (<=<) :: (b -> Identity c) -> (a -> Identity b) -> a -> Identity c Source # ($>>=) :: Covariant u => ((u :. Identity) := a) -> (a -> Identity b) -> (u :. Identity) := b Source # (<>>=) :: (Identity b -> c) -> (a -> Identity b) -> Identity a -> c Source # | |
Bindable Maybe Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Maybe (>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b Source # (=<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # bind :: (a -> Maybe b) -> Maybe a -> Maybe b Source # join :: ((Maybe :. Maybe) := a) -> Maybe a Source # (>=>) :: (a -> Maybe b) -> (b -> Maybe c) -> a -> Maybe c Source # (<=<) :: (b -> Maybe c) -> (a -> Maybe b) -> a -> Maybe c Source # ($>>=) :: Covariant u => ((u :. Maybe) := a) -> (a -> Maybe b) -> (u :. Maybe) := b Source # (<>>=) :: (Maybe b -> c) -> (a -> Maybe b) -> Maybe a -> c Source # | |
Bindable (Proxy :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Proxy (>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source # (=<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # bind :: (a -> Proxy b) -> Proxy a -> Proxy b Source # join :: ((Proxy :. Proxy) := a) -> Proxy a Source # (>=>) :: (a -> Proxy b) -> (b -> Proxy c) -> a -> Proxy c Source # (<=<) :: (b -> Proxy c) -> (a -> Proxy b) -> a -> Proxy c Source # ($>>=) :: Covariant u => ((u :. Proxy) := a) -> (a -> Proxy b) -> (u :. Proxy) := b Source # (<>>=) :: (Proxy b -> c) -> (a -> Proxy b) -> Proxy a -> c Source # | |
(Pointable t, Bindable t) => Bindable (Jack t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Jack (>>=) :: Jack t a -> (a -> Jack t b) -> Jack t b Source # (=<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # bind :: (a -> Jack t b) -> Jack t a -> Jack t b Source # join :: ((Jack t :. Jack t) := a) -> Jack t a Source # (>=>) :: (a -> Jack t b) -> (b -> Jack t c) -> a -> Jack t c Source # (<=<) :: (b -> Jack t c) -> (a -> Jack t b) -> a -> Jack t c Source # ($>>=) :: Covariant u => ((u :. Jack t) := a) -> (a -> Jack t b) -> (u :. Jack t) := b Source # (<>>=) :: (Jack t b -> c) -> (a -> Jack t b) -> Jack t a -> c Source # | |
Covariant t => Bindable (Instruction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction (>>=) :: Instruction t a -> (a -> Instruction t b) -> Instruction t b Source # (=<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # bind :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # join :: ((Instruction t :. Instruction t) := a) -> Instruction t a Source # (>=>) :: (a -> Instruction t b) -> (b -> Instruction t c) -> a -> Instruction t c Source # (<=<) :: (b -> Instruction t c) -> (a -> Instruction t b) -> a -> Instruction t c Source # ($>>=) :: Covariant u => ((u :. Instruction t) := a) -> (a -> Instruction t b) -> (u :. Instruction t) := b Source # (<>>=) :: (Instruction t b -> c) -> (a -> Instruction t b) -> Instruction t a -> c Source # | |
(Extractable t, Alternative t, Bindable t) => Bindable (Tap t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Tap (>>=) :: Tap t a -> (a -> Tap t b) -> Tap t b Source # (=<<) :: (a -> Tap t b) -> Tap t a -> Tap t b Source # bind :: (a -> Tap t b) -> Tap t a -> Tap t b Source # join :: ((Tap t :. Tap t) := a) -> Tap t a Source # (>=>) :: (a -> Tap t b) -> (b -> Tap t c) -> a -> Tap t c Source # (<=<) :: (b -> Tap t c) -> (a -> Tap t b) -> a -> Tap t c Source # ($>>=) :: Covariant u => ((u :. Tap t) := a) -> (a -> Tap t b) -> (u :. Tap t) := b Source # (<>>=) :: (Tap t b -> c) -> (a -> Tap t b) -> Tap t a -> c Source # | |
Alternative t => Bindable (Construction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Construction (>>=) :: Construction t a -> (a -> Construction t b) -> Construction t b Source # (=<<) :: (a -> Construction t b) -> Construction t a -> Construction t b Source # bind :: (a -> Construction t b) -> Construction t a -> Construction t b Source # join :: ((Construction t :. Construction t) := a) -> Construction t a Source # (>=>) :: (a -> Construction t b) -> (b -> Construction t c) -> a -> Construction t c Source # (<=<) :: (b -> Construction t c) -> (a -> Construction t b) -> a -> Construction t c Source # ($>>=) :: Covariant u => ((u :. Construction t) := a) -> (a -> Construction t b) -> (u :. Construction t) := b Source # (<>>=) :: (Construction t b -> c) -> (a -> Construction t b) -> Construction t a -> c Source # | |
(forall a. Semigroup ((t <:.> Construction t) := a), Bindable t) => Bindable (Comprehension t) Source # | |
Defined in Pandora.Paradigm.Structure.Ability.Comprehension (>>=) :: Comprehension t a -> (a -> Comprehension t b) -> Comprehension t b Source # (=<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # bind :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # join :: ((Comprehension t :. Comprehension t) := a) -> Comprehension t a Source # (>=>) :: (a -> Comprehension t b) -> (b -> Comprehension t c) -> a -> Comprehension t c Source # (<=<) :: (b -> Comprehension t c) -> (a -> Comprehension t b) -> a -> Comprehension t c Source # ($>>=) :: Covariant u => ((u :. Comprehension t) := a) -> (a -> Comprehension t b) -> (u :. Comprehension t) := b Source # (<>>=) :: (Comprehension t b -> c) -> (a -> Comprehension t b) -> Comprehension t a -> c Source # | |
Bindable (Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion (>>=) :: Conclusion e a -> (a -> Conclusion e b) -> Conclusion e b Source # (=<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # bind :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # join :: ((Conclusion e :. Conclusion e) := a) -> Conclusion e a Source # (>=>) :: (a -> Conclusion e b) -> (b -> Conclusion e c) -> a -> Conclusion e c Source # (<=<) :: (b -> Conclusion e c) -> (a -> Conclusion e b) -> a -> Conclusion e c Source # ($>>=) :: Covariant u => ((u :. Conclusion e) := a) -> (a -> Conclusion e b) -> (u :. Conclusion e) := b Source # (<>>=) :: (Conclusion e b -> c) -> (a -> Conclusion e b) -> Conclusion e a -> c Source # | |
Bindable (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State (>>=) :: State s a -> (a -> State s b) -> State s b Source # (=<<) :: (a -> State s b) -> State s a -> State s b Source # bind :: (a -> State s b) -> State s a -> State s b Source # join :: ((State s :. State s) := a) -> State s a Source # (>=>) :: (a -> State s b) -> (b -> State s c) -> a -> State s c Source # (<=<) :: (b -> State s c) -> (a -> State s b) -> a -> State s c Source # ($>>=) :: Covariant u => ((u :. State s) := a) -> (a -> State s b) -> (u :. State s) := b Source # (<>>=) :: (State s b -> c) -> (a -> State s b) -> State s a -> c Source # | |
Bindable (Environment e) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment (>>=) :: Environment e a -> (a -> Environment e b) -> Environment e b Source # (=<<) :: (a -> Environment e b) -> Environment e a -> Environment e b Source # bind :: (a -> Environment e b) -> Environment e a -> Environment e b Source # join :: ((Environment e :. Environment e) := a) -> Environment e a Source # (>=>) :: (a -> Environment e b) -> (b -> Environment e c) -> a -> Environment e c Source # (<=<) :: (b -> Environment e c) -> (a -> Environment e b) -> a -> Environment e c Source # ($>>=) :: Covariant u => ((u :. Environment e) := a) -> (a -> Environment e b) -> (u :. Environment e) := b Source # (<>>=) :: (Environment e b -> c) -> (a -> Environment e b) -> Environment e a -> c Source # | |
Semigroup e => Bindable (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator (>>=) :: Accumulator e a -> (a -> Accumulator e b) -> Accumulator e b Source # (=<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # bind :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # join :: ((Accumulator e :. Accumulator e) := a) -> Accumulator e a Source # (>=>) :: (a -> Accumulator e b) -> (b -> Accumulator e c) -> a -> Accumulator e c Source # (<=<) :: (b -> Accumulator e c) -> (a -> Accumulator e b) -> a -> Accumulator e c Source # ($>>=) :: Covariant u => ((u :. Accumulator e) := a) -> (a -> Accumulator e b) -> (u :. Accumulator e) := b Source # (<>>=) :: (Accumulator e b -> c) -> (a -> Accumulator e b) -> Accumulator e a -> c Source # | |
Bindable (Tagged tag) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Tagged (>>=) :: Tagged tag a -> (a -> Tagged tag b) -> Tagged tag b Source # (=<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # bind :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # join :: ((Tagged tag :. Tagged tag) := a) -> Tagged tag a Source # (>=>) :: (a -> Tagged tag b) -> (b -> Tagged tag c) -> a -> Tagged tag c Source # (<=<) :: (b -> Tagged tag c) -> (a -> Tagged tag b) -> a -> Tagged tag c Source # ($>>=) :: Covariant u => ((u :. Tagged tag) := a) -> (a -> Tagged tag b) -> (u :. Tagged tag) := b Source # (<>>=) :: (Tagged tag b -> c) -> (a -> Tagged tag b) -> Tagged tag a -> c Source # | |
Bindable (Schematic Monad t u) => Bindable (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic (>>=) :: (t :> u) a -> (a -> (t :> u) b) -> (t :> u) b Source # (=<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # bind :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # join :: (((t :> u) :. (t :> u)) := a) -> (t :> u) a Source # (>=>) :: (a -> (t :> u) b) -> (b -> (t :> u) c) -> a -> (t :> u) c Source # (<=<) :: (b -> (t :> u) c) -> (a -> (t :> u) b) -> a -> (t :> u) c Source # ($>>=) :: Covariant u0 => ((u0 :. (t :> u)) := a) -> (a -> (t :> u) b) -> (u0 :. (t :> u)) := b Source # (<>>=) :: ((t :> u) b -> c) -> (a -> (t :> u) b) -> (t :> u) a -> c Source # | |
Bindable (Schematic Comonad t u) => Bindable (t :< u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic (>>=) :: (t :< u) a -> (a -> (t :< u) b) -> (t :< u) b Source # (=<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # bind :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # join :: (((t :< u) :. (t :< u)) := a) -> (t :< u) a Source # (>=>) :: (a -> (t :< u) b) -> (b -> (t :< u) c) -> a -> (t :< u) c Source # (<=<) :: (b -> (t :< u) c) -> (a -> (t :< u) b) -> a -> (t :< u) c Source # ($>>=) :: Covariant u0 => ((u0 :. (t :< u)) := a) -> (a -> (t :< u) b) -> (u0 :. (t :< u)) := b Source # (<>>=) :: ((t :< u) b -> c) -> (a -> (t :< u) b) -> (t :< u) a -> c Source # | |
Bindable ((->) e :: Type -> Type) Source # | |
Defined in Pandora.Pattern.Functor.Bindable (>>=) :: (e -> a) -> (a -> e -> b) -> e -> b Source # (=<<) :: (a -> e -> b) -> (e -> a) -> e -> b Source # bind :: (a -> e -> b) -> (e -> a) -> e -> b Source # join :: (((->) e :. (->) e) := a) -> e -> a Source # (>=>) :: (a -> e -> b) -> (b -> e -> c) -> a -> e -> c Source # (<=<) :: (b -> e -> c) -> (a -> e -> b) -> a -> e -> c Source # ($>>=) :: Covariant u => ((u :. (->) e) := a) -> (a -> e -> b) -> (u :. (->) e) := b Source # (<>>=) :: ((e -> b) -> c) -> (a -> e -> b) -> (e -> a) -> c Source # | |
Covariant t => Bindable (Continuation r t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Continuation (>>=) :: Continuation r t a -> (a -> Continuation r t b) -> Continuation r t b Source # (=<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # bind :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # join :: ((Continuation r t :. Continuation r t) := a) -> Continuation r t a Source # (>=>) :: (a -> Continuation r t b) -> (b -> Continuation r t c) -> a -> Continuation r t c Source # (<=<) :: (b -> Continuation r t c) -> (a -> Continuation r t b) -> a -> Continuation r t c Source # ($>>=) :: Covariant u => ((u :. Continuation r t) := a) -> (a -> Continuation r t b) -> (u :. Continuation r t) := b Source # (<>>=) :: (Continuation r t b -> c) -> (a -> Continuation r t b) -> Continuation r t a -> c Source # | |
(Adjoint t' t, Bindable u) => Bindable ((t <:<.>:> t') := u) Source # | |
Defined in Pandora.Paradigm.Schemes.TUT (>>=) :: ((t <:<.>:> t') := u) a -> (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) b Source # (=<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # bind :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # join :: ((((t <:<.>:> t') := u) :. ((t <:<.>:> t') := u)) := a) -> ((t <:<.>:> t') := u) a Source # (>=>) :: (a -> ((t <:<.>:> t') := u) b) -> (b -> ((t <:<.>:> t') := u) c) -> a -> ((t <:<.>:> t') := u) c Source # (<=<) :: (b -> ((t <:<.>:> t') := u) c) -> (a -> ((t <:<.>:> t') := u) b) -> a -> ((t <:<.>:> t') := u) c Source # ($>>=) :: Covariant u0 => ((u0 :. ((t <:<.>:> t') := u)) := a) -> (a -> ((t <:<.>:> t') := u) b) -> (u0 :. ((t <:<.>:> t') := u)) := b Source # (<>>=) :: (((t <:<.>:> t') := u) b -> c) -> (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> c Source # | |
(Traversable t, Bindable t, Applicative u, Monad u) => Bindable (t <.:> u) Source # | |
Defined in Pandora.Paradigm.Schemes.UT (>>=) :: (t <.:> u) a -> (a -> (t <.:> u) b) -> (t <.:> u) b Source # (=<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # bind :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # join :: (((t <.:> u) :. (t <.:> u)) := a) -> (t <.:> u) a Source # (>=>) :: (a -> (t <.:> u) b) -> (b -> (t <.:> u) c) -> a -> (t <.:> u) c Source # (<=<) :: (b -> (t <.:> u) c) -> (a -> (t <.:> u) b) -> a -> (t <.:> u) c Source # ($>>=) :: Covariant u0 => ((u0 :. (t <.:> u)) := a) -> (a -> (t <.:> u) b) -> (u0 :. (t <.:> u)) := b Source # (<>>=) :: ((t <.:> u) b -> c) -> (a -> (t <.:> u) b) -> (t <.:> u) a -> c Source # | |
(Semigroup e, Pointable u, Bindable u) => Bindable ((:*:) e <.:> u) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator (>>=) :: ((:*:) e <.:> u) a -> (a -> ((:*:) e <.:> u) b) -> ((:*:) e <.:> u) b Source # (=<<) :: (a -> ((:*:) e <.:> u) b) -> ((:*:) e <.:> u) a -> ((:*:) e <.:> u) b Source # bind :: (a -> ((:*:) e <.:> u) b) -> ((:*:) e <.:> u) a -> ((:*:) e <.:> u) b Source # join :: ((((:*:) e <.:> u) :. ((:*:) e <.:> u)) := a) -> ((:*:) e <.:> u) a Source # (>=>) :: (a -> ((:*:) e <.:> u) b) -> (b -> ((:*:) e <.:> u) c) -> a -> ((:*:) e <.:> u) c Source # (<=<) :: (b -> ((:*:) e <.:> u) c) -> (a -> ((:*:) e <.:> u) b) -> a -> ((:*:) e <.:> u) c Source # ($>>=) :: Covariant u0 => ((u0 :. ((:*:) e <.:> u)) := a) -> (a -> ((:*:) e <.:> u) b) -> (u0 :. ((:*:) e <.:> u)) := b Source # (<>>=) :: (((:*:) e <.:> u) b -> c) -> (a -> ((:*:) e <.:> u) b) -> ((:*:) e <.:> u) a -> c Source # | |
(Bindable t, Distributive t, Bindable u) => Bindable (t <:.> u) Source # | |
Defined in Pandora.Paradigm.Schemes.TU (>>=) :: (t <:.> u) a -> (a -> (t <:.> u) b) -> (t <:.> u) b Source # (=<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # bind :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # join :: (((t <:.> u) :. (t <:.> u)) := a) -> (t <:.> u) a Source # (>=>) :: (a -> (t <:.> u) b) -> (b -> (t <:.> u) c) -> a -> (t <:.> u) c Source # (<=<) :: (b -> (t <:.> u) c) -> (a -> (t <:.> u) b) -> a -> (t <:.> u) c Source # ($>>=) :: Covariant u0 => ((u0 :. (t <:.> u)) := a) -> (a -> (t <:.> u) b) -> (u0 :. (t <:.> u)) := b Source # (<>>=) :: ((t <:.> u) b -> c) -> (a -> (t <:.> u) b) -> (t <:.> u) a -> c Source # |