[commit: testsuite] master: DPH: test tidying when unvectorised version of an exported variable disappears (0a9a65e)

Manuel Chakravarty chak at cse.unsw.edu.au
Fri Feb 15 04:12:58 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/0a9a65ebbd17a23a496548428b31cf2a7c1e975e

>---------------------------------------------------------------

commit 0a9a65ebbd17a23a496548428b31cf2a7c1e975e
Author: Manuel M T Chakravarty <chak at cse.unsw.edu.au>
Date:   Fri Feb 15 12:08:21 2013 +1100

    DPH: test tidying when unvectorised version of an exported variable disappears

>---------------------------------------------------------------

 tests/dph/modules/ExportList.hs                    |   33 ++++++++++++++++++++
 .../should_compile => dph/modules}/Makefile        |    0 
 tests/dph/modules/dph-ExportList-vseg-fast.stderr  |    6 +++
 .../dph-classes.T => modules/dph-modules.T}        |    9 ++---
 4 files changed, 43 insertions(+), 5 deletions(-)

diff --git a/tests/dph/modules/ExportList.hs b/tests/dph/modules/ExportList.hs
new file mode 100644
index 0000000..99011e1
--- /dev/null
+++ b/tests/dph/modules/ExportList.hs
@@ -0,0 +1,33 @@
+-- Explicit export list
+-- Produces error
+-- > 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.
+
+{-# LANGUAGE ParallelArrays, ParallelListComp #-}
+{-# OPTIONS -fvectorise #-}
+module ExportList (solvePA) where
+
+import Data.Array.Parallel hiding ((+), (-), (*), (/))
+import Data.Array.Parallel.PArray
+import Data.Array.Parallel.Prelude.Bool          as B
+import Data.Array.Parallel.Prelude.Double        as D
+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)
+
+
+solveV :: Double -> [:Double:]
+solveV t
+ = concatP (mapP solveV [: :])
+
diff --git a/tests/annotations/should_compile/Makefile b/tests/dph/modules/Makefile
similarity index 100%
copy from tests/annotations/should_compile/Makefile
copy to tests/dph/modules/Makefile
diff --git a/tests/dph/modules/dph-ExportList-vseg-fast.stderr b/tests/dph/modules/dph-ExportList-vseg-fast.stderr
new file mode 100644
index 0000000..749c3cd
--- /dev/null
+++ b/tests/dph/modules/dph-ExportList-vseg-fast.stderr
@@ -0,0 +1,6 @@
+[1 of 1] Compiling ExportList       ( ExportList.hs, ExportList.o )
+Warning: vectorisation failure: identityConvTyCon: type constructor contains parallel arrays [::]
+  Could NOT call vectorised from original version ExportList.solveV
+Warning: vectorisation failure: identityConvTyCon: type constructor contains parallel arrays NodeV
+  Could NOT call vectorised from original version
+  ExportList.solvePA
diff --git a/tests/dph/classes/dph-classes.T b/tests/dph/modules/dph-modules.T
similarity index 52%
copy from tests/dph/classes/dph-classes.T
copy to tests/dph/modules/dph-modules.T
index aa10c83..77db0cd 100644
--- a/tests/dph/classes/dph-classes.T
+++ b/tests/dph/modules/dph-modules.T
@@ -1,9 +1,8 @@
-test    ('dph-classes-vseg-fast' 
-        , [ expect_fail
-          , extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
+test    ('dph-ExportList-vseg-fast' 
+        , [ extra_clean(['ExportList.o', 'ExportList.hi'])
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
-        , multimod_compile_and_run 
-        , [ 'Main'
+        , multimod_compile
+        , [ 'ExportList'
           , '-O -fno-enable-rewrite-rules -package dph-lifted-vseg'])





More information about the ghc-commits mailing list