Hi Fabian,

I've just begun to play with Data Parallel Haskell but instantly ran into a problem. My very stupid but very simple example ought to sum the values of all Nodes in a Tree. The non-vectorised code behaves like I expected, the vectorised code doesn't terminate. I compiled and ran it the same way as the
example in the tutorial:

ghc -c -O -fdph-par Main.hs
ghc -c -Odph -fcpr-off -fdph-par MinimalParTree.hs
ghc -o MinimalParTree -fdph-par -threaded MinimalParTree.o Main.o
./MinimalParTree

My question is: Is this a bug or is something wrong with the program?

This appears to be a bug in the DPH libraries. Can you please file a bug report at <http://hackage.haskell.org/trac/ghc>?

For the time being, you can change sumTree as follows to get your program working:

sumTree :: Tree Int -> Int
sumTree (Node x ns)
  | lengthP ns == 0 = x
  | otherwise       = x + sumP (mapP sumTree ns)

Thanks for the report,
Manuel


--------------------------------------------------------------------
module Main where

import MinimalParTree

main = do
  print $ sumTreeWrapper 20

--------------------------------------------------------------------
{-# LANGUAGE PArr, ParallelListComp #-}
{-# OPTIONS -fvectorise #-}

module MinimalParTree (sumTreeWrapper) where

import qualified Prelude
import Data.Array.Parallel.Prelude
import Data.Array.Parallel.Prelude.Int

data Tree a = Node a [: Tree a :]

testTree :: Int -> Tree Int
testTree elem = Node elem emptyP

sumTree :: Tree Int -> Int
sumTree (Node x ns) = x + sumP (mapP sumTree ns)

{-# NOINLINE sumTreeWrapper #-}
sumTreeWrapper :: Int -> Int
sumTreeWrapper elem =
 sumTree (testTree elem)

--------------------------------------------------------------------
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to