[commit: ghc] ghc-8.6: Parenthesize rank-n contexts in Convert (a6a83d9)
git at git.haskell.org
git at git.haskell.org
Thu Jul 12 21:07:03 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.6
Link : http://ghc.haskell.org/trac/ghc/changeset/a6a83d9a26db2593fa0e09dcad4c1411d6deb4ac/ghc
>---------------------------------------------------------------
commit a6a83d9a26db2593fa0e09dcad4c1411d6deb4ac
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Thu Jul 5 08:50:56 2018 -0400
Parenthesize rank-n contexts in Convert
Summary: A simple oversight.
Test Plan: make test TEST=T15324
Reviewers: goldfire, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15324
Differential Revision: https://phabricator.haskell.org/D4910
(cherry picked from commit 57733978482dc1e566a7d4cd90d4cbbd1315e3b2)
>---------------------------------------------------------------
a6a83d9a26db2593fa0e09dcad4c1411d6deb4ac
compiler/hsSyn/Convert.hs | 4 +++-
testsuite/tests/th/T15324.hs | 7 +++++++
testsuite/tests/th/T15324.stderr | 6 ++++++
testsuite/tests/th/all.T | 1 +
4 files changed, 17 insertions(+), 1 deletion(-)
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 1c3c853..c64cb7c 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -1284,7 +1284,9 @@ cvtTypeKind ty_str ty
x'' <- case x' of
L _ HsFunTy{} -> returnL (HsParTy noExt x')
L _ HsForAllTy{} -> returnL (HsParTy noExt x')
- -- #14646
+ -- #14646
+ L _ HsQualTy{} -> returnL (HsParTy noExt x')
+ -- #15324
_ -> return x'
returnL (HsFunTy noExt x'' y')
| otherwise ->
diff --git a/testsuite/tests/th/T15324.hs b/testsuite/tests/th/T15324.hs
new file mode 100644
index 0000000..ea124f4
--- /dev/null
+++ b/testsuite/tests/th/T15324.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TemplateHaskell #-}
+module T15324 where
+
+$([d| f :: forall a. (Show a => a) -> a
+ f _ = undefined
+ |])
diff --git a/testsuite/tests/th/T15324.stderr b/testsuite/tests/th/T15324.stderr
new file mode 100644
index 0000000..49db9ed
--- /dev/null
+++ b/testsuite/tests/th/T15324.stderr
@@ -0,0 +1,6 @@
+T15324.hs:(5,3)-(7,6): Splicing declarations
+ [d| f :: forall a. (Show a => a) -> a
+ f _ = undefined |]
+ ======>
+ f :: forall a. (Show a => a) -> a
+ f _ = undefined
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 6209fde..5f756fc 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -416,3 +416,4 @@ test('T14885b', normal, compile, [''])
test('T14885c', normal, compile, [''])
test('T15243', normal, compile, ['-dsuppress-uniques'])
test('T15331', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('T15324', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
More information about the ghc-commits
mailing list