Question

I'm attempting to create something that looks a lot like the State monad, but also carries a list of predicates and accompanying transition functions over the state. The basic steps for computation I'm envisioning are like follows:

Foo (state, [(pred, t)]) >>= f. Apply f to s, yielding s'. Then apply each predicate to s'. For each predicate that matches, apply the associated transition function to the state in sequence. E.g. suppose [(p1, t1), (p2, t2), (p3, t3)], f, and s. If after f s yields s', p1 s' and p3 s' both return True, you would perform t1 s' yielding s'' and then perform t3 s'' yielding s''', the result of the computation.

There's a lot of moving parts here, and I feel as if the correct approach would be to build this on top of the StateT transformer or the State monad, however I can't figure out where to start.

I feel as if this isn't terribly clear. Any clarifications that would make this clearer are much appreciated.

Was it helpful?

Solution

I don't think you can make the monad you're asking for. As I was mentioning in my discussion with jozefg, we have two monad laws that say

f >=> return = f
return >=> f = f

which means that nothing "interesting" can happen at a binding location. In particular, we can't run a state-transition function at each binding, because then f >=> return will run that transition function and f won't, and these laws will be broken.

However, that doesn't stop us from making a monadic action that runs the state transitions on our behalf. So I'll sketch the idea for how to design a monad that tracks such transitions and runs them on demand. You'll surely need to flesh out the API some if you want it to be useful. The basic idea is that instead of just an s as state, we'll store both an s and a transition table. First, some boilerplate.

{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
import Control.Arrow
import Control.Applicative
import Control.Monad.State

For now, let's just work with s -> s transitions. You can implement them however you like -- including looking in a list of predicates and transitions and picking out the ones you want to run, if that's your cup of tea. But that's orthogonal to getting the rest of the idea right. We'll define our new type and give it a Monad instance that just dispatches to the underlying type.

newtype TStateT s m a = TStateT { unTStateT :: StateT (s, s -> s) m a }
    deriving (Functor, Applicative, Monad)

The MonadState instance is a bit trickier than just using deriving, but still pretty straightforward. Presumably publically we want to pretend that only s is part of the state, so we need to focus our attention a bit. We'll also give the runStateT analog, and pick a sane initial transition function. (We'll give a way to modify this choice later.)

instance Monad m => MonadState s (TStateT s m) where
    state f = TStateT (state (\(s, t) -> let (v, s') = f s in (v, (s', t))))

runTStateT :: Functor m => TStateT s m a -> s -> m (a, s)
runTStateT m s = second fst <$> runStateT (unTStateT m) (s, id)

Now comes the interesting bit. The superpower of TStateT is that it has some transitions it can run at any time. So let's provide a way to run them and a way to modify the transition table.

step :: Monad m => TStateT s m ()
step = TStateT (gets snd) >>= modify

modifyTransitions :: Monad m => ((s -> s) -> (s -> s)) -> TStateT s m ()
modifyTransitions = TStateT . modify . second

And that's pretty much everything!

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top