Concurrency demos: Difference between revisions

From HaskellWiki
No edit summary
(category parallel)
 
(17 intermediate revisions by 6 users not shown)
Line 1: Line 1:
[[Category:Tutorials]]
This page collects examples of concurrent and parallel programming in Haskell.
[[Category:Code]]


A large range of small demonstration programs for using concurrent and
== Examples ==
parallel Haskell are in the Haskell [http://darcs.haskell.org/testsuite/tests/ghc-regress/concurrent/should_run/ concurrency regression tests]. In particular, they show the use of <hask>MVars</hask> and <hask>forkIO</hask>.


== A simple example of parallelism in Haskell ==
* [[/Zeta |Riemann's Zeta function approximation]]
* [[/Graceful exit|Signal that you want to gracefully exit another thread]]
* [[/Two reader threads|Passing messages across a single chan to two readers]]
* [[Implement a chat server|Chat server - using a single channel for a variable number of readers]]
* [[/Simple producer and consumer|Passing IO events lazily from a producer to a consumer thread]]


This little piece of code computes an approximation of Riemann's zeta function, balancing the work to be done between N threads.
== More examples ==


<haskell>
A large range of small demonstration programs for using concurrent and
import Control.Concurrent
parallel Haskell are in the Haskell [http://darcs.haskell.org/testsuite/tests/ghc-regress/concurrent/should_run/ concurrency regression tests]. In particular, they show the use of <hask>MVars</hask> and <hask>forkIO</hask>.
import Control.Concurrent.MVar
import Control.Monad
import Data.Complex
import System.Environment


zetaRange :: (Floating (Complex a), RealFloat a, Integral b) => Complex a -> (b, b) -> Complex a
== Proposed updates ==
zetaRange s (x,y) = sum [ (fromIntegral n :+ 0) ** (-s) | n <- [x..y] ]


cut :: (Integral a) => (a, a) -> a -> [(a, a)]
The base 3.0.3.1 package's Control.Concurrent.QSem and QSemN are not exception safe. The [[SafeConcurrent]] has the proposed replacement code.
cut (x,y) n = (x, x + mine - 1) : cut' (x + mine) size (y - mine)
  where
  (size, modulo) = y `divMod` n
  mine = size + modulo


  cut' _ _ 0  = []
== Other examples ==
  cut' x' size' n' = (x', x' + size' - 1) : cut' (x' + size') size' (n' - size')
* [[/Haskell-Javascript concurrency|Haskell -> Javascript: Pseudo-concurrent threads in web browser]]


getParams :: IO (Int, Int, Complex Double)
[[Category:Parallel]]
getParams = do
[[Category:Tutorials]]
  argv <- getArgs
[[Category:Code]]
  case argv of
    (t:n:s:[]) -> return (read t, read n, read s)
    _ -> error "usage: zeta <nthreads> <boundary> <s>"
 
main :: IO ()
main = do
  (t, n, s) <- getParams
  childs <- zipWithM thread (repeat s) (cut (1, n) t)
  results <- mapM takeMVar childs
  print (sum results)
  where
    thread s range = do
      putStrLn ("Starting thread for range " ++ show range)
      mvar <- newEmptyMVar
      forkIO (putMVar mvar (zetaRange s range))
      return mvar
</haskell>

Latest revision as of 16:18, 16 March 2011

This page collects examples of concurrent and parallel programming in Haskell.

Examples

More examples

A large range of small demonstration programs for using concurrent and parallel Haskell are in the Haskell concurrency regression tests. In particular, they show the use of MVars and forkIO.

Proposed updates

The base 3.0.3.1 package's Control.Concurrent.QSem and QSemN are not exception safe. The SafeConcurrent has the proposed replacement code.

Other examples