[commit: testsuite] master: Trac #7736: Parallel array enumeration causes compiler panic (enumFromToP), expected fail (bbb619c)
Amos Robinson
amos.robinson at gmail.com
Mon Mar 4 03:59:42 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/bbb619cbcddbf1715ce5eaad169460d41dd28868
>---------------------------------------------------------------
commit bbb619cbcddbf1715ce5eaad169460d41dd28868
Author: Amos Robinson <amos.robinson at gmail.com>
Date: Mon Mar 4 13:53:42 2013 +1100
Trac #7736: Parallel array enumeration causes compiler panic (enumFromToP), expected fail
>---------------------------------------------------------------
.../ExportList.hs => enumfromto/EnumFromToP.hs} | 23 ++++++-------------
.../should_compile => dph/enumfromto}/Makefile | 0
tests/dph/enumfromto/dph-enumfromto.T | 9 +++++++
3 files changed, 16 insertions(+), 16 deletions(-)
diff --git a/tests/dph/modules/ExportList.hs b/tests/dph/enumfromto/EnumFromToP.hs
similarity index 56%
copy from tests/dph/modules/ExportList.hs
copy to tests/dph/enumfromto/EnumFromToP.hs
index 99011e1..f210f21 100644
--- a/tests/dph/modules/ExportList.hs
+++ b/tests/dph/enumfromto/EnumFromToP.hs
@@ -1,13 +1,14 @@
--- Explicit export list
--- Produces error
+-- List enumeration doesn't work for parallel list comprehensions.
+--
-- > ghc-stage2: panic! (the 'impossible' happened)
-- > (GHC version 7.7.20130109 for x86_64-unknown-linux):
--- > nameModule solveV{v r3Ep}
--- It is something about internal vs external names.
+-- > DsMonad: uninitialised ds_parr_bi
+--
+-- (I.enumFromToP is a workaround)
{-# LANGUAGE ParallelArrays, ParallelListComp #-}
{-# OPTIONS -fvectorise #-}
-module ExportList (solvePA) where
+module EnumFromToP where
import Data.Array.Parallel hiding ((+), (-), (*), (/))
import Data.Array.Parallel.PArray
@@ -17,17 +18,7 @@ import qualified Data.Array.Parallel.Prelude.Int as I
import qualified Data.Vector as V
import qualified Prelude as P
-data NodeV = NodeV Double Double Double [:NodeV:]
-{-# NOINLINE solvePA #-}
-solvePA
- :: NodeV -- ^ nodes
- -> Double -- ^ time
- -> PArray Double
-solvePA nodes t = toPArrayP (solveV t)
+nums = [: 0 .. 100 :]
-solveV :: Double -> [:Double:]
-solveV t
- = concatP (mapP solveV [: :])
-
diff --git a/tests/annotations/should_compile/Makefile b/tests/dph/enumfromto/Makefile
similarity index 100%
copy from tests/annotations/should_compile/Makefile
copy to tests/dph/enumfromto/Makefile
diff --git a/tests/dph/enumfromto/dph-enumfromto.T b/tests/dph/enumfromto/dph-enumfromto.T
new file mode 100644
index 0000000..3d8257e
--- /dev/null
+++ b/tests/dph/enumfromto/dph-enumfromto.T
@@ -0,0 +1,9 @@
+test ('EnumFromToP'
+ , [ extra_clean(['EnumFromToP.o', 'EnumFromToP.hi'])
+ , reqlib('dph-lifted-vseg')
+ , reqlib('dph-prim-par')
+ , ignore_output
+ , expect_broken(7736)
+ , only_ways(['normal', 'threaded1', 'threaded2']) ]
+ , compile_fail
+ , [ '-O -fno-enable-rewrite-rules -package dph-lifted-vseg'])
More information about the ghc-commits
mailing list