Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
) can be inspected.Changes
ChangeAddress
ChangesetT
is a very general state monad transformer.
It has all the standard state monads from transformers
as special cases:
Transformer special case | State type | Monoid type | Intuition |
---|---|---|---|
| () | w | No possibility to observe the current state |
|
| w | The state is the same type as the changes |
| s | First s | The 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
- newtype ChangesetT s w m a = ChangesetT {
- getChangesetT :: s -> m (w, a)
- getChangeT :: Functor m => ChangesetT s w m a -> s -> m w
- runChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m (a, s)
- evalChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m a
- execChangesetT :: (Functor m, RightAction w s) => ChangesetT s w m a -> s -> m s
- changesetA :: Applicative m => (s -> (a, w)) -> ChangesetT s w m a
- changeA :: Applicative m => w -> ChangesetT s w m ()
- currentA :: (Applicative m, Monoid w) => ChangesetT s w m s
- liftF :: (Functor m, Monoid w) => m a -> ChangesetT s w m a
- revise :: Functor m => ChangesetT s w m (a, s -> w -> w) -> ChangesetT s w m a
- changelog :: Functor m => ChangesetT s w m a -> ChangesetT s w m (a, w)
- withCurrent :: (s2 -> s1) -> ChangesetT s1 w m a -> ChangesetT s2 w m a
- mapChange :: Functor m => (w1 -> w2) -> ChangesetT s w1 m a -> ChangesetT s w2 m a
- (|*>) :: (Semigroup w, Applicative m) => ChangesetT s w m (a -> b) -> ChangesetT s w m a -> ChangesetT s w m b
- hoistF :: (forall x. m x -> n x) -> ChangesetT s w m a -> ChangesetT s w n a
- type Changeset s w = ChangesetT s w Identity
- getChangeset :: Changeset s w a -> s -> (w, a)
- getChange :: Changeset s w a -> s -> w
- runChangeset :: RightAction w s => Changeset s w a -> s -> (a, s)
- evalChangeset :: RightAction w s => Changeset s w a -> s -> a
- execChangeset :: RightAction w s => Changeset s w a -> s -> s
- newtype Changes w = Changes {
- getChanges :: Seq w
- changes :: [w] -> Changes w
- addChange :: w -> Changes w -> Changes w
- singleChange :: w -> Changes w
- changeSingle :: MonadChangeset s (Changes w) m => w -> m ()
- data ListChange a
- data Count = Increment
- newtype MaybeChange a = MaybeChange {
- getMaybeChange :: Last (Maybe a)
- setMaybe :: Maybe a -> MaybeChange a
- setJust :: a -> MaybeChange a
- setNothing :: MaybeChange a
- newtype FmapChange (f :: Type -> Type) w = FmapChange {
- getFmapChange :: w
- type JustChange = FmapChange Maybe
- justChange :: w -> JustChange w
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,
,
which implements the semantics of act
:: w -> s -> sw
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
monad, since we only want to modify a small portion.
Instead, we define a type of changes to State
UserUser
:
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
(Note the list type which gives us a free ChangesetT
User [ChangeAddress] m.Monoid
instance.)
Here we can perform operations like
or change
[Add "home" homeAddress]
to modify the addresses,
change
[Delete "work"]current
to view the current state (containing all changes so far),
or apply a more complex function like
which would remove all changes that attempt to delete the revise
$ const $ filter (/= Delete "default")"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
could then have access to some simulated notion of "current time",
while being able to add symbolic "delays".ChangesetT
s w
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 act
ing with the monoid output onto the state, and then perform the second action with the updated state.
So for example,
is different from change
Increment >> current
:
If we apply current
>>= (n -> change
Increment >> return n)
to each,
the first one would return 1, while the second returns 0.flip
evalChangeset
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
|
Instances
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 #
getChangeset :: Changeset s w a -> s -> (w, a) Source #
Like getChangesetT
.
getChange :: Changeset s w a -> s -> w Source #
Like getChangeT
.
runChangeset :: RightAction w s => Changeset s w a -> s -> (a, s) Source #
Like runChangesetT
.
evalChangeset :: RightAction w s => Changeset s w a -> s -> a Source #
Like evalChangesetT
.
execChangeset :: RightAction w s => Changeset s w a -> s -> s Source #
Like execChangesetT
.
Changes
: container for changes that don't have a Monoid
instance
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
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
.
Instances
Show a => Show (ListChange a) Source # | |
Defined in Control.Monad.Trans.Changeset Methods showsPrec :: Int -> ListChange a -> ShowS # show :: ListChange a -> String # showList :: [ListChange a] -> ShowS # | |
Eq a => Eq (ListChange a) Source # | |
Defined in Control.Monad.Trans.Changeset | |
RightAction (ListChange a) [a] Source # | |
Defined in Control.Monad.Trans.Changeset Methods actRight :: [a] -> ListChange a -> [a] Source # |
Changing integers
An integer can be incremented by 1.
Constructors
Increment |
Changing Maybe
s
newtype MaybeChange a Source #
Change a Maybe
by either deleting the value or forcing it to be present.
Constructors
MaybeChange | |
Fields
|
Instances
setJust :: a -> MaybeChange a Source #
Set the state to Just
.
setNothing :: MaybeChange a Source #
Set the state to Nothing
.
Changing Functor
s
newtype FmapChange (f :: Type -> Type) w Source #
Constructors
FmapChange | |
Fields
|
Instances
Changing Maybe
s as Functor
s
type JustChange = FmapChange Maybe Source #
Apply changes only to Just
values.
justChange :: w -> JustChange w Source #
Apply changes only to Just
values.