[Git][ghc/ghc][master] Fix (~) and (@) infix operators in TH splices (#23748)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Aug 4 16:29:34 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
46fd8ced by Vladislav Zavialov at 2023-08-04T12:28:44-04: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
=====================================
@@ -581,3 +581,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/46fd8ced0cc031f2e50a1a4b348738fd39b4a741

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46fd8ced0cc031f2e50a1a4b348738fd39b4a741
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/20230804/6fc7a9bd/attachment-0001.html>


More information about the ghc-commits mailing list