Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Covariant source source t => Bindable source t where
- (=<<) :: source a (t b) -> source (t a) (t b)
- (==<<), (===<<), (====<<), (=====<<), (======<<), (=======<<), (========<<), (=========<<) :: source a (t b) -> source (t a) (t b)
Documentation
class Covariant source source t => Bindable source t where Source #
When providing a new instance, you should ensure it satisfies : * Interchange: t >>= f = join (f <-|- t)
(=<<) :: source a (t b) -> source (t a) (t b) infixr 9 Source #
(==<<) :: source a (t b) -> source (t a) (t b) infixr 8 Source #
(===<<) :: source a (t b) -> source (t a) (t b) infixr 7 Source #
(====<<) :: source a (t b) -> source (t a) (t b) infixr 6 Source #
(=====<<) :: source a (t b) -> source (t a) (t b) infixr 5 Source #
(======<<) :: source a (t b) -> source (t a) (t b) infixr 4 Source #
(=======<<) :: source a (t b) -> source (t a) (t b) infixr 3 Source #
(========<<) :: source a (t b) -> source (t a) (t b) infixr 2 Source #
(=========<<) :: source a (t b) -> source (t a) (t b) infixr 1 Source #
Instances
Bindable ((->) :: Type -> Type -> Type) Exactly Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Exactly (=<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (==<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (===<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (====<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (=====<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (======<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (=======<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (========<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # (=========<<) :: (a -> Exactly b) -> Exactly a -> Exactly b Source # | |
Bindable ((->) :: Type -> Type -> Type) Maybe Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Maybe (=<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (==<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (===<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (====<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (=====<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (======<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (=======<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (========<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # (=========<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Proxy (=<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (==<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (===<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (====<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (=====<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (======<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (=======<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (========<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # (=========<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source # | |
(Monoidal (-->) (-->) (:*:) (:*:) t, Bindable ((->) :: Type -> Type -> Type) t) => Bindable ((->) :: Type -> Type -> Type) (Jack t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Jack (=<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (==<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (===<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (====<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (=====<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (======<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (=======<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (========<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # (=========<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Bindable ((->) :: Type -> Type -> Type) (Instruction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction (=<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (==<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (===<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (====<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (=====<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (======<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (=======<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (========<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # (=========<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion (=<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (==<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (===<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (====<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (=====<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (======<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (=======<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (========<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # (=========<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source # | |
(forall a. Semigroup ((t <::> Construction t) := a), Bindable ((->) :: Type -> Type -> Type) t) => Bindable ((->) :: Type -> Type -> Type) (Comprehension t) Source # | |
Defined in Pandora.Paradigm.Structure.Modification.Comprehension (=<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (==<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (===<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (====<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (=====<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (======<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (=======<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (========<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # (=========<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source # | |
Bindable ((->) :: Type -> Type -> Type) (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.Some.State (=<<) :: (a -> State s b) -> State s a -> State s b Source # (==<<) :: (a -> State s b) -> State s a -> State s b Source # (===<<) :: (a -> State s b) -> State s a -> State s b Source # (====<<) :: (a -> State s b) -> State s a -> State s b Source # (=====<<) :: (a -> State s b) -> State s a -> State s b Source # (======<<) :: (a -> State s b) -> State s a -> State s b Source # (=======<<) :: (a -> State s b) -> State s a -> State s b Source # (========<<) :: (a -> State s b) -> State s a -> State s b Source # (=========<<) :: (a -> State s b) -> State s a -> State s b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Provision e) Source # | |
Defined in Pandora.Paradigm.Inventory.Some.Provision (=<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (==<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (===<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (====<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (=====<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (======<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (=======<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (========<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # (=========<<) :: (a -> Provision e b) -> Provision e a -> Provision e b Source # | |
Semigroup e => Bindable ((->) :: Type -> Type -> Type) (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Some.Accumulator (=<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (==<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (===<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (====<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (=====<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (======<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (=======<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (========<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # (=========<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Tagged tag) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Tagged (=<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (==<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (===<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (====<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (=====<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (======<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (=======<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (========<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # (=========<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Bindable ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic (=<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (==<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (===<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (====<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (=====<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (======<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (=======<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (========<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # (=========<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Bindable ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic (=<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (==<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (===<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (====<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (=====<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (======<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (=======<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (========<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # (=========<<) :: (a -> (t :< u) b) -> (t :< u) a -> (t :< u) b Source # | |
Bindable ((->) :: Type -> Type -> Type) ((->) e :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Algebraic.Exponential (=<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (==<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (===<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (====<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (=====<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (======<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (=======<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (========<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # (=========<<) :: (a -> (e -> b)) -> (e -> a) -> (e -> b) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Bindable ((->) :: Type -> Type -> Type) (Continuation r t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Continuation (=<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (==<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (===<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (====<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (=====<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (======<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (=======<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (========<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # (=========<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) ((t <:<.>:> t') := u) Source # | |
Defined in Pandora.Paradigm.Schemes.TUT (=<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (==<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (===<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (====<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (=====<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (======<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (=======<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (========<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (=========<<) :: (a -> ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # | |
(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Bindable ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) u, Monoidal (-->) (-->) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) Source # | |
Defined in Pandora.Paradigm.Schemes.UT (=<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (==<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (===<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (====<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (=====<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (======<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (=======<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (========<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # (=========<<) :: (a -> (t <.:> u) b) -> (t <.:> u) a -> (t <.:> u) b Source # | |
(Bindable ((->) :: Type -> Type -> Type) t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <:.> u) Source # | |
Defined in Pandora.Paradigm.Schemes.TU (=<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (==<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (===<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (====<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (=====<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (======<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (=======<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (========<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # (=========<<) :: (a -> (t <:.> u) b) -> (t <:.> u) a -> (t <:.> u) b Source # | |
(Bindable ((->) :: Type -> Type -> Type) t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t', Bindable ((->) :: Type -> Type -> Type) t') => Bindable ((->) :: Type -> Type -> Type) (t <::> t') Source # | |
Defined in Pandora.Paradigm.Schemes.TT (=<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (==<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (===<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (====<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (=====<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (======<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (=======<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (========<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # (=========<<) :: (a -> (t <::> t') b) -> (t <::> t') a -> (t <::> t') b Source # |