Count with Writer asynchronously

Hello, Dear List! There is package `async` (https://hackage.haskell.org/package/async-2.1.1.1/docs/Control-Concurrent-As...). Before, I had: import qualified Control.Concurent.Async as A ... runIt :: ... -> IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait But now I want to count something inside `runIt`. I will use `Writer` monad for it (sure, it can be `State` also, not in principle to me). To do it synchronously, I done: module Main where import Control.Monad.Trans.Writer import Control.Monad.IO.Class import Data.Monoid runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something liftIO $ print x main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- runWriterT $ sequence [runIt w i | i <- l] print $ snd z but now my `runIt` changes it's signature: runIt :: Num a => WriterT (Sum a) IO () -> ... -> WriterT (Sum a) IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait ^^^^^^^^^^^ ` ERROR is here! I get the error because `async`::IO () -> IO (A.Async ()) but I'm trying to pass it `WriterT (Sum a) IO ()`! To fix it I added `runWriterT` there: res <- sequence [A.async $ runWriterT (runIt ...) ...] >>= mapM A.wait but now I will get list of counters, not one (res::[((), Sum Int)])! How to solve this problem: to run several actions asyncronously and to count something inside the action with `Writer` monad? === Best regards, Paul

Firstly, a direct answer to your question: use mconcat.
main :: IO ()
main = do
let l = [1,2,3,4]
w = writer ((), 0) :: WriterT (Sum Int) IO ()
z <- sequence
(map (A.async . runWriterT . runIt w) l)
>>= mapM A.wait
print $ snd $ mconcat z
Under the surface, WriterT is using mappend to combine the `Sum` values
anyway, so it's natural is `mconcat` (the version of mappend that applies
to list) to get the same result. Now some possible improvements.
You're not actually using the return value from the `runIt` call, just the
writer value. There's a function called `execWriter` for this:
z <- sequence
(map (A.async . execWriterT . runIt w) l)
>>= mapM A.wait
print $ mconcat z
Next, the combination of map and sequence can be written as traverse:
z <- traverse (A.async . execWriterT . runIt w) l
>>= mapM A.wait
But the async library is cool enough that it provides a function called
mapConcurrently that deals with the async/wait dance for you:
main :: IO ()
main = do
let l = [1,2,3,4]
w = writer ((), 0) :: WriterT (Sum Int) IO ()
z <- A.mapConcurrently (execWriterT . runIt w) l
print $ mconcat z
One final note: usage of `print` like this in a concurrent context can run
into interleaved output if you have the wrong buffer mode turned out,
leading to output like this:
2
3
41
This is especially common when using runghc or ghci. You can either change
the buffering mode or use a different output function like sayShow (from
the say package, which I wrote):
module Main where
import qualified Control.Concurrent.Async as A
import Control.Monad.Trans.Writer
import Data.Monoid
import Say
runIt :: (Show a, Num a)
=> WriterT (Sum a) IO ()
-> a
-> WriterT (Sum a) IO ()
runIt w x = do
censor (+1) w -- emulates conditional count of something
sayShow x
main :: IO ()
main = do
let l = [1,2,3,4]
w = writer ((), 0) :: WriterT (Sum Int) IO ()
z <- A.mapConcurrently (execWriterT . runIt w) l
sayShow $ mconcat z
On Tue, Jul 25, 2017 at 11:36 AM, Baa
Hello, Dear List!
There is package `async` (https://hackage.haskell.org/package/async-2.1.1.1/docs/ Control-Concurrent-Async.html).
Before, I had:
import qualified Control.Concurent.Async as A ... runIt :: ... -> IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait
But now I want to count something inside `runIt`. I will use `Writer` monad for it (sure, it can be `State` also, not in principle to me). To do it synchronously, I done:
module Main where
import Control.Monad.Trans.Writer import Control.Monad.IO.Class import Data.Monoid
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something liftIO $ print x
main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- runWriterT $ sequence [runIt w i | i <- l] print $ snd z
but now my `runIt` changes it's signature:
runIt :: Num a => WriterT (Sum a) IO () -> ... -> WriterT (Sum a) IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait ^^^^^^^^^^^ ` ERROR is here!
I get the error because `async`::IO () -> IO (A.Async ()) but I'm trying to pass it `WriterT (Sum a) IO ()`!
To fix it I added `runWriterT` there:
res <- sequence [A.async $ runWriterT (runIt ...) ...] >>= mapM A.wait
but now I will get list of counters, not one (res::[((), Sum Int)])!
How to solve this problem: to run several actions asyncronously and to count something inside the action with `Writer` monad?
=== Best regards, Paul _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello, Michael! This answers to my question completely, thank you so
much!
But looking at this code, I thought: how is it right to wrap/unwrap
write monad? In languages like C or Python we can pass input/output
argument (`int*` in C or `[0]` in Python) and use it as some
accumulator. But here writer monad is not using as accumulator,
accumulating (summation) happens in `mconcat`, right? It's using only
as output value, i.e. place to "yield" result. I mean `w` is 0, each
call of `runIt` sets there 1, after all calls we calculate sum of this
1's. And instead of `censor (+1) w` I can do `tell 1` only.
It means that `runIt` can return not `IO ()` but `IO Int` and results
of all `runIt`'s asynchnronously gotten values can be accumulated with
`mconcat` without using of writer monad. Am I right, writer monad here
is not accumulator but only output value (like output arguments in
C/C++/IDL/etc)? How is this a typical solution in Haskell - to use
writer monad with wrap/unwrap multiple times, only to save output
value?
On Tue, 25 Jul 2017 12:31:56 +0300
Michael Snoyman
Firstly, a direct answer to your question: use mconcat.
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- sequence (map (A.async . runWriterT . runIt w) l) >>= mapM A.wait print $ snd $ mconcat z
Under the surface, WriterT is using mappend to combine the `Sum` values anyway, so it's natural is `mconcat` (the version of mappend that applies to list) to get the same result. Now some possible improvements.
You're not actually using the return value from the `runIt` call, just the writer value. There's a function called `execWriter` for this:
z <- sequence (map (A.async . execWriterT . runIt w) l) >>= mapM A.wait print $ mconcat z
Next, the combination of map and sequence can be written as traverse:
z <- traverse (A.async . execWriterT . runIt w) l >>= mapM A.wait
But the async library is cool enough that it provides a function called mapConcurrently that deals with the async/wait dance for you:
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l print $ mconcat z
One final note: usage of `print` like this in a concurrent context can run into interleaved output if you have the wrong buffer mode turned out, leading to output like this:
2 3 41
This is especially common when using runghc or ghci. You can either change the buffering mode or use a different output function like sayShow (from the say package, which I wrote):
module Main where
import qualified Control.Concurrent.Async as A import Control.Monad.Trans.Writer import Data.Monoid import Say
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something sayShow x
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l sayShow $ mconcat z
On Tue, Jul 25, 2017 at 11:36 AM, Baa
wrote: Hello, Dear List!
There is package `async` (https://hackage.haskell.org/package/async-2.1.1.1/docs/ Control-Concurrent-Async.html).
Before, I had:
import qualified Control.Concurent.Async as A ... runIt :: ... -> IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait
But now I want to count something inside `runIt`. I will use `Writer` monad for it (sure, it can be `State` also, not in principle to me). To do it synchronously, I done:
module Main where
import Control.Monad.Trans.Writer import Control.Monad.IO.Class import Data.Monoid
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something liftIO $ print x
main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- runWriterT $ sequence [runIt w i | i <- l] print $ snd z
but now my `runIt` changes it's signature:
runIt :: Num a => WriterT (Sum a) IO () -> ... -> WriterT (Sum a) IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait ^^^^^^^^^^^ ` ERROR is here!
I get the error because `async`::IO () -> IO (A.Async ()) but I'm trying to pass it `WriterT (Sum a) IO ()`!
To fix it I added `runWriterT` there:
res <- sequence [A.async $ runWriterT (runIt ...) ...] >>= mapM A.wait
but now I will get list of counters, not one (res::[((), Sum Int)])!
How to solve this problem: to run several actions asyncronously and to count something inside the action with `Writer` monad?
=== Best regards, Paul _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

You're asking very good questions, about a topic I considered bringing up
in my previous response but didn't. I guess I will now :)
The important thing to realize about monad transformers (and monads in
general) is that _they're nothing special_. Under the surface, WriterT is
simply:
* Modifying your functions to have an extra value returned
* Providing convenience functions like `tell` and `liftIO` to work with
that extra value
I would strongly advise getting used to writing code in both the
transformer and non-transformer style to convince yourself that they are
the same thing. To make this concrete, look at the WriterT definition:
newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }
If you take away the newtype wrapping business, you can see that it's just
saying `WriterT w m a = m (a, w)`. And therefore, if we go back to your
types, we can replace:
WriterT (Sum a) IO ()
with
IO ((), Sum a)
In fact, that's exactly what `runWriterT` is doing. I would recommend
trying to rewrite your code to not even bother with the `WriterT` at all
and see if you can get the same output.
So your intuition is correct: there's no output parameter like in C. You
could simulate that in Haskell by passing in a mutable variable (like an
IORef), but that's not idiomatic. Passing back pairs of values is common in
Haskell.
Transformers can be useful for avoiding a lot of boilerplate code. They can
also introduce a lot of complexity in some cases. Figuring out when is the
right time to use them and when not is subjective and nuanced. Knowing the
skill is great; being able to avoid using the skill is also important :)
On Tue, Jul 25, 2017 at 1:29 PM, Baa
Hello, Michael! This answers to my question completely, thank you so much!
But looking at this code, I thought: how is it right to wrap/unwrap write monad? In languages like C or Python we can pass input/output argument (`int*` in C or `[0]` in Python) and use it as some accumulator. But here writer monad is not using as accumulator, accumulating (summation) happens in `mconcat`, right? It's using only as output value, i.e. place to "yield" result. I mean `w` is 0, each call of `runIt` sets there 1, after all calls we calculate sum of this 1's. And instead of `censor (+1) w` I can do `tell 1` only.
It means that `runIt` can return not `IO ()` but `IO Int` and results of all `runIt`'s asynchnronously gotten values can be accumulated with `mconcat` without using of writer monad. Am I right, writer monad here is not accumulator but only output value (like output arguments in C/C++/IDL/etc)? How is this a typical solution in Haskell - to use writer monad with wrap/unwrap multiple times, only to save output value?
On Tue, 25 Jul 2017 12:31:56 +0300 Michael Snoyman
wrote: Firstly, a direct answer to your question: use mconcat.
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- sequence (map (A.async . runWriterT . runIt w) l) >>= mapM A.wait print $ snd $ mconcat z
Under the surface, WriterT is using mappend to combine the `Sum` values anyway, so it's natural is `mconcat` (the version of mappend that applies to list) to get the same result. Now some possible improvements.
You're not actually using the return value from the `runIt` call, just the writer value. There's a function called `execWriter` for this:
z <- sequence (map (A.async . execWriterT . runIt w) l) >>= mapM A.wait print $ mconcat z
Next, the combination of map and sequence can be written as traverse:
z <- traverse (A.async . execWriterT . runIt w) l >>= mapM A.wait
But the async library is cool enough that it provides a function called mapConcurrently that deals with the async/wait dance for you:
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l print $ mconcat z
One final note: usage of `print` like this in a concurrent context can run into interleaved output if you have the wrong buffer mode turned out, leading to output like this:
2 3 41
This is especially common when using runghc or ghci. You can either change the buffering mode or use a different output function like sayShow (from the say package, which I wrote):
module Main where
import qualified Control.Concurrent.Async as A import Control.Monad.Trans.Writer import Data.Monoid import Say
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something sayShow x
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l sayShow $ mconcat z
On Tue, Jul 25, 2017 at 11:36 AM, Baa
wrote: Hello, Dear List!
There is package `async` (https://hackage.haskell.org/package/async-2.1.1.1/docs/ Control-Concurrent-Async.html).
Before, I had:
import qualified Control.Concurent.Async as A ... runIt :: ... -> IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait
But now I want to count something inside `runIt`. I will use `Writer` monad for it (sure, it can be `State` also, not in principle to me). To do it synchronously, I done:
module Main where
import Control.Monad.Trans.Writer import Control.Monad.IO.Class import Data.Monoid
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something liftIO $ print x
main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- runWriterT $ sequence [runIt w i | i <- l] print $ snd z
but now my `runIt` changes it's signature:
runIt :: Num a => WriterT (Sum a) IO () -> ... -> WriterT (Sum a) IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait ^^^^^^^^^^^ ` ERROR is here!
I get the error because `async`::IO () -> IO (A.Async ()) but I'm trying to pass it `WriterT (Sum a) IO ()`!
To fix it I added `runWriterT` there:
res <- sequence [A.async $ runWriterT (runIt ...) ...] >>= mapM A.wait
but now I will get list of counters, not one (res::[((), Sum Int)])!
How to solve this problem: to run several actions asyncronously and to count something inside the action with `Writer` monad?
=== Best regards, Paul _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Yes, it's true. I see now. Thank you again for that good
explanation!
On Tue, 25 Jul 2017 13:41:35 +0300
Michael Snoyman
You're asking very good questions, about a topic I considered bringing up in my previous response but didn't. I guess I will now :)
The important thing to realize about monad transformers (and monads in general) is that _they're nothing special_. Under the surface, WriterT is simply:
* Modifying your functions to have an extra value returned * Providing convenience functions like `tell` and `liftIO` to work with that extra value
I would strongly advise getting used to writing code in both the transformer and non-transformer style to convince yourself that they are the same thing. To make this concrete, look at the WriterT definition:
newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }
If you take away the newtype wrapping business, you can see that it's just saying `WriterT w m a = m (a, w)`. And therefore, if we go back to your types, we can replace:
WriterT (Sum a) IO ()
with
IO ((), Sum a)
In fact, that's exactly what `runWriterT` is doing. I would recommend trying to rewrite your code to not even bother with the `WriterT` at all and see if you can get the same output.
So your intuition is correct: there's no output parameter like in C. You could simulate that in Haskell by passing in a mutable variable (like an IORef), but that's not idiomatic. Passing back pairs of values is common in Haskell.
Transformers can be useful for avoiding a lot of boilerplate code. They can also introduce a lot of complexity in some cases. Figuring out when is the right time to use them and when not is subjective and nuanced. Knowing the skill is great; being able to avoid using the skill is also important :)
On Tue, Jul 25, 2017 at 1:29 PM, Baa
wrote: Hello, Michael! This answers to my question completely, thank you so much!
But looking at this code, I thought: how is it right to wrap/unwrap write monad? In languages like C or Python we can pass input/output argument (`int*` in C or `[0]` in Python) and use it as some accumulator. But here writer monad is not using as accumulator, accumulating (summation) happens in `mconcat`, right? It's using only as output value, i.e. place to "yield" result. I mean `w` is 0, each call of `runIt` sets there 1, after all calls we calculate sum of this 1's. And instead of `censor (+1) w` I can do `tell 1` only.
It means that `runIt` can return not `IO ()` but `IO Int` and results of all `runIt`'s asynchnronously gotten values can be accumulated with `mconcat` without using of writer monad. Am I right, writer monad here is not accumulator but only output value (like output arguments in C/C++/IDL/etc)? How is this a typical solution in Haskell - to use writer monad with wrap/unwrap multiple times, only to save output value?
On Tue, 25 Jul 2017 12:31:56 +0300 Michael Snoyman
wrote: Firstly, a direct answer to your question: use mconcat.
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- sequence (map (A.async . runWriterT . runIt w) l) >>= mapM A.wait print $ snd $ mconcat z
Under the surface, WriterT is using mappend to combine the `Sum` values anyway, so it's natural is `mconcat` (the version of mappend that applies to list) to get the same result. Now some possible improvements.
You're not actually using the return value from the `runIt` call, just the writer value. There's a function called `execWriter` for this:
z <- sequence (map (A.async . execWriterT . runIt w) l) >>= mapM A.wait print $ mconcat z
Next, the combination of map and sequence can be written as traverse:
z <- traverse (A.async . execWriterT . runIt w) l >>= mapM A.wait
But the async library is cool enough that it provides a function called mapConcurrently that deals with the async/wait dance for you:
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l print $ mconcat z
One final note: usage of `print` like this in a concurrent context can run into interleaved output if you have the wrong buffer mode turned out, leading to output like this:
2 3 41
This is especially common when using runghc or ghci. You can either change the buffering mode or use a different output function like sayShow (from the say package, which I wrote):
module Main where
import qualified Control.Concurrent.Async as A import Control.Monad.Trans.Writer import Data.Monoid import Say
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something sayShow x
main :: IO () main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- A.mapConcurrently (execWriterT . runIt w) l sayShow $ mconcat z
On Tue, Jul 25, 2017 at 11:36 AM, Baa
wrote: Hello, Dear List!
There is package `async` (https://hackage.haskell.org/package/async-2.1.1.1/docs/ Control-Concurrent-Async.html).
Before, I had:
import qualified Control.Concurent.Async as A ... runIt :: ... -> IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait
But now I want to count something inside `runIt`. I will use `Writer` monad for it (sure, it can be `State` also, not in principle to me). To do it synchronously, I done:
module Main where
import Control.Monad.Trans.Writer import Control.Monad.IO.Class import Data.Monoid
runIt :: (Show a, Num a) => WriterT (Sum a) IO () -> a -> WriterT (Sum a) IO () runIt w x = do censor (+1) w -- emulates conditional count of something liftIO $ print x
main = do let l = [1,2,3,4] w = writer ((), 0) :: WriterT (Sum Int) IO () z <- runWriterT $ sequence [runIt w i | i <- l] print $ snd z
but now my `runIt` changes it's signature:
runIt :: Num a => WriterT (Sum a) IO () -> ... -> WriterT (Sum a) IO () ... sequence [A.async $ runIt ...] >>= mapM_ A.wait ^^^^^^^^^^^ ` ERROR is here!
I get the error because `async`::IO () -> IO (A.Async ()) but I'm trying to pass it `WriterT (Sum a) IO ()`!
To fix it I added `runWriterT` there:
res <- sequence [A.async $ runWriterT (runIt ...) ...] >>= mapM A.wait
but now I will get list of counters, not one (res::[((), Sum Int)])!
How to solve this problem: to run several actions asyncronously and to count something inside the action with `Writer` monad?
=== Best regards, Paul _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Baa
-
Michael Snoyman