[Git][ghc/ghc][wip/marge_bot_batch_merge_job] EPA: Preserve comments in Match Pats

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Apr 29 10:04:31 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
c4bc82f5 by Alan Zimmerman at 2024-04-29T06:04:19-04:00
EPA: Preserve comments in Match Pats

Closes #24708
Closes #24715
Closes #24734

- - - - -


6 changed files:

- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/MatchPatComments.hs
- testsuite/tests/printer/all.T
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -1244,7 +1244,7 @@ transferAnnsOnlyA (EpAnn a an cs) (EpAnn a' an' cs')
 
 -- | Transfer comments from the annotations in the
 -- first 'SrcSpanAnnA' argument to those in the second.
-transferCommentsOnlyA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA,  SrcSpanAnnA)
+transferCommentsOnlyA :: EpAnn a -> EpAnn b -> (EpAnn a,  EpAnn b)
 transferCommentsOnlyA (EpAnn a an cs) (EpAnn a' an' cs')
   = (EpAnn a an emptyComments, EpAnn a' an' (cs <> cs'))
 


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1220,19 +1220,23 @@ checkLPat e@(L l _) = checkPat l e [] []
 checkPat :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> [HsConPatTyArg GhcPs] -> [LPat GhcPs]
          -> PV (LPat GhcPs)
 checkPat loc (L l e@(PatBuilderVar (L ln c))) tyargs args
-  | isRdrDataCon c = return . L loc $ ConPat
-      { pat_con_ext = noAnn -- AZ: where should this come from?
-      , pat_con = L ln c
-      , pat_args = PrefixCon tyargs args
-      }
+  | isRdrDataCon c = do
+      let (_l', loc') = transferCommentsOnlyA l loc
+      return . L loc' $ ConPat
+        { pat_con_ext = noAnn -- AZ: where should this come from?
+        , pat_con = L ln c
+        , pat_args = PrefixCon tyargs args
+        }
   | (not (null args) && patIsRec c) = do
       ctx <- askParseContext
       patFail (locA l) . PsErrInPat e $ PEIP_RecPattern args YesPatIsRecursive ctx
-checkPat loc (L _ (PatBuilderAppType f at t)) tyargs args =
-  checkPat loc f (HsConPatTyArg at t : tyargs) args
-checkPat loc (L _ (PatBuilderApp f e)) [] args = do
-  p <- checkLPat e
-  checkPat loc f [] (p : args)
+checkPat loc (L _ (PatBuilderAppType (L lf f) at t)) tyargs args = do
+  let (loc', lf') = transferCommentsOnlyA loc lf
+  checkPat loc' (L lf' f) (HsConPatTyArg at t : tyargs) args
+checkPat loc (L _ (PatBuilderApp f (L le e))) [] args = do
+  let (loc', le') = transferCommentsOnlyA loc le
+  p <- checkLPat (L le' e)
+  checkPat loc' f [] (p : args)
 checkPat loc (L l e) [] [] = do
   p <- checkAPat loc e
   return (L l p)
@@ -1432,20 +1436,27 @@ isFunLhs e = go e [] [] []
  where
    mk = fmap ArgPatBuilderVisPat
 
-   go (L _ (PatBuilderVar (L loc f))) es ops cps
-       | not (isRdrDataCon f)        = return (Just (L loc f, Prefix, es, (reverse ops) ++ cps))
-   go (L _ (PatBuilderApp f e))   es       ops cps = go f (mk e:es) ops cps
-   go (L l (PatBuilderPar _ e _)) es@(_:_) ops cps = go e es (o:ops) (c:cps)
+   go (L l (PatBuilderVar (L loc f))) es ops cps
+       | not (isRdrDataCon f)        = do
+           let (_l, loc') = transferCommentsOnlyA l loc
+           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+   go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
+     let (_l, lf') = transferCommentsOnlyA l lf
+     go (L lf' f) (mk e:es) ops cps
+   go (L l (PatBuilderPar _ (L le e) _)) es@(_:_) ops cps = go (L le' e) es (o:ops) (c:cps)
       -- NB: es@(_:_) means that there must be an arg after the parens for the
       -- LHS to be a function LHS. This corresponds to the Haskell Report's definition
       -- of funlhs.
      where
+       (_l, le') = transferCommentsOnlyA l le
        (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp l (L loc' op) r anns)) es ops cps
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
-      = return (Just (L loc' op, Infix, (mk l:mk r:es), (anns ++ reverse ops ++ cps)))
+      = do { let (_l, ll') = transferCommentsOnlyA loc ll
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
       | otherwise                     -- Infix data con; keep going
-      = do { mb_l <- go l es ops cps
+      = do { let (_l, ll') = transferCommentsOnlyA loc ll
+           ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
           reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
@@ -1454,12 +1465,13 @@ isFunLhs e = go e [] [] []
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
                                     (L loc' op) r (reverse ops ++ cps))
           reassociate _other = Nothing
-   go (L _ (PatBuilderAppType pat tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
-             = go pat (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
+   go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
+             = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
              where invis_pat = InvisPat tok ty_pat
                    anc' = case tok of
                      NoEpTok -> anc
                      EpTok l -> widenAnchor anc [AddEpAnn AnnAnyclass l]
+                   (_l, lp') = transferCommentsOnlyA l lp
    go _ _ _ _ = return Nothing
 
 data ArgPatBuilder p


=====================================
testsuite/tests/printer/Makefile
=====================================
@@ -831,3 +831,8 @@ PprLetIn:
 CaseAltComments:
 	$(CHECK_PPR)   $(LIBDIR) CaseAltComments.hs
 	$(CHECK_EXACT) $(LIBDIR) CaseAltComments.hs
+
+.PHONY: MatchPatComments
+MatchPatComments:
+	$(CHECK_PPR)   $(LIBDIR) MatchPatComments.hs
+	$(CHECK_EXACT) $(LIBDIR) MatchPatComments.hs


=====================================
testsuite/tests/printer/MatchPatComments.hs
=====================================
@@ -0,0 +1,16 @@
+module MatchPatComments where
+
+expandProcess
+        outCHAs -- c0
+        locationDescr =
+    blah
+
+next
+    ( steps  -- c1
+    , ys     -- c2
+    ) x      -- c3
+    = (steps, x, ys)
+
+makeProjection
+    Function{funMutual = VV, -- c4
+             funAbstr = ConcreteDef} = undefined


=====================================
testsuite/tests/printer/all.T
=====================================
@@ -199,3 +199,4 @@ test('AnnotationNoListTuplePuns', [ignore_stderr, req_ppr_deps], makefile_test,
 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'])


=====================================
utils/check-exact/Main.hs
=====================================
@@ -128,7 +128,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Ppr034.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr035.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr036.hs" Nothing
- "../../testsuite/tests/printer/Ppr037.hs" Nothing
+ "../../testsuite/tests/printer/MatchPatComments.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr038.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr039.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr040.hs" Nothing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c4bc82f5cc357a2bd7f6341c3bd35b5fb867337d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c4bc82f5cc357a2bd7f6341c3bd35b5fb867337d
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/20240429/64976bdf/attachment-0001.html>


More information about the ghc-commits mailing list