[commit: ghc] master: Parenthesize pretty-printed equalities when necessary (2277172)
git at git.haskell.org
git at git.haskell.org
Thu May 11 21:33:43 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9/ghc
>---------------------------------------------------------------
commit 2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Thu May 11 15:42:55 2017 -0400
Parenthesize pretty-printed equalities when necessary
Fixes #13677 by parenthesizing equalities in a sufficiently high
pretty-printing context.
Test Plan: make test TEST=T13677
Reviewers: goldfire, austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #13677
Differential Revision: https://phabricator.haskell.org/D3570
>---------------------------------------------------------------
2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9
compiler/iface/IfaceType.hs | 2 +-
testsuite/tests/typecheck/should_fail/T13677.hs | 11 +++++++++++
testsuite/tests/typecheck/should_fail/T13677.stderr | 4 ++++
testsuite/tests/typecheck/should_fail/all.T | 1 +
4 files changed, 17 insertions(+), 1 deletion(-)
diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs
index 41cf4f6..eafd6dd 100644
--- a/compiler/iface/IfaceType.hs
+++ b/compiler/iface/IfaceType.hs
@@ -979,7 +979,7 @@ pprTyTcApp' ctxt_prec tc tys dflags style
-> text "(TypeError ...)"
| Just doc <- ppr_equality tc (tcArgsIfaceTypes tys)
- -> doc
+ -> maybeParen ctxt_prec TyConPrec doc
| otherwise
-> ppr_iface_tc_app ppr_ty ctxt_prec tc tys_wo_kinds
diff --git a/testsuite/tests/typecheck/should_fail/T13677.hs b/testsuite/tests/typecheck/should_fail/T13677.hs
new file mode 100644
index 0000000..f452a20
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T13677.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE GADTs #-}
+module T13677 where
+
+import GHC.Exts (Constraint)
+
+data Dict a where
+ Dict :: a => Dict a
+
+foo :: Dict (Int ~ Int) => Int
+foo = undefined
diff --git a/testsuite/tests/typecheck/should_fail/T13677.stderr b/testsuite/tests/typecheck/should_fail/T13677.stderr
new file mode 100644
index 0000000..c29aba2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T13677.stderr
@@ -0,0 +1,4 @@
+
+T13677.hs:10:8: error:
+ • Expected a constraint, but ‘Dict (Int ~ Int)’ has kind ‘*’
+ • In the type signature: foo :: Dict (Int ~ Int) => Int
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 4a409e0..3875063 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -438,3 +438,4 @@ test('T13506', normal, compile_fail, [''])
test('T13611', expect_broken(13611), compile_fail, [''])
test('T13320', normal, compile_fail, [''])
test('T13640', normal, compile_fail, [''])
+test('T13677', normal, compile_fail, [''])
More information about the ghc-commits
mailing list