[Git][ghc/ghc][wip/T24190] Allow untyped brackets in typed splices and vice versa.

Oleg Grenrus (@phadej) gitlab at gitlab.haskell.org
Tue Dec 5 17:12:10 UTC 2023



Oleg Grenrus pushed to branch wip/T24190 at Glasgow Haskell Compiler / GHC


Commits:
aaece53d by Oleg Grenrus at 2023-12-05T19:12:02+02:00
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.

- - - - -


6 changed files:

- compiler/GHC/Rename/Splice.hs
- + testsuite/tests/th/T24190.hs
- + testsuite/tests/th/T24190.stdout
- testsuite/tests/th/TH_NestedSplicesFail3.stderr
- testsuite/tests/th/TH_NestedSplicesFail4.stderr
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -93,9 +93,7 @@ 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 ()
            ; RunSplice _    ->
                -- See Note [RunSplice ThLevel] in GHC.Tc.Types.
                pprPanic "rnTypedBracket: Renaming typed bracket when running a splice"
@@ -123,9 +121,7 @@ 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 ()
            ; RunSplice _    ->
                -- See Note [RunSplice ThLevel] in GHC.Tc.Types.
                pprPanic "rnUntypedBracket: Renaming untyped bracket when running a splice"


=====================================
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))


=====================================
testsuite/tests/th/T24190.stdout
=====================================
@@ -0,0 +1,2 @@
+'x'
+'x'


=====================================
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' |])


=====================================
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' ||])


=====================================
testsuite/tests/th/all.T
=====================================
@@ -598,3 +598,4 @@ test('T23968', normal, compile_and_run, [''])
 test('T23971', normal, compile_and_run, [''])
 test('T23986', normal, compile_and_run, [''])
 test('T24111', normal, compile_and_run, [''])
+test('T24190', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaece53d655dfbfdd6bcf76eaa3b9007b7553b76

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaece53d655dfbfdd6bcf76eaa3b9007b7553b76
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/20231205/3911dd8b/attachment-0001.html>


More information about the ghc-commits mailing list