Skip to content
Snippets Groups Projects
Commit 5e6cf2a9 authored by Ryan Scott's avatar Ryan Scott Committed by Krzysztof Gogolewski
Browse files

Fix #15550 by quoting RULE names during TH conversion

Summary:
When converting a `RuleP` to a GHC source `RuleD` during TH
conversion, we were stupidly not double-quoting the name of the rule.
Easily fixed.

Test Plan: make test TEST=T15550

Reviewers: goldfire, bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, carter

GHC Trac Issues: #15550

Differential Revision: https://phabricator.haskell.org/D5090
parent c523525b
No related branches found
No related tags found
No related merge requests found
...@@ -705,8 +705,8 @@ cvtPragmaD (RuleP nm bndrs lhs rhs phases) ...@@ -705,8 +705,8 @@ cvtPragmaD (RuleP nm bndrs lhs rhs phases)
; rhs' <- cvtl rhs ; rhs' <- cvtl rhs
; returnJustL $ Hs.RuleD noExt ; returnJustL $ Hs.RuleD noExt
$ HsRules noExt (SourceText "{-# RULES") $ HsRules noExt (SourceText "{-# RULES")
[noLoc $ HsRule noExt (noLoc (SourceText nm,nm')) act [noLoc $ HsRule noExt (noLoc (quotedSourceText nm,nm'))
bndrs' lhs' rhs'] act bndrs' lhs' rhs']
} }
cvtPragmaD (AnnP target exp) cvtPragmaD (AnnP target exp)
......
{-# LANGUAGE TemplateHaskell #-}
module T15550 where
$([d| myId :: a -> a
myId x = x
{-# NOINLINE [1] myId #-}
{-# RULES "myId" forall x. myId x = x #-}
|])
T15550.hs:(4,3)-(8,6): Splicing declarations
[d| {-# RULES "myId" forall x. myId x = x #-}
myId :: a -> a
myId x = x
{-# NOINLINE [1] myId #-} |]
======>
myId :: a -> a
myId x = x
{-# NOINLINE [1] myId #-}
{-# RULES "myId" forall x. myId x = x #-}
...@@ -425,4 +425,5 @@ test('T14471', normal, compile, ['']) ...@@ -425,4 +425,5 @@ test('T14471', normal, compile, [''])
test('TH_rebindableAdo', normal, compile, ['']) test('TH_rebindableAdo', normal, compile, [''])
test('T14627', normal, compile_fail, ['']) test('T14627', normal, compile_fail, [''])
test('TH_invalid_add_top_decl', normal, compile_fail, ['']) test('TH_invalid_add_top_decl', normal, compile_fail, [''])
test('T15550', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T15518', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T15518', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
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