[commit: ghc] master: Test case: GHCi uses UnicodeSyntax if the loaded file uses it. (b021572)
git at git.haskell.org
git at git.haskell.org
Fri Jun 6 16:56:58 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/b0215729214859051abf78f6cf5012805fe7d764/ghc
>---------------------------------------------------------------
commit b0215729214859051abf78f6cf5012805fe7d764
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Fri Jun 6 18:42:34 2014 +0200
Test case: GHCi uses UnicodeSyntax if the loaded file uses it.
Its marked as broken, as this does not work yet, but we are calling it a
day here soon, so I want this to be recorded (#8959).
>---------------------------------------------------------------
b0215729214859051abf78f6cf5012805fe7d764
testsuite/tests/ghci/scripts/T8959b.hs | 11 +++++++++++
testsuite/tests/ghci/scripts/T8959b.script | 1 +
testsuite/tests/ghci/scripts/T8959b.stderr | 16 ++++++++++++++++
testsuite/tests/ghci/scripts/all.T | 1 +
4 files changed, 29 insertions(+)
diff --git a/testsuite/tests/ghci/scripts/T8959b.hs b/testsuite/tests/ghci/scripts/T8959b.hs
new file mode 100644
index 0000000..064b267
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T8959b.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE UnicodeSyntax, Arrows, RankNTypes #-}
+module T8959b where
+
+foo :: Int -> Int
+foo = ()
+
+bar :: ()
+bar = proc x -> do return -< x
+
+baz = () :: (forall a. a -> a) -> a
+
diff --git a/testsuite/tests/ghci/scripts/T8959b.script b/testsuite/tests/ghci/scripts/T8959b.script
new file mode 100644
index 0000000..f3c23c9
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T8959b.script
@@ -0,0 +1 @@
+:l T8959b.hs
diff --git a/testsuite/tests/ghci/scripts/T8959b.stderr b/testsuite/tests/ghci/scripts/T8959b.stderr
new file mode 100644
index 0000000..4f1ac7a
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T8959b.stderr
@@ -0,0 +1,16 @@
+
+T8959b.hs:5:7:
+ Couldn't match expected type ‘Int → Int’ with actual type ‘()’
+ In the expression: ()
+ In an equation for ‘foo’: foo = ()
+
+T8959b.hs:8:7:
+ Couldn't match expected type ‘()’ with actual type ‘t0 → m0 t0’
+ In the expression: proc x -> do { return ↢ x }
+ In an equation for ‘bar’: bar = proc x -> do { return ↢ x }
+
+T8959b.hs:10:7:
+ Couldn't match expected type ‘(∀ a2. a2 → a2) → a1’
+ with actual type ‘()’
+ In the expression: () ∷ (∀ a. a -> a) -> a
+ In an equation for ‘baz’: baz = () ∷ (∀ a. a -> a) -> a
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index b0a9912..161e14b 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -173,3 +173,4 @@ test('T8831', normal, ghci_script, ['T8831.script'])
test('T8917', normal, ghci_script, ['T8917.script'])
test('T8931', normal, ghci_script, ['T8931.script'])
test('T8959', normal, ghci_script, ['T8959.script'])
+test('T8959b', expect_broken(8959), ghci_script, ['T8959b.script'])
More information about the ghc-commits
mailing list