[Git][ghc/ghc][wip/marge_bot_batch_merge_job] EPA: Extend StringLiteral range to include trailing commas

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Mar 30 09:01:57 UTC 2024



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


Commits:
c24dd1f3 by Alan Zimmerman at 2024-03-30T05:01:50-04:00
EPA: Extend StringLiteral range to include trailing commas

This goes slightly against the exact printing philosophy where
trailing decorations should be in an annotation, but the
practicalities of adding it to the WarningTxt environment, and the
problems caused by deviating do not make a more principles approach
worthwhile.

- - - - -


2 changed files:

- compiler/GHC/Parser.y
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -4559,7 +4559,8 @@ addTrailingCommaN (L anns a) span = do
   return (L anns' a)
 
 addTrailingCommaS :: Located StringLiteral -> EpaLocation -> Located StringLiteral
-addTrailingCommaS (L l sl) span = L l (sl { sl_tc = Just (epaLocationRealSrcSpan span) })
+addTrailingCommaS (L l sl) span
+    = L (widenSpan l [AddEpAnn AnnComma span]) (sl { sl_tc = Just (epaLocationRealSrcSpan span) })
 
 -- -------------------------------------
 


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -652,6 +652,10 @@ printSourceText :: (Monad m, Monoid w) => SourceText -> String -> EP w m ()
 printSourceText (NoSourceText) txt   =  printStringAdvance txt >> return ()
 printSourceText (SourceText   txt) _ =  printStringAdvance (unpackFS txt) >> return ()
 
+printSourceTextAA :: (Monad m, Monoid w) => SourceText -> String -> EP w m ()
+printSourceTextAA (NoSourceText) txt   = printStringAtAA (EpaDelta (SameLine 0) []) txt >> return ()
+printSourceTextAA (SourceText   txt) _ =  printStringAtAA (EpaDelta (SameLine 0) []) (unpackFS txt) >> return ()
+
 -- ---------------------------------------------------------------------
 
 printStringAtSs :: (Monad m, Monoid w) => SrcSpan -> String -> EP w m ()
@@ -2099,7 +2103,7 @@ instance ExactPrint StringLiteral where
   setAnnotationAnchor a _ _ _ = a
 
   exact l@(StringLiteral src fs mcomma) = do
-    printSourceText src (show (unpackFS fs))
+    printSourceTextAA src (show (unpackFS fs))
     mapM_ (\r -> printStringAtRs r ",") mcomma
     return l
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c24dd1f3fafb27a37c6bef01796141d5228c204c
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/20240330/52b7c463/attachment-0001.html>


More information about the ghc-commits mailing list