[Git][ghc/ghc][master] Fix pretty printing of overlap pragmas in TH splices (fixes #24074)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Oct 10 23:06:19 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d055f099 by Jan HrĨek at 2023-10-10T19:04:33-04:00
Fix pretty printing of overlap pragmas in TH splices (fixes #24074)
- - - - -
5 changed files:
- compiler/GHC/ThToHs.hs
- hadrian/doc/testsuite.md
- + testsuite/tests/th/T24074.hs
- + testsuite/tests/th/T24074.stderr
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -328,10 +328,10 @@ cvtDec (InstanceD o ctxt ty decs)
where
overlap pragma =
case pragma of
- TH.Overlaps -> Hs.Overlaps (SourceText $ fsLit "OVERLAPS")
- TH.Overlappable -> Hs.Overlappable (SourceText $ fsLit "OVERLAPPABLE")
- TH.Overlapping -> Hs.Overlapping (SourceText $ fsLit "OVERLAPPING")
- TH.Incoherent -> Hs.Incoherent (SourceText $ fsLit "INCOHERENT")
+ TH.Overlaps -> Hs.Overlaps (SourceText $ fsLit "{-# OVERLAPS")
+ TH.Overlappable -> Hs.Overlappable (SourceText $ fsLit "{-# OVERLAPPABLE")
+ TH.Overlapping -> Hs.Overlapping (SourceText $ fsLit "{-# OVERLAPPING")
+ TH.Incoherent -> Hs.Incoherent (SourceText $ fsLit "{-# INCOHERENT")
=====================================
hadrian/doc/testsuite.md
=====================================
@@ -68,7 +68,7 @@ more directories, under which the testsuite driver will be looking for
By default, the `test` rule tries to run all the tests available (the ones
under `testsuite/tests/` as well as all the tests of the boot libraries
-or programs (`base`, `haddock`, etc).
+or programs (`base`, `haddock`, etc)).
To restrict the testsuite driver to only run a specific directory of tests,
e.g `testsuite/tests/th`, you can simply do:
=====================================
testsuite/tests/th/T24074.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T24074 where
+
+class A a
+
+$( [d| instance {-# OVERLAPS #-} A Int |] )
+$( [d| instance {-# OVERLAPPABLE #-} A Bool |] )
+$( [d| instance {-# OVERLAPPING #-} A () |] )
+$( [d| instance {-# INCOHERENT #-} A Char |] )
=====================================
testsuite/tests/th/T24074.stderr
=====================================
@@ -0,0 +1,16 @@
+T24074.hs:6:2-43: Splicing declarations
+ [d| instance {-# OVERLAPS #-} A Int |]
+ ======>
+ instance {-# OVERLAPS #-} A Int
+T24074.hs:7:2-48: Splicing declarations
+ [d| instance {-# OVERLAPPABLE #-} A Bool |]
+ ======>
+ instance {-# OVERLAPPABLE #-} A Bool
+T24074.hs:8:2-45: Splicing declarations
+ [d| instance {-# OVERLAPPING #-} A () |]
+ ======>
+ instance {-# OVERLAPPING #-} A ()
+T24074.hs:9:2-46: Splicing declarations
+ [d| instance {-# INCOHERENT #-} A Char |]
+ ======>
+ instance {-# INCOHERENT #-} A Char
=====================================
testsuite/tests/th/all.T
=====================================
@@ -158,6 +158,7 @@ test('TH_tf1', normal, compile, ['-v0'])
test('TH_tf3', normal, compile, ['-v0'])
test('TH_pragma', normal, compile, ['-v0 -dsuppress-uniques'])
+test('T24074', normal, compile, ['-v0 -dsuppress-uniques -ddump-splices'])
test('T3177', normal, compile, ['-v0'])
test('T3177a', normal, compile_fail, ['-v0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d055f09970c863bce940dc554f7631f58080fe7a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d055f09970c863bce940dc554f7631f58080fe7a
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/20231010/eced96b1/attachment-0001.html>
More information about the ghc-commits
mailing list