[Haskell-cafe] Problems running vectorised dph program

Fabian Reck fre at informatik.uni-kiel.de
Wed Jan 28 12:11:00 EST 2009


Hi Manuel,

thanks for your quick response. 

> 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>?

An bug report is filed.

>
> 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)


Unfortunately this workaround only leads to another problem. Instead of a non 
terminating program I now get a vectorisation error:

> ghc -c -fcpr-off -fdph-par MinimalParTree.hs
> *** Vectorisation error ***
>    Variable not vectorised: Control.Exception.Base.patError

Is there another workaround for that one?

Thanks 

Fabian
>
> > --------------------------------------------------------------------
> > 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 at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list