[commit: ghc] wip/T13861: add more test cases (1bee0e8)

git at git.haskell.org git at git.haskell.org
Fri Dec 22 00:02:59 UTC 2017


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

On branch  : wip/T13861
Link       : http://ghc.haskell.org/trac/ghc/changeset/1bee0e8895a8a452e72714f0bf960903629ba738/ghc

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

commit 1bee0e8895a8a452e72714f0bf960903629ba738
Author: Gabor Greif <ggreif at gmail.com>
Date:   Mon Jul 31 12:08:29 2017 +0200

    add more test cases


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

1bee0e8895a8a452e72714f0bf960903629ba738
 testsuite/tests/simplStg/should_run/T13861.hs | 17 ++++++++++++++++-
 1 file changed, 16 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/simplStg/should_run/T13861.hs b/testsuite/tests/simplStg/should_run/T13861.hs
index 89b9318..4f7e9e0 100644
--- a/testsuite/tests/simplStg/should_run/T13861.hs
+++ b/testsuite/tests/simplStg/should_run/T13861.hs
@@ -1,5 +1,6 @@
-{-# LANGUAGE MagicHash, BangPatterns #-}
+{-# LANGUAGE MagicHash, BangPatterns, TypeOperators, GADTs #-}
 import GHC.Exts
+import Data.Type.Equality
 import Unsafe.Coerce
 
 foo :: Either Int a -> Maybe a
@@ -50,6 +51,13 @@ rec2 x =
     in s1
 {-# NOINLINE rec2 #-}
 
+
+eq1 :: a :~: b -> [a]
+eq1 Refl = []
+{-# NOINLINE eq1 #-}
+
+
+
 test x = do
     let (r1,r2) = bar x
     (same $! r1) $! r2
@@ -60,6 +68,13 @@ test x = do
 
     let (r40, r41) = (['l'], baz r40)
     (same $! r40) $! r41
+    let (r42, r43) = ([], eq1 r42)
+    (same $! r42) $! r43
+    let (r44, r45) = ("ab", eq1 r44)
+    (same $! r44) $! r45
+    let (r46, r47) = (Refl, eq1 r46)
+    (same $! r46) $! r47
+
     let (r4,_) = bar r1
     let r5 = nested r4
     (same $! r4) $! r5



More information about the ghc-commits mailing list