What is your recent (>= GHC 9.4) experience using Template Haskell?

Over the years, I have perceived that Template Haskell is much less popular than, e.g. GHC.Generics, for example for custom deriving strategies.
I’m wondering if that perception is supported by evidence, so I want to collect some experience reports.

  1. What are your greatest annoyances about Template Haskell? (Perhaps perf, cross compile support, stage restriction, missing language features for quotes, API of template-haskell, …)
  2. Do you use GHC.Generics instead? If so, why?
  3. Have you tried Template Haskell on a more recent GHC? For example, GHC 9.4 drastically improves recompilation avoidance.
  4. Are you using typed Template Haskell? If so, do you have specific annoyances?
  5. Would you be interested in having a Scheme- or Lean-like macro system? What would be your use case?
12 Likes

In my previous job, I was mainly working on the ~200 module core package of the product. By the time I left, we were at GHC 8.10. The main reason I avoided TH in that setting was due to excessive module recompilations slowing down iterative development and making the IDE experience more sluggish. We were still using TH quite a lot, but I was always on the lookout for de-THifying a module whenever it was convenient to do so.

I also occasionally bumped into the issues due to stages introduced by TH slices. Usually mostly an annoyance in having to move around symbols and introducing unnecessary git diff, so not too hard to work around, but I remember it causing some non-trivial headache on a number of occasions due to forcing you to break up a mutually recursive set of definitions.

I’m not sure if that’s in-scope for this question, but another issue that mildly annoyed me was with quasi quotes from libraries like postgresql-query where you spliced in Haskell expressions into code from another language (SQL in this case). In that case, not only did you lose syntax highlighting and all IDE support for the spliced-in Haskell code, but the error messages also pointed at the whole quasi quote. That’s why I’ve been wishing for some first-class string interpolation support in the language, so that the dev tooling would work better around such code. Though in my heart, a solution worthy of Haskell would be the introduction of some abstractions that would be a bridge between the semantics of your code and the language server, similar to how Monad is a bridge between your code and the do notation.

Lastly, I also feel like TH splices introduce an opaque barrier for type inference between what’s outside and what’s inside. Though admittedly I’ve never used typed Template Haskell and I believe it solves this very problem.

5 Likes

I agree with that perception, I disagree with the status quo.

I’m under the impression that Generics are far more of a gimmick than an actual good programming strategy, and that the ecosystem would be far better without it (or at least not much different from what it is currently). The ability to tie code behavior to data representation might’ve seemed good on paper a decade ago, but it leads to more boilerplate and less customizability, precisely the opposite of what I want when programming.

Template Haskell on the other hand is an old trusty sledgehammer that I have no quarrels with on implementation level, yet I wish the features it’s used for were properly integrated into the language instead. Compilation-time literal typeclasses (quasiquoting), access to type fields using record names (lens) and datatype precompilation (productive use of typed slices btw), there’s probably more I’m not aware of. I feel like adding these to GHC proper would be far more desirable than any meta-level improvements you can come up with.

2 Likes

I agree! Quasiquote errors not pointing to the appropriate part is very annoying. This GHC issue tracks it: #24440: More informative error reporting from QuasiQuoters · Issues · Glasgow Haskell Compiler / GHC · GitLab. Ive sketched one possible solution there. I don’t think it should take too much work to implement

3 Likes

Thanks a lot @sgraf!

  1. As someone who depends on packages using TH, I noticed that every GHC version bump is a burden on their maintainers, which slows the support. As someone who uses TH, stage limitations & UX are my main gripes.

  2. Yes I do, heavily. Better UX, especially with DerivingVia. UX could be improved with upstreaming GitHub - ElderEphemera/deriving-th: A proof of concept GHC plugin for Template Haskell based deriving or democratising its usage. Which is a pity because in applications with lots of generic deriving (JSON instances for instance), the memory footprint of Generics is horrendous.

  3. I do but I think Cabal’s own recompilation problems might be hiding these improvements.

  4. I can’t, as (IIRC) there are no typed versions of Dec and Pat(the latter one being important for my quasi-quoters).

  5. That would be fantastic.
    I would make an extensible eDSL for Haddock, where people can bring their own plugins without me having to support everything under the sun. Concrete usecase: Mermaid rendering for graphs.
    You talk about Racket, I would make Scribble. You talk about Lean 4, I would make Verso.

5 Likes
  • What are your greatest annoyances about Template Haskell? (Perhaps
    perf, cross compile support, stage restriction, missing language
    features for quotes, API of template-haskell, …)
  • API breakage.
  • Only a subset of Haskell’s real AST is supported for QQs.
  • Lack of a parseExp :: String -> Q Exp function, and related for
    types, decls.
  • I’d often like a syntax like 'foo that would give me a Named a
    which contains both the (typed) a and its name.
    • I.e. like ('foo, foo) without the repetition and room for accidents.
    • Often you want to name something for some metaprogramming reason, but for generated runtime code, just reference the real value, and use the type information for typechecking now, not later. I usually hit a wall on designing a nice API because a syntactic construct that produces this does not exist.

Perf, stage restriction don’t bother me much.

  • Would you be interested in having a Scheme- or Lean-like macro
    system? What would be your use case?

Yes, I’d like macros..

  • Do you use GHC.Generics instead? If so, why?

No, I prefer programming in Haskell to the unification game of
type-classes.

  • Have you tried Template Haskell on a more recent GHC? For example,
    GHC 9.4 drastically improves recompilation avoidance.

I haven’t specifically noticed this, but we don’t use that much TH at
work.

  • Are you using typed Template Haskell? If so, do you have specific
    annoyances?

Yes, but only when it wasn’t really useful (just typed QQs and
newtype TExp a = Exp). Haven’t tried the modern version.

5 Likes

Do you use GHC.Generics instead? If so, why?

I do…for a variety of reasons:

  1. Familiarity. I can sling codegen with Generics without much thought but I haven’t used enough TH to be as productive. I also find writing inductive TCs fun and fun is my no1 priority as a Haskeller :face_with_hand_over_mouth:
  2. It’s Just Haskell Types. For instance, the user can add extra type variables and things tend to Just Work. Whereas with TH, that’s often not the case.
    • One example of this is esqueleto records. They are codegen with TH, and you can’t add type variables. I implemented the same functionality with HKD+Generics (before the TH ever existed) and adding type variables Just Worked. Comes in handy…I should really upstream the Generics to esqueleto so those who prefer them can use them :grin:
  3. I find the Haddocks better. With TH, you pretty much have to either read English or click “source” to see wtf it does. While it might take some squinting, the Generics and TC-driven codegen do have meaningful types. And with some good taste, they can be as solid documentation as types can be.
  4. I don’t really care about the downsides. I just don’t play compile-time-accounting with my own projects? It’s all trade-offs, and I choose fancy stuff at the cost of compilation time. And there are plenty of tricks to keep my workflow fast even with super-fancy code.
3 Likes

(Also re: Generics…my understanding is the performance can be improved quite a bit by having it be a higher-branching-factor tree. The main downside is that’s a breaking change though…so we’d need GHC.Generics2 :slightly_frowning_face: )

While we are piling on Generics, here are my own gripes about it:

  • The naming – M1 S1 U1 K1 etc., despite doing a lot of generics programming over the years I have never gotten a good intuition for which is which.
  • How much overhead is necessitated when/if GHC fails to inline away things going through a generic Rep and how slow all that inliner work is. It would be much much better IMO if the generic representation was a flat SOP representation like in Data.Record.Generic
  • Finally: why aren’t documentation comments in Meta? That’d be such a nice feature for many encoder/decoder libraries. Basically the same gripe applies for TH though.
4 Likes

Misc thoughts:

1 Like

Thank you for the feedback so far.

Do you remember whether this was caused by splice functions needing to be defined in a module separate from their uses or was it caused by the implicit dependency ordering imposed by a top-level declaration splice such as $(return [])?

I think stability of template-haskell will become much better in the releases to come, when it can be maintained as a separate library, not in need of a version bump whenever a new GHC is released. See also the tracking ticket #24021.

However, the current design of template-haskell (everything is defined as a closed union of data constructors with an ever changing number of fields without record selectors) inevitably leads to a brittle API and will probably need a few refactorings in order to become more stable.
Also we need to improve the quoting capabilities offered by the language, because that offers by and large the most stable interface.
@teo, @rae, @adamgundry and I discussed a (perhaps System F-like) view data type over template-haskell's Type the other week that would also improve stability for consumers.

All that is to say: Stability is a concern, but one that we can improve rather systematically if we know what kind of breakages caused trouble in the past.

Great idea. There’s #12457 that tracks a more fleshed out proposal. I think it simply lacks someone dedicated to write down the GHC proposal and implement it.

Interesting. That seems like rather low-hanging fruit then. Do you know of a tracking issue?

Very cool :))

This is a great idea, but not that easily achievable after reading @brandonchinn178’s ticket.

Presumably you mean the typed TH equivalent of varE 'foo here? Yeah, I see how that isn’t currently possible in typed TH because of the lack of types in Name.

I think this is a huge factor. See #15822: template-haskell package lacks any real documentation · Issues · Glasgow Haskell Compiler / GHC · GitLab.

You are not alone here.

Incidentally, such a representation is easily achievable in (typed) TH; staged-sop. Alas, it needs a tweaked GHC. I would hope that we could achieve most of the goodness of the API by discarding types (for now).
IMO, such an API would be far superior to GHC.Generics. I started a TH prototype mirroring the latter when I realised that SOP is the far more natural representation.

I opened #24877.

5 Likes

I don’t think it is hard per se. It is just a some tedious work. I spent perhaps a weekend writing ghc-meta and updating it to support a newer GHC version took less than a day. If I had a more concrete use-case or more time I’d probably still be keeping it updated.

I’ll be at ZuriHac, so if there’s enough interest we could get together to update it and polish it into a proper package.

2 Likes

There also is ghc-hs-meta which basically does the same thing (I recently became a co-maintainer of that package, but I have only been doing trivial updates for newer GHCs). It works for all GHCs >=8.10, but it doesn’t yet cover the full AST. Would be happy to join forces here, will also be at ZuriHac :+1:

2 Likes

Template Haskell is basically wrong by design, as Edward Z Yang explains in a blog post. He’s right, it’s important stuff re: GHC/Haskell, but it’s confined to a blog post! It’s not been tied up the way textbook material has.

TH is a morass re: cross-compilation and it’s not even clear what the behavior under cross-compilation should be.

2 Likes

I would not say that TH is “wrong by design”. TH is about staged metaprogramming, whereas Racket macros are about extending source syntax. I recently learned that these approaches are slightly incompatible in the following ways:

  • Staged metaprogramming wants to name analyse and even type-check quotes, whereas macros absolutely do not and instead employ elaborate hygiene algorithms that support user-written binding constructs and hygiene-bending. You might enjoy reading my response here.
  • Staged metaprogramming has cross-stage persistence, that is, fun :: Int -> Q Exp; fun x = [| x + x |] will automatically lift the Int value of x to the next stage. As far as I know, macro systems do not want or have this kind of functionality, because the parameters of pattern-based macros are always quotes.

These two differences, combined with the urge to be backwards compatible, make it unlikely that -XTemplateHaskellQuotes will ever be used for macros in GHC. If we want macros, we need a different (third) kind of quote that is not renamed until expanded, and one which is not subject to cross-stage persistence.

I’m hopeful that many of the technical limitations that Edward writes about (stage restriction, cross compilation, lack of define-for-syntax) can be overcome, yet it will take a significant engineering effort.

3 Likes

FWIW @Ericson2314 wrote up a GHC proposal that covers similar ground https://github.com/ghc-proposals/ghc-proposals/pull/243. Though it’s stalled recently

2 Likes

We have a soft ban on Generic at our work code base because it is so much slower than TemplateHaskell. Even before we’d built support for byte code linking and 9.4’s recompilation checking, swapping all of our JSON instances for Generic from TH caused the compile time to double. I wrote optparse-th to replace optparse-generic for a large sum type, and this ended up reducing our optimized build time by over 15 minutes.

The biggest problem I have with TemplateHaskell is supporting multiple GHC versions in libraries I maintain for it. Fields are added to constructors in breaking ways constantly, and there’s rarely a convenient way aside from CPP littered across all of my projects to make it work nicely. I know I could publish a library to fix this, but it’s still annoying to need to do.

Typed Template Haskell is nice. I use it occasionally. It is somewhat difficult to go from a (Typeable a) => a to a Name suitable for use with reify, but it’s not that bad. The main problem is the difficulty supporting multiple GHC - knowing where and how to put liftSplice is a pain.

8 Likes

Thanks. Now that !12479 has been merged, I really hope that template-haskell can become much stabler and user-oriented, staying compatible with multiple GHC versions. This is all tracked in #24021.

Could you perhaps list a few concrete examples? Were they related to Exp, Dec or Type? Why couldn’t you use quotes for your use case? (Perhaps you were matching on code or needed to generate tuples?)

2 Likes

The most recent example is esqueleto's record functionality: esqueleto/src/Database/Esqueleto/Record.hs at master · bitemyapp/esqueleto · GitHub Searching for #if brings up 7 matches. It may be possible to use quotes to replace some of those - if you have suggestions I’d love to see them! But I generally find quotes a bit hard to work with: they break in weird ways and splicing often doesn’t work exactly how I’d want it to.

esqueleto seems to be what we call a class (C)+(D) client in Plan to Stabilise Template Haskell and thus is subject to breaking changes in the Exp data type. I think it could reasonably become a class (C)+(A) or (B) client in the future with rock-solid stability guarantees. For example,

pure $ ConP 'Value [] [VarP var]
==>
[| Value $(varE var) |]

pure $ mkTySynInstD ''ToMaybeT (ConT sqlName) (ConT sqlMaybeName)
==>
[d| type $(varT ''ToMaybeT) = $(varT sqlName) $(varT sqqlMaybeName) |] 
  -- actually not so sure about this one, but it *must* work some way; otherwise bug report

code like this should still work in GHC 12. After all, the Haskell2010 accepted by GHC will stay by and large the same as well.

I can see how this does not help at all with breakage introduced by the changes to TyVarBndr. It is unclear to me why we need to parameterise over flag. Just instantiate to (BndrVis,Specificity)! The additional info will simply be borign most of the time and lead to compile errors constructed in the wrong way (fine; that’s just a bug in esqueleto then. But in practice all those TyVarBndrs come from correctly constructed syntax anway).
It is also currently impossible to completely refactor the following code to a quote

  pure $
    FunD
      'sqlSelectProcessRow
      [ Clause
          [VarP colsName]
          (NormalB bodyExp)
          -- `where` clause
          [ ValD
              (VarP processName)
              ( NormalB $
                  DoE (statements ++ [NoBindS $ AppE (VarE 'pure) (RecConE constructorName fieldExps)])
              )
              []
          ]
      ]
==>
[d| 
$(varE 'sqlSelectProcessRow) cols = 
   first ((fromString "Failed to parse " ++ $(lift (nameBase name)) ++ ": ") <>)
   flip evalStateT cols $ do
     $*"\n"(statements)
     pure $(varE name) { $*","(fieldExps) }
|]

because we do not have “splicing expansion” (in macro slang) operators $*"\n" and $*"," (syntax tentative) which splice in lists separated by tokens \n/, (very roughly). That will need a GHC proposal.