[commit: ghc] master: Test Trac #12776 (605af54)

git at git.haskell.org git at git.haskell.org
Mon Nov 28 16:44:38 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/605af54aee76cd3d02afb60ff0b0dde052645fe7/ghc

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

commit 605af54aee76cd3d02afb60ff0b0dde052645fe7
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Nov 28 16:43:49 2016 +0000

    Test Trac #12776


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

605af54aee76cd3d02afb60ff0b0dde052645fe7
 testsuite/tests/simplCore/should_compile/T12776.hs | 42 ++++++++++++++++++++++
 testsuite/tests/simplCore/should_compile/all.T     |  1 +
 2 files changed, 43 insertions(+)

diff --git a/testsuite/tests/simplCore/should_compile/T12776.hs b/testsuite/tests/simplCore/should_compile/T12776.hs
new file mode 100644
index 0000000..e8e2c8c
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T12776.hs
@@ -0,0 +1,42 @@
+{-# OPTIONS_GHC -O2 #-}
+
+-- This made the simplifier loop doing infinite inlining
+-- in GHC 8.0
+
+module T12776(distinct_degree_factorization_i) where
+
+import Prelude ((==), Eq);
+
+data Slist a = Nil_s | Cons_s a (Slist a) deriving Eq;
+
+map_s :: (a -> b) -> Slist a -> Slist b;
+map_s f (Cons_s x21 x22) = Cons_s (f x21) (map_s f x22);
+
+normalize_poly_i :: (Eq a) => (a -> a) -> Slist a -> Slist a;
+normalize_poly_i ops xs = if ops (lead_coeff_i xs) == lead_coeff_i xs then Nil_s else map_s ops xs;
+
+mod_poly_one_main_i :: (Eq a) => (a -> a) -> Slist a -> Slist a;
+mod_poly_one_main_i ops d =
+  if d == d then d else mod_poly_one_main_i ops (normalize_poly_i ops d);
+
+last_s :: (Eq a) => Slist a -> a;
+last_s (Cons_s x xs) = (if xs == Nil_s then x else last_s xs);
+
+mod_field_poly_i :: (Eq a) => (a -> a) -> Slist a -> Slist a;
+mod_field_poly_i ops cf =
+  (if cf == cf then cf else
+     mod_poly_one_main_i ops (map_s (\_ -> ops (last_s cf)) cf));
+
+lead_coeff_i :: Eq a => Slist a -> a;
+lead_coeff_i pp = (case pp of {
+                        Cons_s _ _ -> last_s pp;
+                      });
+
+dist_degree_factorize_main_i :: Eq a => (a -> a) -> Slist a -> [Slist a] -> [Slist a];
+dist_degree_factorize_main_i ff_ops w res =
+  if w == w then res
+           else dist_degree_factorize_main_i ff_ops (mod_field_poly_i ff_ops w)
+                   [normalize_poly_i ff_ops (mod_field_poly_i ff_ops w)];
+
+distinct_degree_factorization_i :: Eq a => (a -> a) -> [Slist a];
+distinct_degree_factorization_i ff_ops = dist_degree_factorize_main_i ff_ops Nil_s []
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index f985b4a..19d806f 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -245,3 +245,4 @@ test('T12212', normal, compile, ['-O'])
 
 test('noinline01', only_ways(['optasm']), compile, ['-ddump-stg -dsuppress-uniques -O'])
 test('par01', only_ways(['optasm']), compile, ['-ddump-prep -dsuppress-uniques -O2'])
+test('T12776', normal, compile, ['-O2'])



More information about the ghc-commits mailing list