[commit: ghc] master: Properly designate LambdaCase alts as CaseAlt in TH (32008a9)

git at git.haskell.org git at git.haskell.org
Tue Aug 14 23:03:14 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/32008a9d0e09f0cc8899aa871d9a6b63fcc28a1a/ghc

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

commit 32008a9d0e09f0cc8899aa871d9a6b63fcc28a1a
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Tue Aug 14 22:35:23 2018 +0200

    Properly designate LambdaCase alts as CaseAlt in TH
    
    Summary:
    When `\case` expressions are parsed normally, their
    alternatives are marked as `CaseAlt` (which means that they are
    pretty-printed without a `\` character in front of them, unlike for
    lambda expressions). However, `\case` expressions created by way of
    Template Haskell (in `Convert`) inconsistently designated the case
    alternatives as `LambdaExpr`, causing them to be pretty-printed
    poorly (as shown in #15518). The fix is simple: use `CaseAlt`
    consistently.
    
    Test Plan: make test TEST=T15518
    
    Reviewers: goldfire, bgamari
    
    Subscribers: rwbarton, carter
    
    GHC Trac Issues: #15518
    
    Differential Revision: https://phabricator.haskell.org/D5069


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

32008a9d0e09f0cc8899aa871d9a6b63fcc28a1a
 compiler/hsSyn/Convert.hs        |  2 +-
 testsuite/tests/th/T15518.hs     |  8 ++++++++
 testsuite/tests/th/T15518.stderr | 10 ++++++++++
 testsuite/tests/th/all.T         |  1 +
 4 files changed, 20 insertions(+), 1 deletion(-)

diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 84e4594..fbecf9c 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -829,7 +829,7 @@ cvtl e = wrapL (cvt e)
                             ; return $ HsLam noExt (mkMatchGroup FromSource
                                              [mkSimpleMatch LambdaExpr
                                              pats e'])}
-    cvt (LamCaseE ms)  = do { ms' <- mapM (cvtMatch LambdaExpr) ms
+    cvt (LamCaseE ms)  = do { ms' <- mapM (cvtMatch CaseAlt) ms
                             ; return $ HsLamCase noExt
                                                    (mkMatchGroup FromSource ms')
                             }
diff --git a/testsuite/tests/th/T15518.hs b/testsuite/tests/th/T15518.hs
new file mode 100644
index 0000000..eb424a9
--- /dev/null
+++ b/testsuite/tests/th/T15518.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE TemplateHaskell #-}
+module T15518 where
+
+$([d| f :: Bool -> ()
+      f = \case True  -> ()
+                False -> ()
+    |])
diff --git a/testsuite/tests/th/T15518.stderr b/testsuite/tests/th/T15518.stderr
new file mode 100644
index 0000000..7d9ef29
--- /dev/null
+++ b/testsuite/tests/th/T15518.stderr
@@ -0,0 +1,10 @@
+T15518.hs:(5,3)-(8,6): Splicing declarations
+    [d| f :: Bool -> ()
+        f = \case
+              True -> ()
+              False -> () |]
+  ======>
+    f :: Bool -> ()
+    f = \case
+          True -> ()
+          False -> ()
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 0fddd44..5c7037d 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -425,3 +425,4 @@ test('T14471', normal, compile, [''])
 test('TH_rebindableAdo', normal, compile, [''])
 test('T14627', normal, compile_fail, [''])
 test('TH_invalid_add_top_decl', normal, compile_fail, [''])
+test('T15518', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])



More information about the ghc-commits mailing list