I've been experimenting with the state monad and with StateT, and have some questions about how to combine one state with another.

This email is literate Haskell tested on GHCi, version 6.10.1. Also, sigfpe's post on monad transformers (http://blog.sigfpe.com/2006/05/ grok-haskell-monad-transformers.html) was very helpful.

> import Control.Monad.State

My question is basically whether the function modifyT (below) makes sense, whether some form of it already exists in a standard library, and (most importantly) whether it actually indicates that I'm thinking about StateT all wrong.

> modifyT :: Monad m =>
>            (s -> StateT t m s)
>         -> StateT t (StateT s m) ()
> modifyT f = do
>     x <- get
>     y <- lift get
>     (y',x') <- lift $ lift $ runStateT (f y) x
>     lift $ put y'
>     put x'

Some context may be useful, so here is how I ended up thinking I needed modifyT.

The state monad makes it easy to write stateful computations. For example here is a computation that has an Integer as its state and returns a String:

> test1 :: State Integer String
> test1 = do
>   modify (+ 1)
>   a <- get
>   return $ "foobar" ++ (show a)

If the computation wants to do some IO then it makes sense to start with the IO monad and then apply the StateT transformer to it:

> test2 :: StateT Integer IO String
> test2 = do
>   modify (+ 1)
>   a <- get
>   lift $ print a
>   return $ "foobar" ++ (show a)

So from now on I won't actually do any IO and will replace IO with an arbitrary monad m. Also instead of the fixed string "foobar" I'll have it take a String as a parameter:

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

A nice feature of all this is that it is easy to combine these computations:

> test4 :: Monad m => StateT Integer m (String,String)
> test4 = do
>   s1 <- test3 "foo"
>   s2 <- test3 "bar"
>   return $ (s1,s2)

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

Then running test5 >>= print gives 17. The problem with test5, of course, is that we have manually threaded the state, with all the problems that implies. For example nothing prevents you from erroneously misthreading the state:

> test5bad :: (Monad m) => m Integer
> test5bad = do
>     (s1,x1) <- runStateT (test3 "") 0
>     (s2,x2) <- runStateT (test3 s1) (2*x1 + 1)
>     (s3,x3) <- runStateT (test3 s1) (x2*x1)
>     return x3

Running test5bad >>= print gives 5. Obviously we want operate in a State monad with more state. One way to do this is to stack two StateTs on top of m. This is, finally, where I need the modifyT that we defined above -- it lets us "lift" test3 to a function that modifies the state of the top *two* StateTs. Now let's use it to rewrite test5:

> test6 :: (Monad m) => StateT Integer (StateT String m) Integer
> test6 = do
>   modifyT test3
>   modify $ \x -> 2*x + 1
>   modifyT test3
>   modify $ \x -> x*x
>   modifyT test3
>   x <- get
>   return x
>
> test7 :: (Monad m) => m Integer
> test7  = evalStateT (evalStateT test6 0) ""

As expected, running test7 >>= print gives 17.

So, given that modifyT seems to be useful, does it, or something like it, already exists in the standard libraries? More likely, am I making a mountain of a molehill and is there a better way to structure all this?

Thanks,

Luis

> main = do
>   test5 >>= print
>   test5bad >>= print
>   test7 >>= print

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to