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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d218663c0d45ced49b2b13d008c5431e3fc3f3df

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

commit d218663c0d45ced49b2b13d008c5431e3fc3f3df
Author: Manuel M T Chakravarty <[email protected]>
Date:   Fri Nov 25 22:59:38 2011 +1100

    Test vectorisation of type classes some more

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

 .gitignore                                |    4 ++-
 tests/dph/classes/DefsVect.hs             |   33 ++++++++++++++++++++++++++++-
 tests/dph/classes/Main.hs                 |   13 +++++++++-
 tests/dph/classes/dph-classes-fast.stdout |    2 +-
 4 files changed, 47 insertions(+), 5 deletions(-)

diff --git a/.gitignore b/.gitignore
index 6b69bd4..efc09c6 100644
--- a/.gitignore
+++ b/.gitignore
@@ -124,4 +124,6 @@ timeout/dist/
 /tests/safeHaskell/check/pkg01/dist/
 /tests/safeHaskell/check/pkg01/install/
 /tests/safeHaskell/check/pkg01/local.db/
-/tests/safeHaskell/check/pkg01/setup
\ No newline at end of file
+/tests/safeHaskell/check/pkg01/setup
+tests/dph/classes/dph-classes-fast
+tests/dph/dotp/dph-dotp-opt
\ No newline at end of file
diff --git a/tests/dph/classes/DefsVect.hs b/tests/dph/classes/DefsVect.hs
index fa88c91..e384908 100644
--- a/tests/dph/classes/DefsVect.hs
+++ b/tests/dph/classes/DefsVect.hs
@@ -1,7 +1,9 @@
+{-# LANGUAGE ParallelArrays #-}
 {-# OPTIONS_GHC -fvectorise #-}
 
 module DefsVect where
 
+import Data.Array.Parallel
 import Data.Array.Parallel.Prelude.Bool
 import Data.Array.Parallel.Prelude.Int  (Int)
 
@@ -9,6 +11,14 @@ import Data.Array.Parallel.Prelude.Int  (Int)
 {-# VECTORISE class Eq #-}
 {-# VECTORISE SCALAR instance Eq Int #-}
 
+-- {-# VECTORISE class Ord #-}
+-- {-# VECTORISE SCALAR instance Ord Int #-}
+
+-- {-# VECTORISE type Bool = Bool #-}
+-- {-# VECTORISE type Ordering #-}
+
+data MyBool = MyTrue | MyFalse
+
 class Eq a => Cmp a where
   cmp :: a -> a -> Bool
 
@@ -19,4 +29,25 @@ isEq :: Eq a => a -> Bool
 isEq x = x == x
 
 fiveEq :: Int -> Bool
-fiveEq x = isFive x && isEq x
\ No newline at end of file
+fiveEq x = isFive x && isEq x
+
+cmpArrs :: PArray Int -> PArray Int -> Bool
+{-# NOINLINE cmpArrs #-}
+cmpArrs v w = cmpArrs' (fromPArrayP v) (fromPArrayP w)
+
+cmpArrs' :: [:Int:] -> [:Int:] -> Bool
+cmpArrs' xs ys = andP [:x == y | x <- xs | y <- ys:]
+
+isFives :: PArray Int -> Bool
+{-# NOINLINE isFives #-}
+isFives xs = isFives' (fromPArrayP xs)
+
+isFives' :: [:Int:] -> Bool
+isFives' xs = andP (mapP isFive xs)
+
+isEqs :: PArray Int -> Bool
+{-# NOINLINE isEqs #-}
+isEqs xs = isEqs' (fromPArrayP xs)
+
+isEqs' :: [:Int:] -> Bool
+isEqs' xs = andP (mapP isEq xs)
\ No newline at end of file
diff --git a/tests/dph/classes/Main.hs b/tests/dph/classes/Main.hs
index b5fca71..471c0cc 100644
--- a/tests/dph/classes/Main.hs
+++ b/tests/dph/classes/Main.hs
@@ -1,6 +1,15 @@
 module Main where
 
-import DefsVect
+import Data.Array.Parallel.PArray (PArray, fromList)
 
-main = print $ fiveEq 5
+import DefsVect
 
+main 
+  = let v      = fromList [1..10]
+        w      = fromList [11..20]
+  in
+  print $ [ fiveEq 5
+          , cmpArrs v w
+          , isFives (fromList $ replicate 10 5)
+          , isEqs v
+          ]
diff --git a/tests/dph/classes/dph-classes-fast.stdout 
b/tests/dph/classes/dph-classes-fast.stdout
index 0ca9514..bf8e7b9 100644
--- a/tests/dph/classes/dph-classes-fast.stdout
+++ b/tests/dph/classes/dph-classes-fast.stdout
@@ -1 +1 @@
-True
+[True,False,True,True]



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

Reply via email to