[Haskell-beginners] adding state handing to existing code

Stephen Blackheath [to Haskell-Beginners] mutilating.cauliflowers.stephen at blacksapphire.com
Sun Jan 24 16:11:48 EST 2010


Scott,

Here's the most straightforward way to do it:

--
process ::  Integer -> Integer -> StateT Int IO Integer
process x y = do
    s <- get
    put $ s + 1
    return $ 2 * x * y

doit :: StateT Int IO ()
doit = do
    p <- process 42 43
    liftIO $ printf "f x y = %d\n" p

main :: IO ()
main = do
    n <- execStateT doit 0
    putStrLn $ "done "++show n++" times"
--

One thing you'll note is that the type of 'doit' has changed.  There's
no way to pass state "through" a function without it being reflected in
the type, and in many ways, that's the point of Haskell - to make
potentially dangerous things explicit.  An alternative is to use an
IORef, but that makes your code completely imperative style, which is
not very Haskellish.

One thing you'll notice is that process is now in IO, which is not
desirable, since it's pure.  On occasions I've written this helper function:

-- | Adapt a StateT to a pure state monad.
purely :: Monad m => State s a -> StateT s m a
purely code = do
    s <- get
    let (ret, s') = runState code s
    put s'
    return ret

With this you could re-write it as...

--
process ::  Integer -> Integer -> State Int Integer
process x y = do
    s <- get
    put $ s + 1
    return $ 2 * x * y

doit :: StateT Int IO ()
doit = do
    p <- purely $ process 42 43
    liftIO $ printf "f x y = %d\n" p
--

Monad transformer stacks aren't perfect, but they're good if used
appropriately.  If you use them a lot, then it can lead to a necessity
to unstack and re-stack them like I did here.  I think monads work best
if you initially think of your code in plain Haskell terms, and
introduce them later as a convenience.

As I'm sure you know, the "Haskell way" is to make code as pure as
possible, using IO types only where necessary.


Steve

Scott Thoman wrote:
> Since I'm very new to Haskell I have what is probably a simple
> question yet I'm having trouble finding a clear example of how it
> works.  The basic question is: how do I pass state through existing
> code without the intermediate code knowing about it.  If I have, for
> example, several layers of function calls and the innermost function
> needs to access some state that is only "seeded" by the outermost
> function, how do I do that without the functions in between knowing
> about the additional state being threaded through them?
> 
> I have a simple example (that may *not* be good idiomatic Haskell):
> 
> --
> process ::  Integer -> Integer -> Integer
> process x y =
>     2 * x * y
> 
> doit :: IO ()
> doit = do
>     printf "f x y = %d\n" $ process 42 43
> 
> main :: IO ()
> main = do
>     doit
>     putStrLn "done"
> --
> 
> (I'm not totally sure about the type of "doit" but the code compiles
> and runs as expected)
> 
> What I want to do is add some state handing to "process" to have it,
> say, count the number of times it's been called (putting
> threading/thread-local concerns aside for the moment).  I'm trying to
> understand how to add state to "process" along the lines of:
> 
> --
> process ::  Integer -> Integer -> State Integer Integer
> process x y = do
>     s <- get
>     put $ s + 1
>     return $ 2 * x * y
> --
> 
> but I want to only seed the state from "main" without "doit" having to
> change -- I can call "process" from "doit" like "(execState (process
> 42 43) 0)" but I want the initial state to be determined at the top
> level, from main.
> 
> I have a feeling there's some kind of "ah ha" moment that I'm just not
> seeing yet.  Any help or pointers to where I can look for myself would
> be greatly appreciated.
> 
> Thanks in advance,
> 
> -thor
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 


More information about the Beginners mailing list