Skip to content
Snippets Groups Projects
Commit afe3e120 authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Allow untyped brackets in typed splices and vice versa.

Resolves #24190

Apparently the check was essentially always (as far as I can trace back: d0d47ba7),
and while it does catch some mismatches, the type-checker will catch
them too. OTOH, it prevents writing completely reasonable programs.
parent f5eb0f29
No related branches found
No related tags found
No related merge requests found
Pipeline #87480 passed
......@@ -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"
......
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))
'x'
'x'
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' |])
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' ||])
......@@ -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, [''])
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