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

Control.Monad.Trans.Changeset

Description

A general state monad transformer with separate types for the state and the possible changes, updates, commits, or diffs.

A typical example is a large state type (e.g., a user entry in a database of a webshop) which only allows small changes (e.g., adding or deleting a delivery address):

data User = User
  { userName :: Text
  , password :: Hash
  , ...
  , addresses :: Map Text Address
  , ...
  }

When we want to be able to restrict to specific changes (e.g., only the addresses should be changed), and we want to be able to inspect the changes, then ChangesetT is a good choice. In our example, a general function on addresses, or even on the whole user, cannot be inspected. But if we restrict to only adding or deleting addresses, we can define a custom datatype such as:

data ChangeAddress
  -- | Add an address under a given key
  = Add Text Address
  -- | Delete the address for the given key
  | Delete Text

Changes for such a type (or rather, for the monoid Changes ChangeAddress) can be inspected.

ChangesetT is a very general state monad transformer. It has all the standard state monads from transformers as special cases:

Transformer special caseState typeMonoid typeIntuition
WriterT w()wNo possibility to observe the current state
AccumT wRegular wwThe state is the same type as the changes
StateT ssFirst sThe change overwrites all previous changes

The changeset ecosystem has support for standard containers and optics from lens by providing the packages changeset-containers and changeset-lens.

Orphan instances for newer (2.3) mtl classes such as MonadAccum and MonadSelect can be found in Control.Monad.Trans.Changeset.Orphan. These are only provided for GHC >= 9.6.

Synopsis

The ChangesetT monad transformer

newtype ChangesetT s w m a Source #

Hold a state of type s, which is allowed to be mutated by an action of a monoid w.

The state s has the role of the current state. An a is computed while performing a side effect in m, and these can depend on the current state.

The type w encodes changes (or updates, edits, commits, diffs, patches ...) to the state s. This relation is captured by the RightAction type class from monoid-extras. It contains a method, act :: w -> s -> s, which implements the semantics of w as the type of updates to s.

The standard example is that of a big record where we only want to change a small portion:

data User = User
  { name :: Text
  , password :: Hash
  , ...
  , addresses :: Map Text Address
  , ...
  }

If all changes that our business logic should be able to perform are adding or deleting an address, it would be cumbersome to work in a State User monad, since we only want to modify a small portion. Instead, we define a type of changes to User:

data ChangeAddress
  -- | Add an address under a given key
  = Add Text Address
  -- | Delete the address for the given key
  | Delete Text

instance RightAction ChangeAddress User where
  act = ...

Now we can conveniently work in the monad ChangesetT User [ChangeAddress] m. (Note the list type which gives us a free Monoid instance.) Here we can perform operations like change [Add "home" homeAddress] or change [Delete "work"] to modify the addresses, current to view the current state (containing all changes so far), or apply a more complex function like revise $ const $ filter (/= Delete "default") which would remove all changes that attempt to delete the "default" address.

As a further example, if s represents some type of time stamps, then w can be a type of durations: Two timestamps cannot be added, but two durations can. A computation in ChangesetT s w could then have access to some simulated notion of "current time", while being able to add symbolic "delays".

Another class of examples arises operation based or commutative Conflict-free Replicated Data Type (CRDT). Then s is the internal state (the "payload") of the CRDT, and w is the update operation. For example s = Int, and for w we would define data Count = Increment | Decrement.

The Monad and Applicative classes are defined by performing the first action, then acting with the monoid output onto the state, and then perform the second action with the updated state. So for example, change Increment >> current is different from current >>= (n -> change Increment >> return n): If we apply flip evalChangeset 0 to each, the first one would return 1, while the second returns 0.

So, if at any point in a do notation we want to inspect the current state, we can assume that all previous changes have been applied. In that sense, this monad behaves very much like any other state monad transformer.

Constructors

ChangesetT 

Fields

  • getChangesetT :: s -> m (w, a)

    Extract the changeset function without applying it to the state.

Instances

