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

Pandora.Pattern.Functor.Bindable

Synopsis

Documentation

class Covariant t source source => Bindable t source 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 Identity ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

Bindable (Conclusion e) ((->) :: Type -> Type -> Type) 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 t ((->) :: Type -> Type -> Type)) => Bindable (Comprehension t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

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

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

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(=<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source #

Bindable (Schematic Monad t u) ((->) :: Type -> Type -> Type) => Bindable (t :> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

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

Methods

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

Bindable (Schematic Comonad t u) ((->) :: Type -> Type -> Type) => Bindable (t :< u) ((->) :: Type -> Type -> Type) Source # 
Instance details

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

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

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Bindable (Continuation r t) ((->) :: Type -> Type -> Type) 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 #

(Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bindable t ((->) :: Type -> Type -> Type), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:), Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable (t <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Semigroup e, Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

(Bindable t ((->) :: Type -> Type -> Type), Distributive t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable (t <:.> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

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