parameterized-0.5.0.0: Parameterized/indexed monoids and monads using only a single parameter type variable.

Safe HaskellSafe
LanguageHaskell2010

Parameterized.Control.Monad

Synopsis

Documentation

class PApplicative m t u v => PMonad m t u v where Source #

Parameterized version of Monad.

Minimal complete definition

pbind

Methods

pbind :: PUnary m t a -> (a -> PUnary m u b) -> PUnary m v b infixl 1 Source #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

Instances

(Functor (ManyReader m (Many c)), Monad m, Select a c, Select b c, (~) [Type] c (AppendUnique Type a b)) => PMonad * (ManyReader m) (Many a) (Many b) (Many c) Source # 

Methods

pbind :: PUnary (ManyReader m) (Many a) (Many b) a -> (a -> PUnary (ManyReader m) (Many a) (Many c) b) -> PUnary (ManyReader m) (Many a) v b Source #

(Monad m, Select a c, Select b c, Amend' a c, Amend' b c, (~) [Type] c (AppendUnique Type a b)) => PMonad * (ManyState m) (Many a) (Many b) (Many c) Source # 

Methods

pbind :: PUnary (ManyState m) (Many a) (Many b) a -> (a -> PUnary (ManyState m) (Many a) (Many c) b) -> PUnary (ManyState m) (Many a) v b Source #

Monad m => PMonad * (ChangingState m) (s, t) (t, u) (s, u) Source # 

Methods

pbind :: PUnary (ChangingState m) (s, t) (t, u) a -> (a -> PUnary (ChangingState m) (s, t) (s, u) b) -> PUnary (ChangingState m) (s, t) v b Source #

(&>>=) :: PMonad m t u v => PUnary m t a -> (a -> PUnary m u b) -> PUnary m v b infixl 1 Source #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

(&>>) :: PMonad m t u v => PUnary m t a -> PUnary m u b -> PUnary m v b infixl 1 Source #

(&=<<) :: PMonad m t u v => (a -> PUnary m u b) -> PUnary m t a -> PUnary m v b infixr 1 Source #

Same as &>>=, but with the arguments interchanged.

(&>=>) :: PMonad m t u v => (a -> PUnary m t b) -> (b -> PUnary m u c) -> a -> PUnary m v c infixr 1 Source #

Left-to-right Kleisli composition of monads.

(&<=<) :: PMonad m t u v => (b -> PUnary m u c) -> (a -> PUnary m t b) -> a -> PUnary m v c infixr 1 Source #

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped.