|
|
Line 5: |
Line 5: |
| 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>. | | 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 ==
| | [http://haskell.org/haskellwiki/GHC/Concurrency/Zeta Riemann's Zeta function approximation] |
| | |
| This little piece of code computes an approximation of Riemann's zeta function, balancing the work to be done between N threads.
| |
| | |
| <haskell>
| |
| import Control.Concurrent
| |
| import Control.Concurrent.MVar
| |
| import Control.Monad
| |
| import Data.Complex
| |
| import System.Environment
| |
| | |
| zetaRange s (x,y) = sum [ (fromIntegral n :+ 0) ** (-s) | n <- [x..y] ]
| |
| | |
| cut :: (Integral a) => (a, a) -> a -> [(a, a)]
| |
| 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 = []
| |
| cut' x' size' n' = (x', x' + size' - 1) : cut' (x' + size') size' (n' - size')
| |
| | |
| getParams :: IO (Int, Int, Complex Double)
| |
| getParams = do
| |
| argv <- getArgs
| |
| 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>
| |
Revision as of 15:22, 28 November 2006
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
.
Riemann's Zeta function approximation