There are quite a few forms that are not supported in template haskell quotes. It seems that it would be at least a good warm up patch to add support for tuple sections which you can do simply by desugaring to a lambda and the normal tuple constructor.
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TupleSections #-} module Foo where foo = [|| (,5) ||]
Modify DsMeta.repE to handle tuple sections. You can desugar (,5) => \x -> (x, 5).
Add the above test to the test suite.
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
I disagree with the design in the original post. TH syntax should really be as close as possible to Haskell syntax. Instead, I would say that TH should support tuple sections directly. I propose changing TupE :: [Exp] -> Exp to become TupE :: [Maybe Exp] -> Exp.
My opinion is that @rae's suggestion is the correct implementation but that if it's more difficult for a newcomer then my suggested implementation is also ok.
I don't want to discourage anyone, but I feel more strongly about the design in my #15843 (comment 163537). If we implement the lambda design now and then change later, that could be annoying for TH users. (On the other hand, you could argue that my design breaks code, annoying in a different way.) @RyanGlScott thinks a lot about TH: Ryan, do you have an opinion here?
I don't think either design will be hard to implement. The AST-changing design is harder, yes, but I still think appropriate for a newcomer.
There is a third design possibility in this space: have a completely separate TupSectionE :: [Maybe Exp] -> Exp constructor. (Or perhaps it should be of type NonEmpty Exp -> Exp?) This would avoid breaking any existing Template Haskell code at the expense of having yet another constructor.
I don't feel strongly in favor of one particular design, although I'm somewhat less enthusiastic about the desugaring-to-lambdas design than the others.
On second thought, I'd like to retract my TupSectionE suggestion, as it would introduce unrepresentable states like TupSectionE [Just e1, Just e2]. Well, I suppose we could interpret that as (e1, e2), but that's not a tuple section anymore. Given this impedance mismatch, I think we should just bite the bullet and go with @rae's design, even if it does induce breaking changes. At the very least, we can keep the type signature of Language.Haskell.TH.Lib.tupE the same for some degree of backwards compatibility.
I spent some time and I believe I know what needs to be done.
However, I got stuck a bit in DsMeta.repE. As I understand it, this is where we transform our HsSyn (which comes from TH quotes) into Core Expr?
I suspect we need to do here something similar to what we do in DsExpr.ds_expr?(handle the Missing Tuple argument case).
This Core newtype wrapper really confuses me. Especially this phantom type! But I believe it is there for a good reason. Maybe we could improve the Note for it and add actual examples that justify its existence. I would love to do that when I get to understand it.
Please let me know if this is the right direction! Thanks.
As I understand it, this is where we transform our HsSyn (which comes from TH quotes) into Core Expr?
Yes, that's exactly right.
Personally, I'd advise not looking at DsExpr for inspiration, since that involves a lot of machinery that is never used in DsMeta. Instead, I'd recommend looking at other combinators in DsMeta to see what they do, such as repTup.
This Core newtype wrapper really confuses me. Especially this phantom type!
Core exists to add an extra level of type safety to operations in DsMeta. The underlying type, CoreExpr, does not track in its type whether it represents, say, an Int, a TH.Exp, a Maybe TH.Exp, or whatever it may be. Instead, we can use Core Int, Core TH.Exp, Core (Maybe TH.Exp), etc. to make it more difficult to construct ill typed Core expressions.
For instance, you may find it illuminating to see what the type of repTup would be without Core. Here is its current type:
repTup::Core[TH.ExpQ]->DsM(CoreTH.ExpQ)
And here it is without Core:
repTup::CoreExpr->DsMCoreExpr
It's not difficult to imagine how one could misuse the latter version to construct ill formed Core.