[Haskell-cafe] Data Parallel Haskell Question

James Swaine james.swaine at gmail.com
Wed Feb 4 15:04:58 EST 2009


I am somewhat of a beginner with DPH and wanted to ask a few (maybe
elementary) questions.

There appear to be two main libraries - regular and unlifted.  I was a
little unclear on the difference between the two and was hoping to get some
clarification.  If you use the 'regular' api, it seems that you can use the
sort of 'syntactic sugar' language extensions (e.g. [: blah blah :]), but
you are restricted to the somewhat limited Prelude explicitly written for
use with code that is to be vectorised.

If you use the 'unlifted' libraries, are you able to use functions/types
from the standard Prelude?

My problem is that I want to write a recursively-subdividing radix sort (for
integer keys), where on each iteration I partition my keys into separate
sets based on whether a certain bit is set or not.  So I start with the most
significant digit bit (say 31), and then work down to the least significant
digit.  I can write this in DPH just fine, but I'm getting 'panic' errors
when I attempt to compile, and I wonder if it has something to do with the
fact that I'm using the standard Data.Bits to inspect bits of each key.

{-# LANGUAGE PArr, ParallelListComp #-}
{-# OPTIONS -fvectorise #-}
module RankPar(radix_sort) where

import qualified Prelude
import Data.Array.Parallel.PArray (fromList)
import Data.Array.Parallel.Prelude ((+:+), fromPArrayP, not)
import Data.Array.Parallel.Prelude.Int
import Data.Bits

{-# NOINLINE radix_sort #-}
radix_sort :: Int -> [:Int:] -> [:Int:]
radix_sort (-1) keys = keys
radix_sort bit [:k:] = [:k:]
radix_sort bit [: :] = [: :]
radix_sort bit keys = (radix_sort (bit - 1) left) +:+ (radix_sort (bit - 1)
right)
    where
        right = [: x | x <- keys, (testBit x bit) :]
        left =  [: y | y <- keys, (not (testBit y bit)) :]

Syntactically, this looks correct to me, but won't compile.  Any ideas?

Thanks all!
-James
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090204/68077690/attachment.htm


More information about the Haskell-Cafe mailing list