Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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)
Instances
Bindable ((->) :: Type -> Type -> Type) Identity Source # | |
Bindable ((->) :: Type -> Type -> Type) Maybe Source # | |
Bindable ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # | |
(Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Bindable ((->) :: Type -> Type -> Type) t) => Bindable ((->) :: Type -> Type -> Type) (Jack t) 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 # | |
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 # | |
(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 # | |
Bindable ((->) :: Type -> Type -> Type) (State s) Source # | |
Bindable ((->) :: Type -> Type -> Type) (Environment e) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment (=<<) :: (a -> Environment e b) -> Environment e a -> Environment e b Source # | |
Semigroup e => Bindable ((->) :: Type -> Type -> Type) (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator (=<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # | |
Bindable ((->) :: Type -> Type -> Type) (Tagged tag) Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Bindable ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Bindable ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Bindable ((->) :: Type -> Type -> Type) ((->) e :: Type -> Type) 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 # | |
(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 # | |
(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Bindable ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) 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 # | |