changeset-0.1.0.2: Stateful monad transformer based on monoidal actions
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.RightAction

Synopsis

Documentation

class RightAction m s where Source #

A right action of m on s.

Imagine s to be a type of states, and m a type of changes to s.

Laws:

  • When m is a Semigroup: s `actRight` m1 `actRight` m2 == s `actRight` (m1 <> m2)
  • When m is a Monoid: s `actRight` mempty == s

The default implementation is the trivial action which leaves s unchanged.

See also Action from monoid-extras, which is a left action.

Minimal complete definition

Nothing

Methods

actRight :: s -> m -> s infixl 5 Source #

Instances

Instances details
RightAction Void s Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: s -> Void -> s Source #

RightAction Count Int Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

actRight :: Int -> Count -> Int Source #

RightAction () s Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: s -> () -> s Source #

RightAction m () Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: () -> m -> () Source #

Semigroup m => RightAction m (Regular m) Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: Regular m -> m -> Regular m Source #

RightAction (Last s) s Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: s -> Last s -> s Source #

Action m s => RightAction (Dual m) s Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: s -> Dual m -> s Source #

RightAction w s => RightAction (Changes w) s Source #

Apply all changes sequentially

Instance details

Defined in Control.Monad.Trans.Changeset

Methods

actRight :: s -> Changes w -> s Source #

RightAction m s => RightAction (Maybe m) s Source # 
Instance details

Defined in Data.Monoid.RightAction

Methods

actRight :: s -> Maybe m -> s Source #

RightAction (ListChange a) [a] Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

actRight :: [a] -> ListChange a -> [a] Source #

RightAction (MaybeChange a) (Maybe a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

actRight :: Maybe a -> MaybeChange a -> Maybe a Source #

(RightAction m s, RightAction n s) => RightAction (m :+: n) s Source # 
Instance details

Defined in Data.Monoid.RightAction.Coproduct

Methods

actRight :: s -> (m :+: n) -> s Source #

(Functor f, RightAction w s) => RightAction (FmapChange f w) (f s) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

actRight :: f s -> FmapChange f w -> f s Source #

type REndo s = Dual (Endo s) Source #

Endomorphism type with reverse Monoid instance.

The standard Endo type has a left action on s since its composition is defined as Endo f <> Endo g = Endo (f . g). The "Right Endomorphism" type, on the other hand, has a right action. Intuitively, it behaves like the & operator:

s & f & g == s `actRight` rEndo f <> rEndo g

rEndo :: (s -> s) -> REndo s Source #

Create an endomorphism monoid that has a right action on s.