From 7397c7849763489cdba514cc9ad3f199947e443e Mon Sep 17 00:00:00 2001
From: Oleg Grenrus <oleg.grenrus@iki.fi>
Date: Tue, 5 Dec 2023 16:36:32 +0200
Subject: [PATCH] Allow untyped brackets in typed splices and vice versa.

Resolves #24190

Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27),
and while it does catch some mismatches, the type-checker will catch
them too. OTOH, it prevents writing completely reasonable programs.
---
 compiler/GHC/Rename/Splice.hs                 | 42 ++++++++++++++++---
 testsuite/tests/th/T24190.hs                  | 11 +++++
 testsuite/tests/th/T24190.stdout              |  2 +
 .../tests/th/TH_NestedSplicesFail3.stderr     | 11 +++--
 .../tests/th/TH_NestedSplicesFail4.stderr     | 10 +++--
 testsuite/tests/th/all.T                      |  1 +
 6 files changed, 64 insertions(+), 13 deletions(-)
 create mode 100644 testsuite/tests/th/T24190.hs
 create mode 100644 testsuite/tests/th/T24190.stdout

diff --git a/compiler/GHC/Rename/Splice.hs b/compiler/GHC/Rename/Splice.hs
index 2d7af155f025..58160a5543c2 100644
--- a/compiler/GHC/Rename/Splice.hs
+++ b/compiler/GHC/Rename/Splice.hs
@@ -85,6 +85,38 @@ checkForTemplateHaskellQuotes e =
   unlessXOptM LangExt.TemplateHaskellQuotes $
     failWith $ thSyntaxError $ IllegalTHQuotes e
 
