Skip to content
Snippets Groups Projects
Commit 46fd8ced authored by Vladislav Zavialov's avatar Vladislav Zavialov Committed by Marge Bot
Browse files

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
parent 1b15dbc4
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
{-# LANGUAGE TemplateHaskell #-}
module T23748 where
$([d| a ~ b = ()
a @ b = ()
|])
\ No newline at end of file
......@@ -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, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment