
Daniel Fischer wrote:
Am Freitag 22 Mai 2009 04:59:51 schrieb Mario Blažević:
... I'm confused. I know that `par` must be able work across modules boundaries, because Control.Parallel.Strategies is a module and presumably it works. What am I doing wrong?
You forgot
{-# INLINE parallelize #-}
For me, that works.
That's great, thank you. I am still baffled, though. Must every exported function that uses `par' be INLINEd? Does every exported caller of such a function need the same treatment? Is `par' really a macro, rather than a function?
module Main where
import Control.Parallel import Data.List (find) import Data.Maybe (maybe)
--import Parallelizable parallelize a b = a `par` (b `pseq` (a, b))
test :: Integer -> Integer -> Integer test n1 n2 = let (p1, p2) = parallelize (product $ factors $ product [1..n1]) (product $ factors $ product [1..n2]) in p2 `div` p1
factors n = maybe [n] (\k-> (k : factors (n `div` k))) (find (\k-> n `mod` k == 0) [2 .. n - 1])
main = print (test 5000 5001)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Mario Blazevic mblazevic@stilo.com Stilo Corporation This message, including any attachments, is for the sole use of the intended recipient(s) and may contain confidential and privileged information. Any unauthorized review, use, disclosure, copying, or distribution is strictly prohibited. If you are not the intended recipient(s) please contact the sender by reply email and destroy all copies of the original message and any attachments.