[Git][ghc/ghc][master] EPA: fix span for empty \case(s)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu May 2 12:20:49 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00
EPA: fix span for empty \case(s)
In
instance SDecide Nat where
SZero %~ (SSucc _) = Disproved (\case)
Ensure the span for the HsLam covers the full construct.
Closes #24748
- - - - -
4 changed files:
- compiler/GHC/Parser.y
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/Test24748.hs
- testsuite/tests/printer/all.T
Changes:
=====================================
compiler/GHC/Parser.y
=====================================
@@ -2900,10 +2900,10 @@ aexp :: { ECP }
[mj AnnLam $1] }
| '\\' 'lcase' altslist(pats1)
{ ECP $ $3 >>= \ $3 ->
- mkHsLamPV (comb2 $1 $>) LamCase $3 [mj AnnLam $1,mj AnnCase $2] }
+ mkHsLamPV (comb3 $1 $2 $>) LamCase $3 [mj AnnLam $1,mj AnnCase $2] }
| '\\' 'lcases' altslist(argpats)
{ ECP $ $3 >>= \ $3 ->
- mkHsLamPV (comb2 $1 $>) LamCases $3 [mj AnnLam $1,mj AnnCases $2] }
+ mkHsLamPV (comb3 $1 $2 $>) LamCases $3 [mj AnnLam $1,mj AnnCases $2] }
| 'if' exp optSemi 'then' exp optSemi 'else' exp
{% runPV (unECP $2) >>= \ ($2 :: LHsExpr GhcPs) ->
return $ ECP $
=====================================
testsuite/tests/printer/Makefile
=====================================
@@ -837,6 +837,11 @@ MatchPatComments:
$(CHECK_PPR) $(LIBDIR) MatchPatComments.hs
$(CHECK_EXACT) $(LIBDIR) MatchPatComments.hs
+.PHONY: Test24748
+Test24748:
+ $(CHECK_PPR) $(LIBDIR) Test24748.hs
+ $(CHECK_EXACT) $(LIBDIR) Test24748.hs
+
.PHONY: DataDeclShort
DataDeclShort:
$(CHECK_PPR) $(LIBDIR) DataDeclShort.hs
=====================================
testsuite/tests/printer/Test24748.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE LambdaCase #-}
+module Test24748 where
+
+instance SDecide Nat where
+ SZero %~ (SSucc _) = Disproved (\case)
+
+foo = (\case)
+bar = (\cases)
=====================================
testsuite/tests/printer/all.T
=====================================
@@ -200,4 +200,5 @@ test('Test24533', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24533'])
test('PprLetIn', [ignore_stderr, req_ppr_deps], makefile_test, ['PprLetIn'])
test('CaseAltComments', [ignore_stderr, req_ppr_deps], makefile_test, ['CaseAltComments'])
test('MatchPatComments', [ignore_stderr, req_ppr_deps], makefile_test, ['MatchPatComments'])
+test('Test24748', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24748'])
test('DataDeclShort', [ignore_stderr, req_ppr_deps], makefile_test, ['DataDeclShort'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/167a56a003106ed84742e3970cc2189ffb98b0c7
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/167a56a003106ed84742e3970cc2189ffb98b0c7
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240502/8854cfc6/attachment-0001.html>
More information about the ghc-commits
mailing list