[Haskell-cafe] ghc 7.2.1 and super simple DPH

Erik de Castro Lopo mle+hs at mega-nerd.com
Mon Oct 3 08:17:11 CEST 2011


Peter Braam wrote:

> Hi -
> 
> I'm trying to compile DotP.hs from
> http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell#A_simple_example
> (see
> below)
> 
> The compiler complains and says (twice in fact):
> 
> DotP.hs:17:33: Not in scope: `fromPArrayP'
> 
> Could someone help me out please?  Thanks a lot!


The code you posted had some wrapping issues and was missing an
import. I've included a version of the code that compiles for
me here (using ghc fromgit HEAD) using:

    ghc -c -Odph -fdph-par DotP.hs

HTH,
Erik


{-# LANGUAGE ParallelArrays #-}
{-# OPTIONS_GHC -fvectorise #-}

module DotP (dotp_wrapper) where
import qualified Prelude

import Data.Array.Parallel
import Data.Array.Parallel.Prelude
import Data.Array.Parallel.Prelude.Double

dotp_double :: [:Double:] -> [:Double:] -> Double
dotp_double xs ys = sumP [:x * y | x <- xs | y <- ys:]

dotp_wrapper :: PArray Double -> PArray Double -> Double
{-# NOINLINE dotp_wrapper #-}
dotp_wrapper v w = dotp_double (fromPArrayP v) (fromPArrayP w)



-- 
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/



More information about the Haskell-Cafe mailing list