Passing a Name to a typed splice

Given a mkStuff function that takes a Name and produces Stuff using typed TH:

{-# LANGUAGE LambdaCase #-}
module Example where

import Language.Haskell.TH (Code, Name, Q)
import qualified Language.Haskell.TH as TH

data Stuff = Stuff
  { tyName :: String
  , isSynonym :: Bool
  }

mkStuff :: Name -> Code Q Stuff
mkStuff nm = do
  let tyName = TH.nameBase nm
  TH.liftCode do
    TH.reify nm >>= \case
      TH.TyConI (TH.TySynD _nmSyn _tyVars _ty) -> do
        TH.examineCode [||
          Stuff
            { tyName
            , isSynonym = True
            }
          ||]
      _other -> do
        TH.examineCode [||
          Stuff
            { tyName
            , isSynonym = False
            }
          ||]

How do I create Name values to pass to the typed splice? For example, this attempt:

module Demo where

import Scratch

type Foo = Int

x :: Stuff
x = $$(mkStuff ''Foo)

produces:

error:
    • Untyped brackets may only appear in untyped splices.
    • In the Template Haskell quotation ''Foo
      In the typed splice: $$(mkStuff ''Foo)
   |
   | x = $$(mkStuff ''Foo)
   |

That error message is at least very confusing, so I’d recommend reporting it at Issues Ā· Glasgow Haskell Compiler / GHC Ā· GitLab.

The easy way to solve this seems to be to do:

x = $(unTypeCode (mkStuff ''Foo))

That gives a new error:

Main.hs:9:6: error:
    • ā€˜Foo’ is not in the type environment at a reify
    • In the untyped splice: $(unTypeCode (mkStuff ''Foo))
  |
9 | x = $(unTypeCode (mkStuff ''Foo))
  |      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Edit: But this works:

module Demo where

import Example
import Language.Haskell.TH

type Foo = Int

$(pure [])

x = $(unTypeCode (mkStuff ''Foo))
2 Likes

Interesting - thank you. What’s the reason behind splitting up the type synonym and x with a dummy splice?

I also see that if I have the type synonym in one module and x in another that seems to work. I take it the dummy splice separates things in an equivalent way to separate modules from TH’s point of view?

Yes, I don’t understand it much better than that, I’m afraid.

See the discussion of ā€œdeclaration groupsā€ in the ghc manual: 6.13. Template Haskell — Glasgow Haskell Compiler 9.13.20250110 User's Guide

Top-level declaration splices break up a source file into declaration groups. A declaration group is the group of declarations created by a top-level declaration splice, plus those following it, down to but not including the next top-level declaration splice. N.B. only top-level splices delimit declaration groups, not expression splices. The first declaration group in a module includes all top-level definitions down to but not including the first top-level declaration splice.

Each group is compiled just like a separately compiled module. That is:

  • Later groups can ā€œseeā€ declarations, and instance declarations, from earlier groups;
  • But earlier groups cannot ā€œseeā€ declarations, or instance declarations, from later groups.

Each declaration group is mutually recursive only within the group. Declaration groups can refer to definitions within previous groups, but not later ones.

1 Like