+{-
+
+Note [Untyped quotes in typed splices and vice versa]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider this typed splice
+   $$(f [| x |])
+
+Is there anything wrong with that /typed/ splice containing an /untyped/
+quote [| x |]?   One could ask the same about an /untyped/ slice containing a
+/typed/ quote.
+
+In fact, both are fine (#24190). Presumably f's type looks something like:
+   f :: Q Expr -> Code Q Int
+
+It is pretty hard for `f` to use its (untyped code) argument to build a typed
+syntax tree, but not impossible:
+* `f` could use `unsafeCodeCoerce :: Q Exp -> Code Q a`
+* `f` could just perform case analysis on the tree
+
+But in the end all that matters is that in $$( e ), the expression `e` has the
+right type.  It doesn't matter how `e` is built.  To put it another way, the
+untyped quote `[| x |]` could also be written `varE 'x`, which is an ordinary
+expression.
+
+Moreover the ticked variable, 'x :: Name, is itself treated as an untyped quote;
+but it is a perfectly fine sub-expression to have in a typed splice.
+
+(Historical note: GHC used to unnecessarily  check that a typed quote only
+occurred in a typed splice: #24190.)
+
+-}
+
 rnTypedBracket :: HsExpr GhcPs -> LHsExpr GhcPs -> RnM (HsExpr GhcRn, FreeVars)
 rnTypedBracket e br_body
   = addErrCtxt (typedQuotationCtxtDoc br_body) $
@@ -93,9 +125,8 @@ rnTypedBracket e br_body
          -- Check for nested brackets
        ; cur_stage <- getStage
        ; case cur_stage of
-           { Splice Typed   -> return ()
-           ; Splice Untyped -> failWithTc $ thSyntaxError
-                                          $ MismatchedSpliceType Untyped IsBracket
+           { Splice _       -> return ()
+               -- See Note [Untyped quotes in typed splices and vice versa]
            ; RunSplice _    ->
                -- See Note [RunSplice ThLevel] in GHC.Tc.Types.
                pprPanic "rnTypedBracket: Renaming typed bracket when running a splice"
@@ -123,9 +154,8 @@ rnUntypedBracket e br_body
          -- Check for nested brackets
        ; cur_stage <- getStage
        ; case cur_stage of
-           { Splice Typed   -> failWithTc $ thSyntaxError
-                                          $ MismatchedSpliceType Typed IsBracket
-           ; Splice Untyped -> return ()
+           { Splice _       -> return ()
+               -- See Note [Untyped quotes in typed splices and vice versa]
            ; RunSplice _    ->
                -- See Note [RunSplice ThLevel] in GHC.Tc.Types.
                pprPanic "rnUntypedBracket: Renaming untyped bracket when running a splice"
diff --git a/testsuite/tests/th/T24190.hs b/testsuite/tests/th/T24190.hs
new file mode 100644
index 000000000000..80cf5a304b00
--- /dev/null
+++ b/testsuite/tests/th/T24190.hs
@@ -0,0 +1,11 @@
+module Main (main) where
+
+import Language.Haskell.TH
+
+main :: IO ()
+main = do
+    -- type annotations are needed so the monad is not ambiguous.
+    -- we also highlight that the monad can be different:
+    -- brackets are "just" syntax.
+    print $$(const [|| 'x' ||] ([| 'y' |]  :: IO Exp))
+    print $( const  [| 'x' |] ([|| 'y' ||] :: Code IO Char))
diff --git a/testsuite/tests/th/T24190.stdout b/testsuite/tests/th/T24190.stdout
new file mode 100644
index 000000000000..04787c443197
--- /dev/null
+++ b/testsuite/tests/th/T24190.stdout
@@ -0,0 +1,2 @@
+'x'
+'x'
diff --git a/testsuite/tests/th/TH_NestedSplicesFail3.stderr b/testsuite/tests/th/TH_NestedSplicesFail3.stderr
index 375867c1f87d..fe433256051c 100644
--- a/testsuite/tests/th/TH_NestedSplicesFail3.stderr
+++ b/testsuite/tests/th/TH_NestedSplicesFail3.stderr
@@ -1,5 +1,8 @@
 
-TH_NestedSplicesFail3.hs:4:12: error: [GHC-45108]
-    • Untyped brackets may not appear in typed splices.
-    • In the Template Haskell quotation [| 'x' |]
-      In the typed splice: $$([| 'x' |])
+TH_NestedSplicesFail3.hs:4:12: error: [GHC-39999]
+    • No instance for ‘Language.Haskell.TH.Syntax.Quote
+                         (Language.Haskell.TH.Syntax.Code Language.Haskell.TH.Syntax.Q)’
+        arising from a quotation bracket
+    • In the expression: [| 'x' |]
+      In the Template Haskell splice $$([| 'x' |])
+      In the expression: $$([| 'x' |])
diff --git a/testsuite/tests/th/TH_NestedSplicesFail4.stderr b/testsuite/tests/th/TH_NestedSplicesFail4.stderr
index 41ad9ff6e8c1..e5adec5df1b3 100644
--- a/testsuite/tests/th/TH_NestedSplicesFail4.stderr
+++ b/testsuite/tests/th/TH_NestedSplicesFail4.stderr
@@ -1,5 +1,9 @@
 
-TH_NestedSplicesFail4.hs:4:11: error: [GHC-45108]
-    • Typed brackets may not appear in untyped splices.
-    • In the Template Haskell typed quotation [|| 'y' ||]
+TH_NestedSplicesFail4.hs:4:11: error: [GHC-83865]
+    • Couldn't match type: Language.Haskell.TH.Syntax.Code m0 Char
+                     with: Language.Haskell.TH.Syntax.Q Language.Haskell.TH.Syntax.Exp
+      Expected: Language.Haskell.TH.Lib.Internal.ExpQ
+        Actual: Language.Haskell.TH.Syntax.Code m0 Char
+    • In the Template Haskell quotation [|| 'y' ||]
+      In the expression: [|| 'y' ||]
       In the untyped splice: $([|| 'y' ||])
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 5c3db230dfdb..416a0000fe3e 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -599,3 +599,4 @@ test('T23971', normal, compile_and_run, [''])
 test('T23986', normal, compile_and_run, [''])
 test('T24111', normal, compile_and_run, [''])
 test('T23719', normal, compile_fail, [''])
+test('T24190', normal, compile_and_run, [''])
-- 
GitLab