[Git][ghc/ghc][wip/int-index/th-ops-tilde-atsign] Fix (~) and (@) infix operators in TH splices (#23748)
Vladislav Zavialov (@int-index)
gitlab at gitlab.haskell.org
Tue Aug 1 13:58:26 UTC 2023
Vladislav Zavialov pushed to branch wip/int-index/th-ops-tilde-atsign at Glasgow Haskell Compiler / GHC
Commits:
94c49e1e by Vladislav Zavialov at 2023-08-01T15:56:26+02:00
Fix (~) and (@) infix operators in TH splices (#23748)
8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept
the following infix operators:
a ~ b = ()
a @ b = ()
But not if TH is used to generate those declarations:
$([d| a ~ b = ()
a @ b = ()
|])
-- Test.hs:5:2: error: [GHC-55017]
-- Illegal variable name: ‘~’
-- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.()
This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme
- - - - -
3 changed files:
- compiler/GHC/Utils/Lexeme.hs
- + testsuite/tests/th/T23748.hs
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/Utils/Lexeme.hs
=====================================
@@ -227,10 +227,11 @@ reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving"
, "module", "newtype", "of", "then", "type", "where"
, "_" ]
--- | All reserved operators. Taken from section 2.4 of the 2010 Report.
+-- | All reserved operators. Taken from section 2.4 of the 2010 Report,
+-- excluding @\@@ and @~@ that are allowed by GHC (see GHC Proposal #229).
reservedOps :: Set.Set String
reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->"
- , "@", "~", "=>" ]
+ , "=>" ]
-- | Does this string contain only dashes and has at least 2 of them?
isDashes :: String -> Bool
=====================================
testsuite/tests/th/T23748.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T23748 where
+
+$([d| a ~ b = ()
+ a @ b = ()
+ |])
\ No newline at end of file
=====================================
testsuite/tests/th/all.T
=====================================
@@ -580,3 +580,4 @@ test('T22559b', normal, compile_fail, [''])
test('T22559c', normal, compile_fail, [''])
test('T23525', normal, compile, [''])
test('CodeQ_HKD', normal, compile, [''])
+test('T23748', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/94c49e1ec37347f4b8b1dd59134b4034c7deff0e
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/94c49e1ec37347f4b8b1dd59134b4034c7deff0e
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/20230801/317a0397/attachment-0001.html>
More information about the ghc-commits
mailing list