pandora-0.4.6: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Pattern.Functor.Bindable

Synopsis

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)

Methods

(=<<) :: source a (t b) -> source (t a) (t b) infixr 1 Source #

Instances

Instances details
Bindable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

Bindable ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

(Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Bindable ((->) :: Type -> Type -> Type) t) => Bindable ((->) :: Type -> Type -> Type) (Jack t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(=<<) :: (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 # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

Bindable ((->) :: Type -> Type -> Type) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(=<<) :: (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 # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

(=<<) :: (a -> Comprehension t b) -> Comprehension t a -> Comprehension t b Source #

Bindable ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

Bindable ((->) :: Type -> Type -> Type) (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

Semigroup e => Bindable ((->) :: Type -> Type -> Type) (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

Bindable ((->) :: Type -> Type -> Type) (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(=<<) :: (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 # 
Instance details

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

Methods

(=<<) :: (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 # 
Instance details

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Bindable ((->) :: Type -> Type -> Type) (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

(=<<) :: (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 # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

(=<<) :: (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 ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

(=<<) :: (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 # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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