#5070: dph and new code generator don't play nicely with each other
---------------------------------+------------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Component: Data Parallel Haskell
Version: 7.0.3 | Keywords:
Testcase: | Blockedby: 5065
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
I'm looking at the current failure of DPH with the new code generator,
which is a bit different from what I've dealt with before. The bug
appears
to be in the compiled libraries code, and I can tickle it with the
following minimized example:
{{{
{-# LANGUAGE ParallelArrays #-}
{-# OPTIONS -fvectorise #-}
module PrimesVect where
import Data.Array.Parallel.Prelude
import qualified Prelude
f :: PArray Bool
f = toPArrayP f'
f' :: [:Bool:]
f' = [: True | _ <- singletonP True, g emptyP:]
g :: [:Bool:] -> Bool
g ps = andP [: True | _ <- ps:]
}}}
and a runner:
{{{
import qualified Data.Array.Parallel.PArray as P
import PrimesVect
main = print (P.toList f)
}}}
I expect to get [True], but instead I get:
{{{
dph-primespj-fast: libraries/vector/Data/Vector/Generic.hs:369
(slice): invalid slice (0,1,0)
dph-primespj-fast: thread blocked indefinitely in an MVar operation
}}}
Now, in the situation that the library code is broken, I'd usually try to
inline
all of the library code and then pare that down into something manageable.
Unfortunately,
DPH is pretty closely tied to the compiler, so I don't see an easy way to
do that.
So I'm not really sure how to go about debugging this.
Note that we can't work on this bug until #5065 is resolved, since these
tests are currently failing for unrelated reasons.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5070>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs