adding state handing to existing code

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

Hello Scott Here's the "simplest solution" I can come up with. It uses literate Haskell (code lines begin with >) - rather than normal Haskell. It means I can check the code as I write it rather than post rubbish. Copy pate it into a file with .lhs as the extension or remove the > and first space.
{-# LANGUAGE FlexibleContexts #-}
module UseState where
import Control.Monad.State import Text.Printf
process :: Integer -> Integer -> StateT Integer IO Integer process x y = do s <- get put $ s + 1 return $ 2 * x * y
doit :: StateT Integer IO () doit = do ans <- process 42 43 liftIO $ printf "f x y = %d\n" ans
main :: IO () main = do runStateT doit 0 putStrLn "done"
Now I wouldn't argue that this simple solution is particularly simple - its merit is only that it is the closest I could get to your original. Because 'process' is now a monadic function 'doit' has to change - it can't apply printf "..." to process 42 43 anymore, instead it has to bind the result of process 42 43 to the temporary variable 'ans' and use that (there are ways to avoid using temporary bindings but for the moment they would make things more complicated). Also 'printf' is in the IO monad - and whereas 'process' is "in" the state monad. To use one monad within another, you need one monad to be the base monad and one monad to be a transformer. Here IO is the base monad and State is the transformer (IO is special it can only be a base monad and never a transformer). Because the State monad is now a transformer I had to use the StateT transformer version rather than the regular State version - that's why I used the exaggerated quotes for '"in" the state monad' above. To use 'printf' you have to lift it from the base monad so it can be used within the transformer monad - hence the prefix of 'liftIO' to the call to 'printf'. As the code now uses the transformer version of the state monad, this mandates a change to 'process' as well as its type needs to be compatible with the transformer+base monad rather than the previous State monad. All in all there are quite a lot of changes to do something that superficially at least should seem simple to do. If there's an ah-ha moment its probably more anticipating want effects (state, error handling, logging - writer monad, reader monad for a read-only 'environment' - e.g. configuration data, ...) you want the monad to have. Taking pure code to monadic code is a burden, but adding another effect to monadic code is much less so (though again IO is a bit of a problem as it can only be a base monad and operations from IO must always be lifted with 'liftIO' other monads use plain 'lift'). Some things you can do to minimise later changes are define an alias for your monad, e.g:
type PMonad ans = StateT Integer IO ans
processP :: Integer -> Integer -> PMonad Integer processP x y = do s <- get put $ s + 1 return $ 2 * x * y
doitP :: PMonad () doitP = do ans <- processP 42 43 liftIO $ printf "f x y = %d\n" ans
main_alt :: IO () main_alt = do runStateT doitP 0 putStrLn "done"
A better idiom - more flexible, but more abstract - is rather than have your monadic operations depend on a concrete monad, is to make them depend on a monad transformers signature (for instance the state transformer has the corresponding type class MonadState for its signature):
processAbstract :: MonadState Integer m => Integer -> Integer -> m Integer processAbstract x y = do s <- get put $ s + 1 return $ 2 * x * y
Best wishes Stephen

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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thank you guys very much for the quick responses. This is very useful
info and I've definitely got more reading and learning to do - in
particular, the whole lifting/transforming/stacking monads area. Part
of this exercise of learning Haskell is learning how to do things with
a pure functional approach and so I'm thinking about things that might
happen while building and maintaining software. In this scenario I
was imagining that the "doit" function was something over which I
might not have control. I like the idea that you can't just jam state
into the code without the type system, and everyone involved, knowing
about it. So my question is now evolving into looking at it the other
way around - from the designer of "doit".
If I were designing something, for a very simple example, like the map
function but maybe over some custom sequence-like thing, how could I
make it so that the user-supplied function could be monadic/stateful
or not? Is there a way to make the map function flexible enough so
that the author of the function argument could make it stateful or
pure without any control over the definition of map itself?
That question doesn't really need an answer that just my reasoning at
this point - one of those "what if I had written software with Haskell
and a high priority requirement came along, how would I handle it"
kind of questions. It's an interesting exercise to think about
applying a purely functional approach to something might happen in day
to day development.
-stt
On Sun, Jan 24, 2010 at 4:11 PM, Stephen Blackheath [to
Haskell-Beginners]
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

2010/1/25 Scott Thoman
If I were designing something, for a very simple example, like the map function but maybe over some custom sequence-like thing, how could I make it so that the user-supplied function could be monadic/stateful or not? Is there a way to make the map function flexible enough so that the author of the function argument could make it stateful or pure without any control over the definition of map itself?
Hi Scott [Not quite answering your question directly, but...] There are monadic versions of the usual 'functionals' map fold - mapM, foldM. etc If you don't need to consider other monadic effects (eg. exceptions) and only need state, some of the common higher order functions are 'stateful'. 'unfoldr' is the most obvious one. 'unfoldr' passes a state though each recursive step. At each step the 'user function' looks at the state and decides whether to produce both a new value and a new state or terminate the computation. foldr, and foldl too can be seen as stateful. One way to think about folds (on lists) is that they reduce the list to a summary value, the summary value is effectively state. If you want to have 'user state' and still produce a summary value you can pass a pair to the fold partitioning the user state and summary value. mapAccumL and mapAccumR from Data.List are variations on this theme - they combine fold and map, passing an accumulating parameter (a.k.a. the user state) through the list traversal returning both the new list and the state. The unfold version of mapAccumL unfortunately isn't in the standard library, it lets you traverse the list statefully but has the additional very useful property that you can escape the traversal before the end of the list. Here's the definition I use: -- | @unfoldMap@ is the unfold analogue of accumMapL. -- We can signal exhaustion early by the Maybe type. unfoldMap :: (a -> st -> Maybe (b,st)) -> st -> [a] -> ([b],st) unfoldMap _ s0 [] = ([],s0) unfoldMap f s0 (x:xs) = case (f x s0) of Nothing -> ([],s0) Just (a,st) -> (a:as,b) where (as,b) = unfoldMap f st xs Best wishes Stephen

Scott, Generally your code is either written to be monadic or pure, but "monadic" can be more or less specific depending on what typeclass is used to say it's monadic. The most general is Monad m =>. Here's a design where I've encountered this situation, which I think might shed some light on the question: I did a web form editor for server-side web applications. The whole thing was pure, but I realized I had a problem: validators could not access the database. The thing to do in this situation is to make the type something like: processForm :: Monad m => Form m -> m Result where 'Form m' can contain validators with a return type 'm (Either String a)' in which validation errors are expressed as, e.g. Left "Value must be positive!" The logic of processForm can be as complex as you like, and written completely purely (the generalness of the type Monad m => constrains the logic of processForm to be pure), but validators that are passed in as arguments can be any monad that the caller wants, e.g. able to access the database. If a particular caller only uses pure validators, processForm can be 'run' in the Identity monad. Using typeclasses, the validators themselves can be expressed with capabilities, e.g. validateKeyExists :: ReadableDatabase m => ...something... -> m (Either String a) This might mean that it can only read from the database, not write. Then the whole thing would only typecheck if processForm was sequenced in a monad that gave (at least) read access to the database. Steve Scott Thoman wrote:
Thank you guys very much for the quick responses. This is very useful info and I've definitely got more reading and learning to do - in particular, the whole lifting/transforming/stacking monads area. Part of this exercise of learning Haskell is learning how to do things with a pure functional approach and so I'm thinking about things that might happen while building and maintaining software. In this scenario I was imagining that the "doit" function was something over which I might not have control. I like the idea that you can't just jam state into the code without the type system, and everyone involved, knowing about it. So my question is now evolving into looking at it the other way around - from the designer of "doit".
If I were designing something, for a very simple example, like the map function but maybe over some custom sequence-like thing, how could I make it so that the user-supplied function could be monadic/stateful or not? Is there a way to make the map function flexible enough so that the author of the function argument could make it stateful or pure without any control over the definition of map itself?
That question doesn't really need an answer that just my reasoning at this point - one of those "what if I had written software with Haskell and a high priority requirement came along, how would I handle it" kind of questions. It's an interesting exercise to think about applying a purely functional approach to something might happen in day to day development.
-stt
On Sun, Jan 24, 2010 at 4:11 PM, Stephen Blackheath [to Haskell-Beginners]
wrote: 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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Now that sounds like what i was imagining too where processForm is
"prepared" to handle the case where the user wants monadic stuff but
can deal with the case where they're pure too - leaving processForm
pure and unchanged.
There sure is a lot to learn with this Haskell stuff.
-stt
On Mon, Jan 25, 2010 at 4:18 PM, Stephen Blackheath [to
Haskell-Beginners]
Scott,
Generally your code is either written to be monadic or pure, but "monadic" can be more or less specific depending on what typeclass is used to say it's monadic. The most general is Monad m =>.
Here's a design where I've encountered this situation, which I think might shed some light on the question: I did a web form editor for server-side web applications. The whole thing was pure, but I realized I had a problem: validators could not access the database.
The thing to do in this situation is to make the type something like:
processForm :: Monad m => Form m -> m Result
where 'Form m' can contain validators with a return type 'm (Either String a)' in which validation errors are expressed as, e.g. Left "Value must be positive!"
The logic of processForm can be as complex as you like, and written completely purely (the generalness of the type Monad m => constrains the logic of processForm to be pure), but validators that are passed in as arguments can be any monad that the caller wants, e.g. able to access the database. If a particular caller only uses pure validators, processForm can be 'run' in the Identity monad.
Using typeclasses, the validators themselves can be expressed with capabilities, e.g. validateKeyExists :: ReadableDatabase m => ...something... -> m (Either String a)
This might mean that it can only read from the database, not write. Then the whole thing would only typecheck if processForm was sequenced in a monad that gave (at least) read access to the database.
Steve
Scott Thoman wrote:
Thank you guys very much for the quick responses. This is very useful info and I've definitely got more reading and learning to do - in particular, the whole lifting/transforming/stacking monads area. Part of this exercise of learning Haskell is learning how to do things with a pure functional approach and so I'm thinking about things that might happen while building and maintaining software. In this scenario I was imagining that the "doit" function was something over which I might not have control. I like the idea that you can't just jam state into the code without the type system, and everyone involved, knowing about it. So my question is now evolving into looking at it the other way around - from the designer of "doit".
If I were designing something, for a very simple example, like the map function but maybe over some custom sequence-like thing, how could I make it so that the user-supplied function could be monadic/stateful or not? Is there a way to make the map function flexible enough so that the author of the function argument could make it stateful or pure without any control over the definition of map itself?
That question doesn't really need an answer that just my reasoning at this point - one of those "what if I had written software with Haskell and a high priority requirement came along, how would I handle it" kind of questions. It's an interesting exercise to think about applying a purely functional approach to something might happen in day to day development.
-stt
On Sun, Jan 24, 2010 at 4:11 PM, Stephen Blackheath [to Haskell-Beginners]
wrote: 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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- "Very well, then, Mr. Knox, sir. Let's have a little talk about tweetle beetles...." - Dr. S.
participants (3)
-
Scott Thoman
-
Stephen Blackheath [to Haskell-Beginners]
-
Stephen Tetley