[commit: ghc] ghc-8.0: FunDep printer: Fix unicode arrow (38036f0)
git at git.haskell.org
git at git.haskell.org
Wed Aug 24 00:22:37 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/38036f0d3f0a3776e8aba561f4572a426bb29ee4/ghc
>---------------------------------------------------------------
commit 38036f0d3f0a3776e8aba561f4572a426bb29ee4
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date: Fri May 20 04:39:57 2016 -0400
FunDep printer: Fix unicode arrow
The arrow should be printed in unicode arrow syntax when
-fprint-unicode-syntax is used.
Reviewers: austin, bgamari, thomie
Reviewed By: thomie
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2243
GHC Trac Issues: #11825
(cherry picked from commit 08e47ca9849ab986d0367746a003754fcf0d4176)
>---------------------------------------------------------------
38036f0d3f0a3776e8aba561f4572a426bb29ee4
compiler/types/Class.hs | 2 +-
testsuite/tests/ghci/should_run/T11825.hs | 4 ++++
.../tests/ghci/{scripts/T8959b.script => should_run/T11825.script} | 3 ++-
testsuite/tests/ghci/should_run/T11825.stdout | 4 ++++
testsuite/tests/ghci/should_run/all.T | 1 +
5 files changed, 12 insertions(+), 2 deletions(-)
diff --git a/compiler/types/Class.hs b/compiler/types/Class.hs
index b182e46..77bae72 100644
--- a/compiler/types/Class.hs
+++ b/compiler/types/Class.hs
@@ -300,7 +300,7 @@ pprFundeps [] = empty
pprFundeps fds = hsep (vbar : punctuate comma (map pprFunDep fds))
pprFunDep :: Outputable a => FunDep a -> SDoc
-pprFunDep (us, vs) = hsep [interppSP us, text "->", interppSP vs]
+pprFunDep (us, vs) = hsep [interppSP us, arrow, interppSP vs]
instance Data.Data Class where
-- don't traverse?
diff --git a/testsuite/tests/ghci/should_run/T11825.hs b/testsuite/tests/ghci/should_run/T11825.hs
new file mode 100644
index 0000000..c3dd32e
--- /dev/null
+++ b/testsuite/tests/ghci/should_run/T11825.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE FunctionalDependencies #-}
+
+class X a b | a -> b where
+ to :: a -> b
diff --git a/testsuite/tests/ghci/scripts/T8959b.script b/testsuite/tests/ghci/should_run/T11825.script
similarity index 53%
copy from testsuite/tests/ghci/scripts/T8959b.script
copy to testsuite/tests/ghci/should_run/T11825.script
index e4d0df6..7c9d10a 100644
--- a/testsuite/tests/ghci/scripts/T8959b.script
+++ b/testsuite/tests/ghci/should_run/T11825.script
@@ -1,2 +1,3 @@
:set -fprint-unicode-syntax
-:l T8959b.hs
+:load T11825.hs
+:info X
diff --git a/testsuite/tests/ghci/should_run/T11825.stdout b/testsuite/tests/ghci/should_run/T11825.stdout
new file mode 100644
index 0000000..9ab7b1b
--- /dev/null
+++ b/testsuite/tests/ghci/should_run/T11825.stdout
@@ -0,0 +1,4 @@
+class X a b | a → b where
+ to ∷ a → b
+ {-# MINIMAL to #-}
+ -- Defined at T11825.hs:3:1
diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T
index 930f14b..08fe33d 100644
--- a/testsuite/tests/ghci/should_run/all.T
+++ b/testsuite/tests/ghci/should_run/all.T
@@ -23,3 +23,4 @@ test('T9915', just_ghci, ghci_script, ['T9915.script'])
test('T10145', just_ghci, ghci_script, ['T10145.script'])
test('T7253', just_ghci, ghci_script, ['T7253.script'])
test('T11328', just_ghci, ghci_script, ['T11328.script'])
+test('T11825', just_ghci, ghci_script, ['T11825.script'])
More information about the ghc-commits
mailing list