Skip to content

TemplateHaskellQuotes and RebindableSyntax don't play nicely

EDIT: The original problem described here was about untyped TH, and it was fixed in !2960 (closed). But we identify a new problem with typed Template Haskell, which has yet to be solved. #18102 (comment 292247) shows two illustrative examples.


If I say

{-# LANGUAGE TemplateHaskell, RebindableSyntax #-}

module Bug where

import Prelude ( Monad(..), Bool(..), print, ($) )
import Language.Haskell.TH.Syntax

$( do stuff <- [| if True then 10 else 15 |]
      runIO $ print stuff
      return [] )

then I get errors about ifThenElse and fromInteger not being in scope. When I bring them into scope, the code is accepted, but the quoted syntax does not mention them, instead accurately reflecting the original source Haskell I wrote.

There are several problems in this story:

  1. Template Haskell quotes are meant to work even in the presence of unbound identifiers.

  2. Template Haskell is all about quoting (and splicing) surface syntax. Quoting should not care about -XRebindableSyntax.

  3. If we were to decide that quoting should respect -XRebindableSyntax (I disagree with this design, to be clear), then the output of the quote is incorrect.

I propose: disable -XRebindableSyntax within quotes. That should fix all these problems.

Other reasonable possibility: disable -XRebindableSyntax within quotes, but use the TH combinators that are in scope (like conE and appE, etc.). I think this would be nightmarish to implement, and no one is asking for it, but it would be a consistent way forward.

Edited by Richard Eisenberg
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information