[commit: ghc] master: Fix #15527 by pretty-printing an RdrName prefixly (5238f20)

git at git.haskell.org git at git.haskell.org
Thu Aug 16 11:30:13 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5238f204482ac7f05f4e2d2e92576288cc00d42d/ghc

>---------------------------------------------------------------

commit 5238f204482ac7f05f4e2d2e92576288cc00d42d
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Thu Aug 16 11:53:33 2018 +0200

    Fix #15527 by pretty-printing an RdrName prefixly
    
    Summary:
    When `(.) @Int` is used without enabling `TypeApplications`,
    the resulting error message will pretty-print the (symbolic)
    `RdrName` `(.)`. However, it does so without parenthesizing it, which
    causes the pretty-printed expression to appear as `. at Int`. Yuck.
    
    Since the expression in a type application will always be prefix,
    we can fix this issue by using `pprPrefixOcc` instead of plain ol'
    `ppr`.
    
    Test Plan: make test TEST=T15527
    
    Reviewers: bgamari, monoidal, simonpj
    
    Reviewed By: monoidal, simonpj
    
    Subscribers: rwbarton, carter
    
    GHC Trac Issues: #15527
    
    Differential Revision: https://phabricator.haskell.org/D5071


>---------------------------------------------------------------

5238f204482ac7f05f4e2d2e92576288cc00d42d
 compiler/hsSyn/HsExpr.hs                            | 2 +-
 testsuite/tests/typecheck/should_fail/T15527.hs     | 4 ++++
 testsuite/tests/typecheck/should_fail/T15527.stderr | 4 ++++
 testsuite/tests/typecheck/should_fail/all.T         | 1 +
 4 files changed, 10 insertions(+), 1 deletion(-)

diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index a5c65fb..6ca37e0 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -1087,7 +1087,7 @@ ppr_expr (ArithSeq _ _ info) = brackets (ppr info)
 
 ppr_expr (EWildPat _)     = char '_'
 ppr_expr (ELazyPat _ e)   = char '~' <> ppr e
-ppr_expr (EAsPat _ v e)   = ppr v <> char '@' <> ppr e
+ppr_expr (EAsPat _ (L _ v) e) = pprPrefixOcc v <> char '@' <> ppr e
 ppr_expr (EViewPat _ p e) = ppr p <+> text "->" <+> ppr e
 
 ppr_expr (HsSCC _ st (StringLiteral stl lbl) expr)
diff --git a/testsuite/tests/typecheck/should_fail/T15527.hs b/testsuite/tests/typecheck/should_fail/T15527.hs
new file mode 100644
index 0000000..b65c26c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T15527.hs
@@ -0,0 +1,4 @@
+module T15527 where
+
+f :: (Int -> Int) -> (Int -> Int) -> (Int -> Int)
+f =  (.) @Int
diff --git a/testsuite/tests/typecheck/should_fail/T15527.stderr b/testsuite/tests/typecheck/should_fail/T15527.stderr
new file mode 100644
index 0000000..dd03a0a
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T15527.stderr
@@ -0,0 +1,4 @@
+
+T15527.hs:4:6: error:
+    Pattern syntax in expression context: (.)@Int
+    Did you mean to enable TypeApplications?
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 962ffb7..9c4df89 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -478,3 +478,4 @@ test('T15330', normal, compile_fail, [''])
 test('T15361', normal, compile_fail, [''])
 test('T15438', normal, compile_fail, [''])
 test('T15523', normal, compile_fail, ['-O'])
+test('T15527', normal, compile_fail, [''])



More information about the ghc-commits mailing list