
Hi, My application has to manage a data set. I assume the state monad is designed for this. The state changes in functions that: a. perform IO actions and b. return execution status and execution trace (right now I'm using WriteT for this). Is the best solution: 1. to build a monad stack (for example State -> Writer -> IO) or 2. to use IORef for the data set or 3. something else? Are monad stacks with 3 and more monads common? How could an example implementation look like? What I have for now is: -- Status data Status = OK | FAILED deriving (Show, Read, Enum) -- Example data set manages by state type Config = [String] -- WriterT transformer type OutputWriter = WriterT [String] IO Status -- example execute function execute :: [String] -> OutputWriter execute fs = do rs <- liftIO loadData fs tell $ map show rs return OK -- run it inside e.g. main (s, os) <- runWriterT $ execute files How do I bring a state into this, for example for: execute fs = do ?? conf <- get ?? -- get Config from state rs <- liftIO loadData conf fs ?? set conf ?? -- change Config and set to state tell "new state:" tell $ show conf return OK Do I have to use and how do I use StateT in this context: data DataState = StateT Config OutputWriter ?? and how do I run it runStateT . runWriterT? Thanks for help, Adam

On 29 Jan 2008, at 9:44 PM, Adam Smyczek wrote:
Hi,
My application has to manage a data set. I assume the state monad is designed for this. The state changes in functions that: a. perform IO actions and b. return execution status and execution trace (right now I'm using WriteT for this).
Is the best solution: 1. to build a monad stack (for example State -> Writer -> IO) or 2. to use IORef for the data set or 3. something else?
Are monad stacks with 3 and more monads common?
I'd say they're fairly common, yes; at least, they don't jump out at me as bad style (especially when the monads are fairly orthogonal, as here).
How could an example implementation look like?
newtype Program alpha = Program { runProgram :: StateT Config (WriterT [String] IO) alpha } deriving (Functor, Monad, MonadWriter, MonadState)
What I have for now is:
-- Status data Status = OK | FAILED deriving (Show, Read, Enum)
-- Example data set manages by state type Config = [String]
-- WriterT transformer type OutputWriter = WriterT [String] IO Status
-- example execute function execute :: [String] -> OutputWriter
execute :: [String] -> Program Status
execute fs = do rs <- liftIO loadData fs tell $ map show rs return OK
-- run it inside e.g. main (s, os) <- runWriterT $ execute files
(s', (s, os)) <- runWriterT (runStateT (runProgram $ execute files) inputstate) It's a bit tricky, since you have to write it inside-out, but it should only type check if you've got it right :)
How do I bring a state into this, for example for: execute fs = do ?? conf <- get ?? -- get Config from state
Right.
rs <- liftIO loadData conf fs ?? set conf ?? -- change Config and set to state
Right.
tell "new state:"
Right.
tell $ show conf return OK
Do I have to use
Depends on what you mean by `have to'. If you don't want to thread the state yourself, and you don't want to use an IORef, you'll need some implementation of a state monad. That will have to be in the form of a monad transformer applied to IO, so the easy answer is `yes'.
and how do I use StateT in this context: data DataState = StateT Config OutputWriter ??
This is parenthesized wrong; the output type goes outside the parentheses around WriterT: StateT Config (WriterT [String] IO) Status not StateT Config (WriterT [String] IO Status)
and how do I run it runStateT . runWriterT?
Other way 'round, as above. HTH jcc

It works like a charm, thanks a lot Jonathan! Adam On Jan 29, 2008, at 10:26 PM, Jonathan Cast wrote:
On 29 Jan 2008, at 9:44 PM, Adam Smyczek wrote:
Hi,
My application has to manage a data set. I assume the state monad is designed for this. The state changes in functions that: a. perform IO actions and b. return execution status and execution trace (right now I'm using WriteT for this).
Is the best solution: 1. to build a monad stack (for example State -> Writer -> IO) or 2. to use IORef for the data set or 3. something else?
Are monad stacks with 3 and more monads common?
I'd say they're fairly common, yes; at least, they don't jump out at me as bad style (especially when the monads are fairly orthogonal, as here).
How could an example implementation look like?
newtype Program alpha = Program { runProgram :: StateT Config (WriterT [String] IO) alpha } deriving (Functor, Monad, MonadWriter, MonadState)
What I have for now is:
-- Status data Status = OK | FAILED deriving (Show, Read, Enum)
-- Example data set manages by state type Config = [String]
-- WriterT transformer type OutputWriter = WriterT [String] IO Status
-- example execute function execute :: [String] -> OutputWriter
execute :: [String] -> Program Status
execute fs = do rs <- liftIO loadData fs tell $ map show rs return OK
-- run it inside e.g. main (s, os) <- runWriterT $ execute files
(s', (s, os)) <- runWriterT (runStateT (runProgram $ execute files) inputstate)
It's a bit tricky, since you have to write it inside-out, but it should only type check if you've got it right :)
How do I bring a state into this, for example for: execute fs = do ?? conf <- get ?? -- get Config from state
Right.
rs <- liftIO loadData conf fs ?? set conf ?? -- change Config and set to state
Right.
tell "new state:"
Right.
tell $ show conf return OK
Do I have to use
Depends on what you mean by `have to'. If you don't want to thread the state yourself, and you don't want to use an IORef, you'll need some implementation of a state monad. That will have to be in the form of a monad transformer applied to IO, so the easy answer is `yes'.
and how do I use StateT in this context: data DataState = StateT Config OutputWriter ??
This is parenthesized wrong; the output type goes outside the parentheses around WriterT:
StateT Config (WriterT [String] IO) Status
not
StateT Config (WriterT [String] IO Status)
and how do I run it runStateT . runWriterT?
Other way 'round, as above.
HTH
jcc

Are monad stacks with 3 and more monads common? How could an example implementation look like?
I found reading the xmonad code (http://code.haskell.org/xmonad/) enlightening. The X monad definition can be found in http://code.haskell.org/xmonad/XMonad/Core.hs -- | The X monad, a StateT transformer over IO encapsulating the window -- manager state -- -- Dynamic components may be retrieved with 'get', static components -- with 'ask'. With newtype deriving we get readers and state monads -- instantiated on XConf and XState automatically. -- newtype X a = X (ReaderT XConf (StateT XState IO) a) deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf) -- Johan

On Jan 30, 2008 12:44 AM, Adam Smyczek
Hi,
My application has to manage a data set. I assume the state monad is designed for this. The state changes in functions that: a. perform IO actions and b. return execution status and execution trace (right now I'm using WriteT for this).
Is the best solution: 1. to build a monad stack (for example State -> Writer -> IO) or 2. to use IORef for the data set or 3. something else?
Are monad stacks with 3 and more monads common? How could an example implementation look like?
Hi Adam, Indeed, this is quite common. You may be interested in reading http://cale.yi.org/index.php/How_To_Use_Monad_Transformers Good luck! -Brent
participants (4)
-
Adam Smyczek
-
Brent Yorgey
-
Johan Tibell
-
Jonathan Cast