[Haskell-cafe] Stacking StateTs

David Menendez dave at zednenem.com
Sat Feb 21 18:37:36 EST 2009


On Sat, Feb 21, 2009 at 3:33 PM, Luis O'Shea <loshea at gmail.com> wrote:
> I've been experimenting with the state monad and with StateT, and have some
> questions about how to combine one state with another.

<snip>

>> test3 :: Monad m => String -> StateT Integer m String
>> test3 s = do
>>   modify (+ 1)
>>   a <- get
>>   return $ s ++ (show a)

A style point: It's often better to specify what operations test3
uses, rather than requiring a specific family of monads.

test3 :: MonadState Integer m => String -> m String

> Now seeing as test3 takes a String and returns another String you can
> imagine using it to transform a String state.  (I'm also going to assume
> that test3 is in another library so we don't want to alter how it's
> written.)  So here is how you could use test3 in a computation that has
> (String,Integer) as its state:
>
>> test5 :: (Monad m) => m Integer
>> test5 = do
>>   (s1,x1) <- runStateT (test3 "") 0
>>   (s2,x2) <- runStateT (test3 s1) (2*x1 + 1)
>>   (s3,x3) <- runStateT (test3 s2) (x2*x2)
>>   return x3

You don't really need to jump all the way out of the state
transformer. Something like this would work just as well:

test5a = flip execStateT 0 $ do
    s1 <- test3 ""
    modify $ \x -> 2 * x + 1
    s2 <- test3 s1
    modify $ \x -> x * x
    test3 s2

Contrast this with your test6.

Now, if you want to avoid passing the strings around explicitly, you
could add another state transformer. For example, we could layer a
String transformer on top of the underlying monad with this fairly
general combinator:

modifyM :: (Monad m) => (s -> m s) -> StateT s m ()
modifyM f = StateT $ \s -> f s >>= \s' -> return ((),s')

test5b = flip execStateT 0 . flip evalStateT "" $ do
    modifyM test3
    lift $ modify $ \x -> 2 * x + 1
    modifyM test3
    lift $ modify $ \x -> x * x
    modifyM test3

Note that modifyM works on the top-level state, whereas lift . modify
works on the inner state.

Or, you can put the state transformer on the bottom by taking
advantage of the fact that test3 is polymorphic in any underlying
monad.

test3' = lift get >>= test3 >>= lift . put   -- this is essentially
modifyT test3

test5c = flip evalState "" . flip execStateT 0 $ do
    test3'
    modify $ \x -> 2*x+1
    test3'
    modify $ \x -> x * x
    test3'

But this only really makes sense if you expect the String state to
last at least as long as the Integer state.

Of my three alternatives, test5a actually seems the most idiomatic to
me, followed by test5b and then test5c. It's possible to write test5a
in a way that avoids explicitly passing the strings around, but the
result doesn't end up looking much better.


PS. Here are two functions that I ended up not using in my examples,
but which may come in handy when dealing with nested applications of
StateT:

curryStateT :: (Monad m) => StateT (s,t) m a -> StateT s (StateT t m) a
curryStateT m = StateT $ \s -> StateT $ \t ->
	runStateT m (s,t) >>= \ ~(a,(s,t)) -> return ((a,s),t)

uncurryStateT :: (Monad m) => StateT s (StateT t m) a -> StateT (s,t) m a
uncurryStateT m = StateT $ \ ~(s,t) ->
	runStateT (runStateT m s) t >>= \ ~((a,s),t) -> return (a,(s,t))

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list