Instances details
(MonadRWS r w s m, RightAction w' s', Monoid w') => MonadRWS r w s (ChangesetT s' w' m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

(RightAction w s, Monoid w, Monad m) => MonadChangeset s w (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

changeset :: (s -> (a, w)) -> ChangesetT s w m a Source #

change :: w -> ChangesetT s w m () Source #

current :: ChangesetT s w m s Source #

MFunctor (ChangesetT s w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ChangesetT s w m b -> ChangesetT s w n b #

(MonadAccum w m, RightAction w' s, Monoid w') => MonadAccum w (ChangesetT s w' m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset.Orphan

Methods

look :: ChangesetT s w' m w #

add :: w -> ChangesetT s w' m () #

accum :: (w -> (a, w)) -> ChangesetT s w' m a #

(MonadError e m, RightAction w s, Monoid w) => MonadError e (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

throwError :: e -> ChangesetT s w m a #

catchError :: ChangesetT s w m a -> (e -> ChangesetT s w m a) -> ChangesetT s w m a #

(MonadReader r m, RightAction w s, Monoid w) => MonadReader r (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

ask :: ChangesetT s w m r #

local :: (r -> r) -> ChangesetT s w m a -> ChangesetT s w m a #

reader :: (r -> a) -> ChangesetT s w m a #

(MonadSelect r m, RightAction w s, Monoid w) => MonadSelect r (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset.Orphan

Methods

select :: ((a -> r) -> a) -> ChangesetT s w m a #

(MonadState s m, RightAction w' s', Monoid w') => MonadState s (ChangesetT s' w' m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

get :: ChangesetT s' w' m s #

put :: s -> ChangesetT s' w' m () #

state :: (s -> (a, s)) -> ChangesetT s' w' m a #

(MonadWriter w m, RightAction w' s, Monoid w') => MonadWriter w (ChangesetT s w' m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

writer :: (a, w) -> ChangesetT s w' m a #

tell :: w -> ChangesetT s w' m () #

listen :: ChangesetT s w' m a -> ChangesetT s w' m (a, w) #

pass :: ChangesetT s w' m (a, w -> w) -> ChangesetT s w' m a #

(RightAction w s, Monoid w) => MMonad (ChangesetT s w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

embed :: forall (n :: Type -> Type) m b. Monad n => (forall a. m a -> ChangesetT s w n a) -> ChangesetT s w m b -> ChangesetT s w n b #

(RightAction w s, Monoid w) => MonadTrans (ChangesetT s w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

lift :: Monad m => m a -> ChangesetT s w m a #

(Alternative m, Monoid w, RightAction w s, Monad m) => Alternative (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

empty :: ChangesetT s w m a #

(<|>) :: ChangesetT s w m a -> ChangesetT s w m a -> ChangesetT s w m a #

some :: ChangesetT s w m a -> ChangesetT s w m [a] #

many :: ChangesetT s w m a -> ChangesetT s w m [a] #

(Monoid w, RightAction w s, Monad m) => Applicative (ChangesetT s w m) Source #

The Monad m constraint is indeed necessary, since we need the log from the first action to change it to the state for the second action.

Instance details

Defined in Control.Monad.Trans.Changeset

Methods

pure :: a -> ChangesetT s w m a #

(<*>) :: ChangesetT s w m (a -> b) -> ChangesetT s w m a -> ChangesetT s w m b #

liftA2 :: (a -> b -> c) -> ChangesetT s w m a -> ChangesetT s w m b -> ChangesetT s w m c #

(*>) :: ChangesetT s w m a -> ChangesetT s w m b -> ChangesetT s w m b #

(<*) :: ChangesetT s w m a -> ChangesetT s w m b -> ChangesetT s w m a #

Functor m => Functor (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

fmap :: (a -> b) -> ChangesetT s w m a -> ChangesetT s w m b #

(<$) :: a -> ChangesetT s w m b -> ChangesetT s w m a #

(RightAction w s, Monoid w, Monad m) => Monad (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(>>=) :: ChangesetT s w m a -> (a -> ChangesetT s w m b) -> ChangesetT s w m b #

(>>) :: ChangesetT s w m a -> ChangesetT s w m b -> ChangesetT s w m b #

return :: a -> ChangesetT s w m a #

(Alternative m, Monoid w, RightAction w s, Monad m) => MonadPlus (ChangesetT s w m) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

mzero :: ChangesetT s w m a #

mplus :: ChangesetT s w m a -> ChangesetT s w m a -> ChangesetT s w m a #

Running a ChangesetT action

getChangeT :: Functor m => ChangesetT s w m a -> s -> m w Source #

Extract the changes that would be applied.

runChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m (a, s) Source #

Run the action with an initial state and apply all resulting changes to it.

evalChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m a Source #

Run the action with an initial state and extract only the value.

execChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m s Source #

Run the action with an initial state and extract only the state.

ChangesetT API with relaxed constraints

changesetA :: Applicative m => (s -> (a, w)) -> ChangesetT s w m a Source #

See changeset.

The A suffix means that only Applicative is required, not Monad.

changeA :: Applicative m => w -> ChangesetT s w m () Source #

See change.

The A suffix means that only Applicative is required, not Monad.

currentA :: (Applicative m, Monoid w) => ChangesetT s w m s Source #

See current.

The A suffix means that only Applicative is required, not Monad.

liftF :: (Functor m, Monoid w) => m a -> ChangesetT s w m a Source #

Like lift from the MonadTrans class, but with fewer constraints.

Transforming ChangesetT operations

revise :: Functor m => ChangesetT s w m (a, s -> w -> w) -> ChangesetT s w m a Source #

Change the action that would be applied.

The function in the second position of the tuple receives the initial state and the change that would be applied. It has to output the action that will be applied instead.

changelog :: Functor m => ChangesetT s w m a -> ChangesetT s w m (a, w) Source #

Adds the to-be-applied changes to the foreground value.

withCurrent :: (s2 -> s1) -> ChangesetT s1 w m a -> ChangesetT s2 w m a Source #

Precomposes the current state with a function to before computing the change.

mapChange :: Functor m => (w1 -> w2) -> ChangesetT s w1 m a -> ChangesetT s w2 m a Source #

Apply a function to the change.

Combining ChangesetT operations

(|*>) :: (Semigroup w, Applicative m) => ChangesetT s w m (a -> b) -> ChangesetT s w m a -> ChangesetT s w m b Source #

Like (<*>) from Applicative, but ignore the change from the first action in the initial state for the second action.

This only needs an Applicative constraint on m, not Monad.

hoistF :: (forall x. m x -> n x) -> ChangesetT s w m a -> ChangesetT s w n a Source #

Like hoist from the mmorph package, but with no constraints.

Pure changesets

type Changeset s w = ChangesetT s w Identity Source #

A pure changeset acts in the Identity monad. The only effects it has are inspecting the current state, and adding a change.

Changeset s w a is isomorphic to s -> (w, a).

getChangeset :: Changeset s w a -> s -> (w, a) Source #

getChange :: Changeset s w a -> s -> w Source #

runChangeset :: RightAction w s => Changeset s w a -> s -> (a, s) Source #

evalChangeset :: RightAction w s => Changeset s w a -> s -> a Source #

execChangeset :: RightAction w s => Changeset s w a -> s -> s Source #

Changes: container for changes that don't have a Monoid instance

newtype Changes w Source #

A collection of individual changes.

Often, we only want to define a type for single changes to a state. In that case, Changes is handy. It serves as a container for changes that don't have a Monoid or Semigroup instance. All changes are applied sequentially.

To inspect or edit Changes, see the type classes Functor, Foldable, Traversable, Filterable and Witherable.

Constructors

Changes 

Fields

Instances

Instances details
Foldable Changes Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

fold :: Monoid m => Changes m -> m #

foldMap :: Monoid m => (a -> m) -> Changes a -> m #

foldMap' :: Monoid m => (a -> m) -> Changes a -> m #

foldr :: (a -> b -> b) -> b -> Changes a -> b #

foldr' :: (a -> b -> b) -> b -> Changes a -> b #

foldl :: (b -> a -> b) -> b -> Changes a -> b #

foldl' :: (b -> a -> b) -> b -> Changes a -> b #

foldr1 :: (a -> a -> a) -> Changes a -> a #

foldl1 :: (a -> a -> a) -> Changes a -> a #

toList :: Changes a -> [a] #

null :: Changes a -> Bool #

length :: Changes a -> Int #

elem :: Eq a => a -> Changes a -> Bool #

maximum :: Ord a => Changes a -> a #

minimum :: Ord a => Changes a -> a #

sum :: Num a => Changes a -> a #

product :: Num a => Changes a -> a #

Traversable Changes Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

traverse :: Applicative f => (a -> f b) -> Changes a -> f (Changes b) #

sequenceA :: Applicative f => Changes (f a) -> f (Changes a) #

mapM :: Monad m => (a -> m b) -> Changes a -> m (Changes b) #

sequence :: Monad m => Changes (m a) -> m (Changes a) #

Functor Changes Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

fmap :: (a -> b) -> Changes a -> Changes b #

(<$) :: a -> Changes b -> Changes a #

Filterable Changes Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

mapMaybe :: (a -> Maybe b) -> Changes a -> Changes b #

catMaybes :: Changes (Maybe a) -> Changes a #

filter :: (a -> Bool) -> Changes a -> Changes a #

drain :: Changes a -> Changes b #

Witherable Changes Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Changes a -> f (Changes b) #

witherM :: Monad m => (a -> m (Maybe b)) -> Changes a -> m (Changes b) #

filterA :: Applicative f => (a -> f Bool) -> Changes a -> f (Changes a) #

witherMap :: Applicative m => (Changes b -> r) -> (a -> m (Maybe b)) -> Changes a -> m r #

Monoid (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

mempty :: Changes w #

mappend :: Changes w -> Changes w -> Changes w #

mconcat :: [Changes w] -> Changes w #

Semigroup (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(<>) :: Changes w -> Changes w -> Changes w #

sconcat :: NonEmpty (Changes w) -> Changes w #

stimes :: Integral b => b -> Changes w -> Changes w #

Read w => Read (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Show w => Show (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

showsPrec :: Int -> Changes w -> ShowS #

show :: Changes w -> String #

showList :: [Changes w] -> ShowS #

Eq w => Eq (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(==) :: Changes w -> Changes w -> Bool #

(/=) :: Changes w -> Changes w -> Bool #

Ord w => Ord (Changes w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

compare :: Changes w -> Changes w -> Ordering #

(<) :: Changes w -> Changes w -> Bool #

(<=) :: Changes w -> Changes w -> Bool #

(>) :: Changes w -> Changes w -> Bool #

(>=) :: Changes w -> Changes w -> Bool #

max :: Changes w -> Changes w -> Changes w #

min :: Changes w -> Changes w -> Changes w #

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 #

changes :: [w] -> Changes w Source #

Create Changes from a list of changes.

addChange :: w -> Changes w -> Changes w Source #

Append a single change.

When addChange w cs acts on a state with actRight, w will be applied last.

singleChange :: w -> Changes w Source #

Create a Changes from a single change.

changeSingle :: MonadChangeset s (Changes w) m => w -> m () Source #

Apply a single change.

Change examples

Changing lists

data ListChange a Source #

A list can be changed by prepending an element, or removing one.

To change an element of a list, see the indexed changes from changeset-lens.

Constructors

Cons a

Prepend an element

Pop

Remove the first element (noop on an empty list)

Instances

Instances details
Show a => Show (ListChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Eq a => Eq (ListChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(==) :: ListChange a -> ListChange a -> Bool #

(/=) :: ListChange a -> ListChange a -> Bool #

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

Defined in Control.Monad.Trans.Changeset

Methods

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

Changing integers

data Count Source #

An integer can be incremented by 1.

Constructors

Increment 

Instances

Instances details
Show Count Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Eq Count Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(==) :: Count -> Count -> Bool #

(/=) :: Count -> Count -> Bool #

RightAction Count Int Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

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

Changing Maybes

newtype MaybeChange a Source #

Change a Maybe by either deleting the value or forcing it to be present.

Constructors

MaybeChange 

Fields

Instances

Instances details
Monoid (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Semigroup (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Read a => Read (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Show a => Show (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Eq a => Eq (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Ord a => Ord (MaybeChange a) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

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

Defined in Control.Monad.Trans.Changeset

Methods

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

setMaybe :: Maybe a -> MaybeChange a Source #

Set the state to the given Maybe value.

setJust :: a -> MaybeChange a Source #

Set the state to Just.

setNothing :: MaybeChange a Source #

Set the state to Nothing.

Changing Functors

newtype FmapChange (f :: Type -> Type) w Source #

Change a Functor structure by applying a change for every element through fmap.

Constructors

FmapChange 

Fields

Instances

Instances details
Functor (FmapChange f) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

fmap :: (a -> b) -> FmapChange f a -> FmapChange f b #

(<$) :: a -> FmapChange f b -> FmapChange f a #

Monoid w => Monoid (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

mempty :: FmapChange f w #

mappend :: FmapChange f w -> FmapChange f w -> FmapChange f w #

mconcat :: [FmapChange f w] -> FmapChange f w #

Semigroup w => Semigroup (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(<>) :: FmapChange f w -> FmapChange f w -> FmapChange f w #

sconcat :: NonEmpty (FmapChange f w) -> FmapChange f w #

stimes :: Integral b => b -> FmapChange f w -> FmapChange f w #

Read w => Read (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Show w => Show (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

showsPrec :: Int -> FmapChange f w -> ShowS #

show :: FmapChange f w -> String #

showList :: [FmapChange f w] -> ShowS #

Eq w => Eq (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

(==) :: FmapChange f w -> FmapChange f w -> Bool #

(/=) :: FmapChange f w -> FmapChange f w -> Bool #

Ord w => Ord (FmapChange f w) Source # 
Instance details

Defined in Control.Monad.Trans.Changeset

Methods

compare :: FmapChange f w -> FmapChange f w -> Ordering #

(<) :: FmapChange f w -> FmapChange f w -> Bool #

(<=) :: FmapChange f w -> FmapChange f w -> Bool #

(>) :: FmapChange f w -> FmapChange f w -> Bool #

(>=) :: FmapChange f w -> FmapChange f w -> Bool #

max :: FmapChange f w -> FmapChange f w -> FmapChange f w #

min :: FmapChange f w -> FmapChange f w -> FmapChange f w #

(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 #

Changing Maybes as Functors

type JustChange = FmapChange Maybe Source #

Apply changes only to Just values.

justChange :: w -> JustChange w Source #

Apply changes only to Just values.