ghc 7.2.1 and super simple DPH

Hi - I'm trying to compile DotP.hs from http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell#A_simple_exampl... (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! Peter {-# LANGUAGE ParallelArrays #-}{-# OPTIONS_GHC -fvectorise #-} module DotP (dotp_wrapper)where import qualified Preludeimport Data.Array.Parallel.Preludeimport 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)

Peter Braam wrote:
Hi -
I'm trying to compile DotP.hs from http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell#A_simple_exampl... (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/

Erik de Castro Lopo wrote:
The code you posted had some wrapping issues and was missing an import.
I should have also mentioned how I figured out what the missing import was. Firstly, I tried hoogle [0] but couldn't find it. I then realised that it must be part of DPH and that I had a copy of the DPH sources on my machine. Going to the DPH source tree I did: find . -name \*.hs | xargs grep ^fromPArrayP which showed up this: dph-common/Data/Array/Parallel.hs:fromPArrayP :: PArray a -> [:a:] Cheers, Erik [0] http://www.haskell.org/hoogle/ -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

Super helpful, thanks!
Peter
On Mon, Oct 3, 2011 at 12:54 AM, Erik de Castro Lopo
Erik de Castro Lopo wrote:
The code you posted had some wrapping issues and was missing an import.
I should have also mentioned how I figured out what the missing import was.
Firstly, I tried hoogle [0] but couldn't find it. I then realised that it must be part of DPH and that I had a copy of the DPH sources on my machine. Going to the DPH source tree I did:
find . -name \*.hs | xargs grep ^fromPArrayP
which showed up this:
dph-common/Data/Array/Parallel.hs:fromPArrayP :: PArray a -> [:a:]
Cheers, Erik
[0] http://www.haskell.org/hoogle/ -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Erik de Castro Lopo
-
Peter Braam