[Haskell-cafe] StateWriter: a monad-writing exercise

Anthony LODI anthony.lodi at gmail.com
Thu Sep 25 10:18:13 EDT 2008


Hello haskell-cafe,

In my application I have a complex state threaded through long
computation chains, and I need a way to log all state changes (so that
the evolving state can be animated/replayed somewhere else).
Initially I tried combining State and Writer monads but this allows
for the possibility to change the state, and forget to write a log
entry, etc.

So I decided to write a separate monad, StateWriter l s, that takes a
state-modifying function, l->s->s (l is an ADT for all the allowable
state transitions), an initial state s, and only allows s to change by
appending 'l' log entries inside the monad.  The net result is that I
should have read-only access to the current state inside the monad,
and all state transitions should be logged (by going through the one
function, the log entries serve as witnesses to all state
transitions).

Anyway, here's my (very rough!) first stab at the problem.  This is
the first time I've tried writing a monad so any comments/critiques
are much appreciated.

Also, about the 'StateWriter' idea in general: am I just (poorly?)
reimplementing something obvious?  Is it unlikely to scale well on
real-world problems?  Is there some way to combine the existing State
and Writer monads to avoid having to do this?

If there's nothing seriously wrong here, I was thinking my next step
would be to try changing the lists to monoids (like in the Writer
monad), and then to try writing a transformer version of the whole
thing.

Cheers,

- Anthony LODI


================================================================================

{-# LANGUAGE MultiParamTypeClasses,
            FunctionalDependencies,
            FlexibleInstances #-}

newtype StateWriter l s a = StateWriter { _runSWriter :: (l -> s -> s)
                                                     -> [l]
                                                     -> s
                                                     -> (a, [l], s)
                                       }


instance Monad (StateWriter l s) where
   return a = StateWriter $ \_ ls s -> (a, ls, s)

   (StateWriter x) >>= f = StateWriter $ \fn ls s ->
                                let (v, ls', s') = x fn ls s
                                in
                                  _runSWriter (f v) fn ls' s'

class MonadStateWriter m l s | m -> l s where
 put :: l -> m ()
 get :: m s

instance MonadStateWriter (StateWriter l s) l s where
 put l = StateWriter $ \fn ls s -> ((), ls ++ [l], fn l s)
 get = StateWriter $ \fn ls s -> (s, ls, s)


runSWriter :: StateWriter l s a -> (l -> s -> s) -> s -> (a, [l], s)
runSWriter sw fn = _runSWriter sw fn []


--------------------------------------------------------------------------------


data Ops = Inc
        | Dec
          deriving (Show)

test :: StateWriter Ops Int String
test = do
 put Inc
 put Inc
 put Inc
 val <- get
 let op = if val == 3 then Dec else Inc
 put op
 return "done"

stateFn :: Ops -> Int -> Int
stateFn Inc s = s + 1
stateFn Dec s = s - 1

runtest = runSWriter test stateFn 0 -- ("done",[Inc,Inc,Inc,Dec],2)


More information about the Haskell-Cafe mailing list