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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3857074e5c31e5b795679a7645ba6457f1b96270

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

commit 3857074e5c31e5b795679a7645ba6457f1b96270
Author: Manuel M T Chakravarty <[email protected]>
Date:   Thu Nov 17 22:30:13 2011 +1100

    New test 'dph-classes'
    
    * Test vectorisation of type classes

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

 tests/dph/classes/DefsVect.hs                      |   22 ++++++++++++++++++++
 tests/dph/classes/Main.hs                          |    6 +++++
 .../should_compile => dph/classes}/Makefile        |    0 
 .../classes/dph-classes-fast.stdout}               |    0 
 .../dph-sumnats.T => classes/dph-classes.T}        |    8 ++----
 5 files changed, 31 insertions(+), 5 deletions(-)

diff --git a/tests/dph/classes/DefsVect.hs b/tests/dph/classes/DefsVect.hs
new file mode 100644
index 0000000..fa88c91
--- /dev/null
+++ b/tests/dph/classes/DefsVect.hs
@@ -0,0 +1,22 @@
+{-# OPTIONS_GHC -fvectorise #-}
+
+module DefsVect where
+
+import Data.Array.Parallel.Prelude.Bool
+import Data.Array.Parallel.Prelude.Int  (Int)
+
+
+{-# VECTORISE class Eq #-}
+{-# VECTORISE SCALAR instance Eq Int #-}
+
+class Eq a => Cmp a where
+  cmp :: a -> a -> Bool
+
+isFive :: Int -> Bool
+isFive x = x == 5
+
+isEq :: Eq a => a -> Bool
+isEq x = x == x
+
+fiveEq :: Int -> Bool
+fiveEq x = isFive x && isEq x
\ No newline at end of file
diff --git a/tests/dph/classes/Main.hs b/tests/dph/classes/Main.hs
new file mode 100644
index 0000000..b5fca71
--- /dev/null
+++ b/tests/dph/classes/Main.hs
@@ -0,0 +1,6 @@
+module Main where
+
+import DefsVect
+
+main = print $ fiveEq 5
+
diff --git a/tests/annotations/should_compile/Makefile 
b/tests/dph/classes/Makefile
similarity index 100%
copy from tests/annotations/should_compile/Makefile
copy to tests/dph/classes/Makefile
diff --git a/tests/codeGen/should_run/cgrun033.stdout 
b/tests/dph/classes/dph-classes-fast.stdout
similarity index 100%
copy from tests/codeGen/should_run/cgrun033.stdout
copy to tests/dph/classes/dph-classes-fast.stdout
diff --git a/tests/dph/sumnats/dph-sumnats.T b/tests/dph/classes/dph-classes.T
similarity index 51%
copy from tests/dph/sumnats/dph-sumnats.T
copy to tests/dph/classes/dph-classes.T
index 182b85d..566c64a 100644
--- a/tests/dph/sumnats/dph-sumnats.T
+++ b/tests/dph/classes/dph-classes.T
@@ -1,11 +1,9 @@
-
-test    ('dph-sumnats' 
-        , [ extra_clean(['Main.hi', 'Main.o',
-                         'SumNatsVect.hi', 'SumNatsVect.o'])
+test    ('dph-classes-fast' 
+        , [ extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
         , multimod_compile_and_run 
         , [ 'Main'
-          , '-Odph -package dph-lifted-copy'])
+          , '-O -fno-enable-rewrite-rules -package dph-lifted-copy'])
 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to