[Haskell-beginners] Count with Writer asynchronously
Baa
aquagnu at gmail.com
Tue Jul 25 08:36:11 UTC 2017
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
More information about the Beginners
mailing list