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

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Mar 31 21:33:30 UTC 2024



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


Commits:
00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00: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.

- - - - -
f9884f01 by brandon s allbery kf8nh at 2024-03-31T17:33:20-04:00
clarify Note [Preproccesing invocations]

- - - - -


3 changed files:

- compiler/GHC/Parser.y
- compiler/GHC/SysTools/Cpp.hs
- 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) })
 
 -- -------------------------------------
 


=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -63,7 +63,22 @@ underlying program (the C compiler), the set of flags passed determines the
 behaviour of the preprocessor, and Cpp and HsCpp behave differently.
 Specifically, we rely on "traditional" (pre-standard) preprocessing semantics
 (which most compilers expose via the `-traditional` flag) when preprocessing
-Haskell source. This avoids, e.g., the preprocessor removing C-style comments.
+Haskell source. This avoids the following situations:
+
+  * Removal of C-style comments, which are not comments in Haskell but valid
+    operators;
+
+  * Errors due to an ANSI C preprocessor lexing the source and failing on
+    names with single quotes (TH quotes, ticked promoted constructors,
+    names with primes in them).
+
+  Both of those cases may be subtle: gcc and clang permit C++-style //
+  comments in C code, and Data.Array and Data.Vector both export a //
+  operator whose type is such that a removed "comment" may leave code that
+  typechecks but does the wrong thing. Another example is that, since ANSI
+  C permits long character constants, an expression involving multiple
+  functions with primes in their names may not expand macros properly when
+  they occur between the primed functions.
 -}
 
 -- | Run either the Haskell preprocessor or the C preprocessor, as per the


=====================================
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/-/compare/5278cd2c39d550a7ba11fe5f7c8aa40339e28430...f9884f016e07e78aff67a38786c45a536621a20e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5278cd2c39d550a7ba11fe5f7c8aa40339e28430...f9884f016e07e78aff67a38786c45a536621a20e
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/20240331/b5d96acf/attachment-0001.html>


More information about the ghc-commits mailing list