[commit: ghc] master: Test Trac #10112 (104c0ad)
git at git.haskell.org
git at git.haskell.org
Mon Mar 2 16:39:42 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899/ghc
>---------------------------------------------------------------
commit 104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Feb 26 17:27:15 2015 +0000
Test Trac #10112
>---------------------------------------------------------------
104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899
testsuite/tests/rebindable/T10112.hs | 16 ++++++++++++++++
testsuite/tests/rebindable/all.T | 1 +
2 files changed, 17 insertions(+)
diff --git a/testsuite/tests/rebindable/T10112.hs b/testsuite/tests/rebindable/T10112.hs
new file mode 100644
index 0000000..1cfe49e
--- /dev/null
+++ b/testsuite/tests/rebindable/T10112.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE RankNTypes, RebindableSyntax #-}
+module T10112 where
+
+import qualified Prelude as P
+
+(>>=) :: a -> ((forall b . b) -> c) -> c
+a >>= f = f P.undefined
+return a = a
+fail s = P.undefined
+
+t1 = 'd' >>= (\_ -> 'k')
+
+t2 = do { _ <- 'd'
+ ; 'k' }
+
+foo = P.putStrLn [t1, t2]
diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T
index 70628fa..6d7283e 100644
--- a/testsuite/tests/rebindable/all.T
+++ b/testsuite/tests/rebindable/all.T
@@ -31,3 +31,4 @@ test('T5038', normal, compile_and_run, [''])
test('T4851', normal, compile, [''])
test('T5908', normal, compile, [''])
+test('T10112', normal, compile, [''])
More information about the ghc-commits
mailing list