[commit: ghc] master: Fix pretty-printing of zero-argument lambda expressions (3c4537e)
git at git.haskell.org
git at git.haskell.org
Fri Jun 23 17:08:02 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c/ghc
>---------------------------------------------------------------
commit 3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Fri Jun 23 11:40:10 2017 -0400
Fix pretty-printing of zero-argument lambda expressions
Using Template Haskell, one can construct lambda expressions with no
arguments. The pretty-printer isn't aware of this fact, however. This
changes that.
Test Plan: make test TEST=T13856
Reviewers: bgamari, austin, goldfire
Reviewed By: bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #13856
Differential Revision: https://phabricator.haskell.org/D3664
>---------------------------------------------------------------
3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c
compiler/hsSyn/Convert.hs | 4 ++++
libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 1 +
testsuite/tests/th/T13856.hs | 8 ++++++++
testsuite/tests/th/T13856.stderr | 1 +
testsuite/tests/th/all.T | 1 +
5 files changed, 15 insertions(+)
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 5ded8bc..8b7af27 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -784,6 +784,10 @@ cvtl e = wrapL (cvt e)
; t' <- cvtType t
; tp <- wrap_apps t'
; return $ HsAppType e' $ mkHsWildCardBndrs tp }
+ cvt (LamE [] e) = cvt e -- Degenerate case. We convert the body as its
+ -- own expression to avoid pretty-printing
+ -- oddities that can result from zero-argument
+ -- lambda expressions. See #13856.
cvt (LamE ps e) = do { ps' <- cvtPats ps; e' <- cvtl e
; return $ HsLam (mkMatchGroup FromSource
[mkSimpleMatch LambdaExpr ps' e'])}
diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
index a851a22..4173991 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
@@ -143,6 +143,7 @@ pprExp i (InfixE (Just e1) op (Just e2))
pprExp _ (InfixE me1 op me2) = parens $ pprMaybeExp noPrec me1
<+> pprInfixExp op
<+> pprMaybeExp noPrec me2
+pprExp i (LamE [] e) = pprExp i e -- #13856
pprExp i (LamE ps e) = parensIf (i > noPrec) $ char '\\' <> hsep (map (pprPat appPrec) ps)
<+> text "->" <+> ppr e
pprExp i (LamCaseE ms) = parensIf (i > noPrec)
diff --git a/testsuite/tests/th/T13856.hs b/testsuite/tests/th/T13856.hs
new file mode 100644
index 0000000..d1ef71d
--- /dev/null
+++ b/testsuite/tests/th/T13856.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -ddump-splices #-}
+module T13856 where
+
+import Language.Haskell.TH
+
+f :: Int
+f = $(lamE [] [| 42 |])
diff --git a/testsuite/tests/th/T13856.stderr b/testsuite/tests/th/T13856.stderr
new file mode 100644
index 0000000..141b7a2
--- /dev/null
+++ b/testsuite/tests/th/T13856.stderr
@@ -0,0 +1 @@
+T13856.hs:8:7-22: Splicing expression lamE [] [| 42 |] ======> 42
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 1f0a7ec..0092e5a 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -388,3 +388,4 @@ test('T13618', normal, compile_and_run, ['-v0'])
test('T13642', normal, compile_fail, ['-v0'])
test('T13781', normal, compile, ['-v0'])
test('T13782', normal, compile, [''])
+test('T13856', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
More information about the ghc-commits
mailing list