Changeset package released

I just released the initial version of the changeset library, and its companions changeset-containers: Stateful monad transformer based on monoidal actions and changeset-lens: Stateful monad transformer based on monoidal actions.

It contains a very general state monad that allows you to restrict, inspect, and edit the changes you are about to perform.

Motivation

Imagine you have a big data structure s, and you only want to perform a few specific kinds of updates. s might be a huge record, and you want to allow only a particular kind of benign changes to one field of that record.

Then you’d have:

data User = User
  { name :: Text
  , password :: Hash
  , ... -- Oodles of other fields
  , addresses :: [Address]
  , ...
  }

We want to change User, but only by adding more addresses to the list. Then we could define a type

data AddAddress = AddAddress Address

which denotes the change of adding an address to the user.
Its semantics are implemented with a type class:

instance RightAction AddAddress User where
  actRight user (AddAddress a) = user { addresses = a : addresses user }

The library changeset defines a new monad transformer where you can, as a first order effect:

  1. read the current state of type User
  2. add new changes of type AddAddress

You can also, as higher order operations review and revise all the currently to be applied. This is very useful if you want to have a later part of the program roll back, or log certain changes.

For example in a big web application with a huge Model, you would typically pass around changes to tiny parts of the model. Often the situation arises where we have a potentially updated model, but depending on the context we only want to allow some changes, and not others.

Theory

The gist is this:

  1. The new monad ChangesetT s w m a is isomorphic to s -> m (w, a)
  2. w is a monoid of reified changes to s.
  3. Define a right action of w on s: actRight :: s -> w -> s which contains the semantics of the change.
  4. Running a ChangesetT s w m a requires an initial state s, and returns a m (a, s), that is, an effect in the background monad m, a value, and the changed state s.

Compare to usual state: State s a is isomorphic to s -> (s, a). You cannot inspect the change itself, only what it does to the whole, possibly intractable value.

Comparison

changeset compares to a few different concepts around there:

  • AccumT: The inspiration for ChangesetT was to generalise AccumT to situations where the current state is not a Monoid, but the changes to it are. So AccumT is a special case of ChangesetT.
  • StateT: Is a special case of ChangesetT as well
  • Conflict-free replicated data types: You could model these in ChangesetT.
  • Database transactions: When s is the state of a database and w is a query, then ChangesetT s w m a has the semantics of a transaction.

Ecosystem

Planned: Integration in fused-effects, rhine, …

Questions to you, if you’re willing to play around with changeset

  • Any general feedback on the design of the library
  • Is this useful to you?
  • Is it ergonomic enough? What are the pain points?
  • Do you have an application in mind, but are unsure how to make it work?
  • Is there any other library you would want to have this integrated in? (E.g. effect framework, FRP framework)
12 Likes

Cool idea, I haven’t seen anyone try to mix actions and transformers before. Building your updates out of actions and making your action type a Group seems like a promising way to set up undo/redo in a larger program.

I’m curious what made you favour right actions over left actions, as I find the type of actLeft :: w -> s -> s much more intuitive (as with containers and lens, it makes partial application return a function over the larger structure).

Also, how’s the type inference? Most typeclasses representing actions have two unconstrained type variables which can make inference difficult.

2 Likes

That’s a great point. The initial WIP version used Action (which is a left action) from Brent Yorgey’s excellent monoid-extras package. I would have loved just piggybacking on this, and put in quite some effort to make it work. But it turned out to be unintuitive:

For a left action you expect a generalized associativity axiom to hold:

m1 <> m2 `act` s == m1 `act` m2 `act` s

So m2 acts on s first, and m1 second. But imagine you’d add two changes in changeset:

do
  change m1
  change m2

I think that intuitively you’d expect that m1 is applied first, and m2 second. WriterT and AccumT behave that way.

But you would also expect that change is a monoid morphism:

change m1 >> change m2 == change (m1 <> m2)

These two observations force you to adopt a right action instead of a left action, I believe. And yes, this makes a few situations a bit awkward. But for some consolation, consider how adding several changes feels similar to the & operator:

s & execChangeset (change m1 >> change m2)
==
s & execChangeset (change m1) & execChangeset (change m2)

You’re absolutely right to be concerned. In general you will have to annotate state or change types in many places. I considered introducing a functional dependency, but I still believe it’s too restrictive.

3 Likes

This reminds me of delta encodings as advertised by Heinrich Apfelmus.

1 Like

If that is the problem that changeset solves, then from any MonadChangeset I would expect to be able to get hold of the accumulated change w, not the state, like the listen action of MonadWriter. Otherwise, why would I accumulate changes to apply later with change when I can not inspect and transform the changes?

\f -> ChangesetT (\s -> fmap ((\(w,a) -> (w,(w,a)))) (getChangesetT f s))

Can one define this for any MonadChangeset?

Also, could one not define

MonadChangeset s w m = (MonadState s m, MonadWriter w m, RightAction w s) 

and obtain essentially the same capabilities?

import Control.Arrow ((&&&))
import Control.Monad.State.Class
import Control.Monad.Writer.Class
current = get
change w = modify (flip actRight w) -- and tell w?
changeset f = state (f &&& id) >>= (\(a,w) -> tell w >> return a)