[commit: ghc] ghc-8.2: Add regression test for #7944 (72f1071)

git at git.haskell.org git at git.haskell.org
Thu Apr 6 22:29:36 UTC 2017


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

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/72f1071981cf5c969745070135cdd8b1657723eb/ghc

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

commit 72f1071981cf5c969745070135cdd8b1657723eb
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Tue Apr 4 21:46:55 2017 -0400

    Add regression test for #7944
    
    Commit b8b3e30a6eedf9f213b8a718573c4827cfa230ba happened to fix the bug
    reported in #7944. Let's add a regression test so that it stays that
    way.
    
    Fixes #7944.
    
    Test Plan: make test TEST=T7944
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3404
    
    (cherry picked from commit af941a96f62101a6539f3cc35d82df3fd964539c)


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

72f1071981cf5c969745070135cdd8b1657723eb
 testsuite/tests/simplCore/should_compile/T7944.hs | 19 +++++++++++++++++++
 testsuite/tests/simplCore/should_compile/all.T    |  1 +
 2 files changed, 20 insertions(+)

diff --git a/testsuite/tests/simplCore/should_compile/T7944.hs b/testsuite/tests/simplCore/should_compile/T7944.hs
new file mode 100644
index 0000000..bb62427
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T7944.hs
@@ -0,0 +1,19 @@
+module T7944 where
+
+import GHC.Exts
+
+-- Force specialisation of "go"
+data SPEC = SPEC | SPEC2
+{-# ANN type SPEC ForceSpecConstr #-}
+
+-- This is more or less just an ordinary fold
+go :: SPEC -> [a] -> IntMap a -> IntMap a
+go SPEC [] m = m
+go SPEC (_:xs) m
+ = go SPEC xs
+ -- This would be the "worker function" of the fold
+ $ Unary m
+
+
+-- Both constructors are necessary, despite only one being used
+data IntMap a = Nil | Unary (IntMap a)
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 2d87e24..1bf1f36 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -158,6 +158,7 @@ test('T7702',
      compile,
      ['-v0 -package-db T7702plugin/pkg.T7702/local.package.conf -fplugin T7702Plugin -package T7702plugin ' + config.plugin_way_flags])
 
+test('T7944', normal, compile, ['-O2'])
 test('T7995',
      # RULE doesn't seem to fire unless optimizations are turned on.
      # This seems reasonable, so I've required it for the test. -- EZY 20130720



More information about the ghc-commits mailing list