
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