[Haskell-beginners] Count with Writer asynchronously
Michael Snoyman
michael at snoyman.com
Tue Jul 25 09:31:56 UTC 2017
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 <aquagnu at gmail.com> 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 at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20170725/5aae9422/attachment.html>
More information about the Beginners
mailing list