Great to hear this is being worked on and it looks like it’s well thought through.
Reading that data constructors are often used instead of quotes made me think of all the times I used Template Haskell to implement something, and I think I veered to data constructors because they were explicit in what they represented, where using quotes felt a bit like *magic*.
If we want people to prefer the quote style of using/creating Template Haskell, it’s probably important to put big obvious warnings in the module with the data constructors to “prefer the quote style to minimize future breakage” and to have better documentation with lots of practical examples in how to use quotes to use/construct Template Haskell.
I’ve just looked through the template-haskell package again, and I still can’t find a good explanation about what [|...|] exactly does, how it works and how to use it.
These don’t completely explain their low uptake though.
I think we have traditionally avoided TH splices ($(...)) and quasiquotes ([|...|]) because they (used to ?) make compilation slower. If that’s no longer the case, we should advertise it.
I think the situation has improved a lot recently! But splicing still can slow things down in some cases.
But I was thinking more about comparing using quotes versus directly creating TH ASTs using constructors. I don’t think there should be much of a performance difference there.
What is your position on addTopDecls? I think there have been a number of times I’ve thought it might work as a good workaround for some practical problem, only to find that it doesn’t support the particular Dec I wanted to float up. Should I raise those as issues to increase addTopDecls coverage, or should I focus on issues for the original problems?
That documentation is not in the template-haskell package, where I feel it makes a lot of sense to put it. So doing that (or having a VERY obvious link to the User Guide) would definitely be an improvement.
Yet, quotes are much less popular than direct uses of constructors. There are definitely some places where quotes (currently) fall short and we are trying to track these here. These don’t completely explain their low uptake though.
I can’t build an intuition on how to use quotes. I have to go back and forth thinking about being inside Q and out. I have to figure what to splice, what to use fmap with to change what’s inside of Q.
I find that with the constructors you have Exp, Pat and Name and you mix and match and generate the final Exp and wrap it in Q. You know what you want, you play type tetris and you’re done.
How do I write this recent example with a quote?
{-# LANGUAGE TemplateHaskell #-}
module Setter where
import Language.Haskell.TH
set :: [Name] -> Q Exp
set names = return $ LamE [VarP a, VarP r] (go names (VarE r))
where
a = mkName "a"
r = mkName "r"
go ns acc = case ns of
[n] -> RecUpdE acc [(n, VarE a)]
n : zs -> RecUpdE acc [(n, go zs (AppE (VarE n) acc))]
_ -> error "no fields?"
-- reference
-- [] = error
-- [n1] = \a r -> r { n1 = a }
-- [n1, n2] = \a r -> r { n1 = (n1 r) { n2 = a } }
-- [n1, n2, n3] = \a r -> r { n1 = (n1 r) { n2 = (n2 (n1 r)) { n3 = a } } }
-- ...
go ns acc = case ns of
[n] -> RecUpdE acc [(n, VarE a)]
n : zs -> RecUpdE acc [(n, go zs (AppE (VarE n) acc))]
_ -> error "no fields?"
becomes
go ns acc = case ns of
[n] -> pure (RecUpdE acc [(n, VarE a)])
n : zs -> do
go' <- go zs (AppE (VarE n) acc)
pure (RecUpdE acc [(n, go')])
_ -> error "no fields?"
Overall you get the following. It’s not obviously a massive improvement. If names were spliceable it would be better. Maybe someone else knows a way of improving it further.
set :: [Name] -> Q Exp
set names = [| \ $(varP a) $(varP r) -> $(go names (VarE r)) |]
where
a = mkName "a"
r = mkName "r"
rec `upd` t = RecUpdE rec [t]
(.=) = (,)
go ns acc = case ns of
[n] -> pure (acc `upd` (n .= VarE a))
n : zs -> do
app <- [| $(varE n) $(pure acc) |]
go' <- go zs app
pure (acc `upd` (n .= go'))
_ -> error "no fields?"
We can use more smart constructors for less monad gymnastics:
set :: [Name] -> Q Exp
set names = [| \ $(varP a) $(varP r) -> $(go names (varE r)) |]
where
a = mkName "a"
r = mkName "r"
(.=) = fmap . (,)
go ns acc = case ns of
[n] -> recUpdE acc [n .= varE a]
n : zs -> recUpdE acc [n .= go zs [| $(varE n) $acc |]]
_ -> error "no fields?"
In this form, it’s easy to see that we can also make go total¹, which simplifies it:
go ns acc = case ns of
[] -> varE a
n : zs -> recUpdE acc [n .= go zs [| $(varE n) $acc |]]
This is, of course, a fold:
go = foldr f (const (varE a))
f n z acc = recUpdE acc [n .= z [| $(varE n) $acc |]]
Now notice that we never use a and r as names after they’re statically declared in the lambda, only as expressions. That means we can create them as part of the lambda quote and quote them into the fold (at this point it’s clearer I think to inline go):
set :: [Name] -> Q Exp
set names = [| \a r -> $(foldr f (const [| a |]) names [| r |]) |]
where
(.=) = fmap . (,)
f n z acc = recUpdE acc [n .= z [| $(varE n) $acc |]]
I think that’s pretty good, and if the recUpdE and .= bits can be replaced with a quote in the future, it’s easy to see where that would go and how it would make things even simpler. If name splicing used ₦$ instead of $, I’d expect this to do the trick:
set :: [Name] -> Q Exp
set names = [| \a r -> $(foldr f (const [| a |]) names [| r |]) |]
where
f n z acc -> [| $acc { ₦$n = $(z [| $(varE n) $acc |]) } |]
¹ If you truly desire set [] to be an error instead of the IMO quite justifiable const, I would add a set [] = error "..." clause at the top.
At worst, I write garbage that doesn’t compile, like
set names = [| \a r -> go names r |] -- WRONG, go must run
-- or
set names = [| \a r -> $(go names r) |] -- WRONG, can't stuff r in there
$r { n = $a } -- WRONG
$r { $n = $a } -- WRONG
$r { $(mkName n) = $a } -- WRONG, YOU CANT SPLICE NAMES, GET THE HINT ALREADY, AND THAT'S NOT EVEN Q
before giving up and falling back to playing Exp puzzle.
2) In the middle, if I somehow manage to overcome my skill issues, I end up with monadic plumbing all over the place, not really making it any different from the raw constructor version.
3) At best, I am a long beard wizard that can come up with triple nested $ and [| … |] expressions.
In conclusion: there is nothing wrong with quotes, and it’s me being a mere mortal. So perhaps to increase quote adoption you could extend the wiki tutorial with expressions more advanced than [| 1 + 2 |] and less advanced than full blown DSLs, to bridge the gap. Maybe even include my example, after the name splicing is figured out.
The suggestion to quote [| r |] is helpful. The stage talk was a bit confusing because it reminds me of lexical analysis → syntactical analysis → compilation → linking → execution stages and I kinda assumed something like that was going on because of the metaprogramming context. And that I broke it so bad I got a classic link time bogus error. Well now I know.