[Haskell-cafe] Initial (term) algebra for a state monad

ajb at spamcop.net ajb at spamcop.net
Wed Jan 5 20:17:37 EST 2005


G'day all.

Quoting Iavor Diatchki <iavor.diatchki at gmail.com>:

> Apologies if I missed the point of the post (I couldn't fnid the original),
> but there is yet another even simpler way to define such term algebras,
> and it works in Haskell'98.
>
> The idea is that operations are paremeterized by their continuation, i.e.
> "bind" is spread across the computations:

Ralf Hinze advocated this approach (based on a technique by John Hughes)
in his paper "Deriving Backtracking Monad Transformers".  As you can see
from the backtracking with pruning ("cut") monad that he derives, though,
it's not necessarily a "simple" derivation, and there is a creative step
required, in working out what the context (in the case of State, the
continuation) actually is.

However, the point of the exercise was not to find a way to express a
state monad.  The point was to find a way to express it easily, as an
attempt to find the right interface before going to the trouble of
deriving an efficient implementation which is optimised for that
interface.

The GADT solution is one way to do this, and IMO it's pretty close to
the easiest.

BTW, if someone would like an "interesting" monad to play with, here is
one that I've been playing with for a while.  It's a nondeterminism
monad transformer with negation-as-failure and if-then-else with soft
cut.  The appropriate contexts/continuations for an efficient
implementation (using the Hughes/Hinze technique) turn out to be quite
difficult to find.

The operations that we need to implement are:

    - the Monad operations (return and bind),
    - the MonadTrans operation (lift),
    - the MonadPlus ones (mzero and mplus), and
    - one other operation, which plays the role of logical if-then-else.

Logical if-then-else has this signature:

    mif :: LogicT m a -> (a -> LogicT m b) -> LogicT m b -> LogicT m b

Intuitively, this takes three arguments: the "condition", the "then"
case and the "else" case.  This obeys the "obvious" laws of if-then-else:

    mif (return a) t e = t a
    mif (mzero) t e = e
    mif (mif c t' e') t e = mif c (\x -> mif (t' x) t e) (mif e' t e)

plus the "soft cut" law:

    mif (return a `mplus` m) t e = t a `mplus` (m >>= t)

The soft cut law is the one that stuffs up the more obvious candidates
for the passed context, because of this non-identity:

    mif (c1 `mplus` c2) t e /= mif c1 t e `mplus` mif c2 t e

Cheers,
Andrew Bromage


More information about the Haskell-Cafe mailing list