[commit: ghc] wip/T11982-test: testsuite: Add tests from #11982 (0d789ad)

git at git.haskell.org git at git.haskell.org
Tue Jan 22 16:35:10 UTC 2019


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

On branch  : wip/T11982-test
Link       : http://ghc.haskell.org/trac/ghc/changeset/0d789ad0acedb542917672be4b368b194c787b15/ghc

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

commit 0d789ad0acedb542917672be4b368b194c787b15
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Jan 22 11:27:30 2019 -0500

    testsuite: Add tests from #11982


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

0d789ad0acedb542917672be4b368b194c787b15
 testsuite/tests/typecheck/should_compile/T11982a.hs |  7 +++++++
 testsuite/tests/typecheck/should_compile/T11982b.hs | 17 +++++++++++++++++
 testsuite/tests/typecheck/should_compile/T11982c.hs | 18 ++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T      |  3 +++
 4 files changed, 45 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T11982a.hs b/testsuite/tests/typecheck/should_compile/T11982a.hs
new file mode 100644
index 0000000..1928bf2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11982a.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE MonadComprehensions, ParallelListComp #-}
+
+module Foo where
+
+foo xs ys = [ (f y True, f x 'c')
+            | let f _ z = z, x <- xs
+            | y <- ys ]
diff --git a/testsuite/tests/typecheck/should_compile/T11982b.hs b/testsuite/tests/typecheck/should_compile/T11982b.hs
new file mode 100644
index 0000000..5c695d2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11982b.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ApplicativeDo #-}
+module Main where
+import Control.Concurrent.MVar
+
+type Locker = forall a. IO a -> IO a
+
+main :: IO ()
+main = do
+    line <- getLine
+    lock <- newMVar ()
+    let locker :: Locker
+        locker = withMVar lock . const
+    f line locker
+
+f :: String -> Locker -> IO ()
+f line locker = locker $ putStrLn line
diff --git a/testsuite/tests/typecheck/should_compile/T11982c.hs b/testsuite/tests/typecheck/should_compile/T11982c.hs
new file mode 100644
index 0000000..cdc4a98
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11982c.hs
@@ -0,0 +1,18 @@
+-- This is similar to T11982b but 'locker' inlined which allows the module to
+-- compile.
+
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ApplicativeDo #-}
+module Main where
+import Control.Concurrent.MVar
+
+type Locker = forall a. IO a -> IO a
+
+main :: IO ()
+main = do
+    line <- getLine
+    lock <- newMVar ()
+    f line $ withMVar lock . const
+
+f :: String -> Locker -> IO ()
+f line locker = locker $ putStrLn line
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 3ad727d..b032121 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -511,6 +511,9 @@ test('T11811', normal, compile, [''])
 test('T11793', normal, compile, [''])
 test('T11348', normal, compile, [''])
 test('T11947', normal, compile, [''])
+test('T11982a', expect_broken(11982), compile, [''])
+test('T11982b', expect_broken(11982), compile, [''])
+test('T11982c', normal, compile, [''])
 test('T12045a', normal, compile, [''])
 test('T12064', [], multimod_compile, ['T12064', '-v0'])
 test('ExPat', normal, compile, [''])



More information about the ghc-commits mailing list