summaryrefslogtreecommitdiff
path: root/testsuite/tests/dph/diophantine
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/dph/diophantine')
-rw-r--r--testsuite/tests/dph/diophantine/DiophantineVect.hs38
-rw-r--r--testsuite/tests/dph/diophantine/Main.hs43
-rw-r--r--testsuite/tests/dph/diophantine/Makefile3
-rw-r--r--testsuite/tests/dph/diophantine/dph-diophantine-fast.stdout3
-rw-r--r--testsuite/tests/dph/diophantine/dph-diophantine-opt.stdout3
-rw-r--r--testsuite/tests/dph/diophantine/dph-diophantine.T20
6 files changed, 110 insertions, 0 deletions
diff --git a/testsuite/tests/dph/diophantine/DiophantineVect.hs b/testsuite/tests/dph/diophantine/DiophantineVect.hs
new file mode 100644
index 0000000000..bef6694b3d
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/DiophantineVect.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE ParallelArrays #-}
+{-# OPTIONS -fvectorise -XParallelListComp #-}
+module DiophantineVect (solution3) where
+
+import Data.Array.Parallel
+import Data.Array.Parallel.Prelude.Int
+
+import qualified Prelude as P
+
+solution3'
+ = let
+ pow x i = productP (replicateP i x)
+ primes = [: 2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73 :]
+ sumpri xx = productP [: pow p x | p <- primes | x <- xx :]
+ distinct xx = productP [: x + 1 | x <- xx :]
+
+ series :: [:Int:] -> Int -> [:[:Int:]:]
+ series xs n
+ | n == 1 = [: [: 0 :] :]
+ | otherwise = [: [: x :] +:+ ps
+ | x <- xs
+ , ps <- series (enumFromToP 0 x) (n-1) :]
+
+ prob x y
+ = let xx = [: (sumpri m ,m)
+ | m <- series (enumFromToP 1 3) x
+ , distinct [: x * 2 | x <- m :] > y :]
+ i = minIndexP [: a | (a, b) <- xx :]
+ in xx !: i
+ in
+ prob 7 2000
+
+solution3 :: (Int, PArray Int)
+{-# NOINLINE solution3 #-}
+solution3
+ = let (i, is) = solution3'
+ in
+ (i, toPArrayP is)
diff --git a/testsuite/tests/dph/diophantine/Main.hs b/testsuite/tests/dph/diophantine/Main.hs
new file mode 100644
index 0000000000..eb8ae7ac28
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/Main.hs
@@ -0,0 +1,43 @@
+{-# LANGUAGE ParallelArrays #-}
+
+import Data.List
+import DiophantineVect
+
+import qualified Data.Array.Parallel.PArray as P
+import Data.Array.Parallel.Prelude
+
+
+-- Solution for the 108th Euler problem.
+-- From the Haskell Wiki
+solution1
+ = let primes = [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73]
+ series _ 1 = [[0]]
+ series xs n = [x:ps | x <- xs, ps <- series [0..x] (n-1) ]
+ distinct = product . map (+1)
+ sumpri x = product $ zipWith (^) primes x
+
+ prob x y = minimum [ (sumpri m ,m)
+ | m <- series [1..3] x
+ , (>y) $ distinct $ map (*2) m]
+ in prob 7 2000
+
+solution2
+ = let primes = [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73]
+ series _ 1 = [[0]]
+ series xs n = [x:ps | x <- xs, ps <- series [0..x] (n-1) ]
+ distinct xx = product [ x + 1 | x <- xx ]
+ sumpri xx = product $ zipWith (^) primes xx
+
+ prob x y = minimum [ (sumpri m ,m)
+ | m <- series [1..3] x
+ , (distinct $ map (*2) m) > y ]
+ in prob 7 2000
+
+
+main
+ = do print solution1
+ print solution2
+ print solution3
+
+
+ \ No newline at end of file
diff --git a/testsuite/tests/dph/diophantine/Makefile b/testsuite/tests/dph/diophantine/Makefile
new file mode 100644
index 0000000000..9101fbd40a
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/Makefile
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/testsuite/tests/dph/diophantine/dph-diophantine-fast.stdout b/testsuite/tests/dph/diophantine/dph-diophantine-fast.stdout
new file mode 100644
index 0000000000..7088d6ced3
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/dph-diophantine-fast.stdout
@@ -0,0 +1,3 @@
+(180180,[2,2,1,1,1,1,0])
+(180180,[2,2,1,1,1,1,0])
+(180180,[:2,2,1,1,1,1,0:])
diff --git a/testsuite/tests/dph/diophantine/dph-diophantine-opt.stdout b/testsuite/tests/dph/diophantine/dph-diophantine-opt.stdout
new file mode 100644
index 0000000000..7088d6ced3
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/dph-diophantine-opt.stdout
@@ -0,0 +1,3 @@
+(180180,[2,2,1,1,1,1,0])
+(180180,[2,2,1,1,1,1,0])
+(180180,[:2,2,1,1,1,1,0:])
diff --git a/testsuite/tests/dph/diophantine/dph-diophantine.T b/testsuite/tests/dph/diophantine/dph-diophantine.T
new file mode 100644
index 0000000000..c963db9145
--- /dev/null
+++ b/testsuite/tests/dph/diophantine/dph-diophantine.T
@@ -0,0 +1,20 @@
+
+test ('dph-diophantine-opt'
+ , [ alone
+ , skip_if_fast
+ , reqlib('dph-par')
+ , reqlib('dph-prim-par')
+ , only_ways(['normal', 'threaded1', 'threaded2']) ]
+ , multimod_compile_and_run
+ , [ 'Main'
+ , '-Odph -fdph-par'])
+
+test ('dph-diophantine-fast'
+ , [ reqlib('dph-par')
+ , reqlib('dph-prim-par')
+ , expect_broken(5065)
+ , only_ways(['normal', 'threaded1', 'threaded2']) ]
+ , multimod_compile_and_run
+ , [ 'Main'
+ , '-O -fno-enable-rewrite-rules -fdph-par'])
+