{-# LANGUAGE TemplateHaskell #-}moduleAwheremkFootyQ=[d| foo :: a ~ $(tyQ) => a foo = undefined|]
{-# LANGUAGE TemplateHaskell, GADTs #-}moduleBwhereimportAmkFoo[t| Int -> Int |]
This loads fine in ghc-8.4.2, but with ghc-8.6.1 and current head (commit 23956b2a), the splice goes wrong:
$ ghci B.hsGHCi, version 8.6.1: http://www.haskell.org/ghc/ :? for help[1 of 2] Compiling A ( A.hs, interpreted )[2 of 2] Compiling B ( B.hs, interpreted )B.hs:7:1: error: • Expected a type, but ‘a_a4uD ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a4uD ~ Int -> Int => a_a4uD |7 | mkFoo [t| Int -> Int |] | ^^^^^^^^^^^^^^^^^^^^^^^Failed, one module loaded.*A>
As a workaround one can define a type alias for the Int -> Int type.
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
{-# LANGUAGE GADTs #-}{-# LANGUAGE TemplateHaskell #-}moduleBugwhere$([d| foo :: a ~ (Int -> Int) => a foo = undefined |])
$ /opt/ghc/8.4.4/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )$ /opt/ghc/8.6.1/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )Bug.hs:5:3: error: • Expected a type, but ‘a_a44c ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a44c ~ Int -> Int => a_a44c |5 | $([d| foo :: a ~ (Int -> Int) => a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Or, using fewer quotes:
{-# LANGUAGE GADTs #-}{-# LANGUAGE TemplateHaskell #-}moduleBugwhereimportLanguage.Haskell.TH$(dofoo<-newName"foo"a<-newName"a"pure[SigDfoo(ForallT[][AppT(AppTEqualityT(VarTa))(AppT(AppTArrowT(ConT''Int))(ConT''Int))](VarTa)),ValD(VarPfoo)(NormalB(VarE'undefined))[]])
$ /opt/ghc/8.4.4/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )$ /opt/ghc/8.6.1/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )Bug.hs:7:3: error: • Expected a type, but ‘a_a452 ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a452 ~ Int -> Int => a_a452 |7 | $(do foo <- newName "foo" | ^^^^^^^^^^^^^^^^^^^^^^^...
I believe I understand what is happening here. The problem is that when you roundtrip the following declaration through Template Haskell:
$([d| foo :: a ~ (Int -> Int) => a foo = undefined |])
Then all parentheses are stripped away when converting this to the GHC AST. This has important consequences when processing foo's type signature. Before the offending commit (that I linked to in ticket:15815#comment:162807), the context of foo's type signature would become:
HsEqTy a (HsOpTy Int (->) Int)
But after the offending commit, this becomes:
HsOpTy a (~) (HsOpTy Int (->) Int)
Upon first glance, these would appear to be identical. But as it turns out, HsEqTy actually had special treatment in the renamer, which means that it was renamed as though one had implicitly added HsParTys around both of its arguments. On the other hand, when GHC renaming sequences of HsOpTys (as in the second example), no such thing happens. In essence, that AST corresponds to:
a~Int->Int
GHC thinks that should be parenthesized as:
(a~Int)->Int
Which leads to the error that we see in this ticket.
A quick-and-dirty way to fix this would be to change cvtTypeKind such that when we convert an EqualityT, we parenthesize ~'s arguments if they aren't parenthesized. In other words, apply this patch:
That makes the original program compile again, although it's just applying a bandage over a deeper wound—namely, that TH conversion strips away parentheses in the first place.
goldfire, weren't you looking into fixing the parentheses issue in #15760? If so, perhaps your patch there would make for a more elegant fix for this ticket. On the other hand, if that still needs some work, I could whip up a stopgap solution now (based on the code above) so that this could be backported to a patch release if necessary.
Ryan, why do you believe that preserving parentheses would solve this issue? The original code does not have any parentheses (unlike your minimised version).
The issue here appears to be manyfold
We reassociate type operators according to their fixities, so with a ~ $(tyQ) and [t| Int -> Int |] from the original report we get a ~ Int -> Int (no parens!) which gets correctly associated as (a ~ Int) -> Int. That's not the behaviour I would expect, but I've just learned that it's documented in Note [Converting UInfix].
However, we map all three of (~) a b, a ~ b, and (a ~ b) to AppT (AppT EqualityT a) b. So we discard both parenthesization information (as you noted) and whether equality was applied in an infix or a prefix fashion.
When we convert back to HsType, we use HsOpTy if there are two operands, even if (~) was prefix in the original code. This means that even if we fix #15760, we will still get incorrect behaviour in the (~) a b case.
For expressions, we have a distinction between UInfixE and InfixE:
UInfixE gets reassociated as necessary (documented in Note [Operator association])
InfixE gets parenthesised as necessary (documented in Note [Converting UInfix])
In types we have a similar distinction – UInfixT and InfixT. The former must get reassociated, and the latter parenthesised.
NB. Looking at the code that handles InfixT it appears broken to me (because unlike code for InfixE, it does not seem to parenthesise). But this is either a bug or I'm missing something. For the sake of the argument let's assume InfixT is treated the same way as InfixE – by parenthesising arguments as necessary.
The question is: do we treat AppT (AppT (EqualityT a)) b as a moral equivalent of UInfixT or InfixT? The bug seems to be that we used to treat it as InfixT (or at least as InfixT is supposed to work), now we treat it as UInfixT. Your patch with adding parenthesizeHsType seems to make it treated like InfixT again, but ideally the fix should be to
stop confusing (~) a b and a ~ b: map the former to AppT (AppT (EqualityT a)) b and the latter to InfixT a EqualityT b
fix the treatment of InfixT in cvtTypeKind – parenthesise as necessary in expressions
You're right, I misspoke about #15760 fixing this issue. Forget I said anything about that.
Your fix smells correct to me, and if there weren't any other extenuating circumstances, I'd endorse it as the one true solution. Unfortunately, there's a bit of a thorny issue in that this code no longer works on GHC 8.6, and I don't see a simple way to work around the issue at the moment. We need to backport //something// to fix this, but the question is //what//.
Alas, changing the way we desugar infix types to use InfixT would constitute a breaking change in practice, so I'm reluctant to backport that. There is quite a bit of code in the wild which, for better or worse, assumes that InfixT only ever appears in user written code (i.e., InfixT never appears in desugared or reified TH ASTs). See this function from th-abstraction as one example. I'm not sure what exactly would happen if we started feeding that function InfixTs, but I imagine that something or another would change at runtime, which would be awful for a point release.
Therefore, I'm inclined to adopt the patch in ticket:15815#comment:162809 as a crude (and ideally, temporary) fix for this issue in an 8.6 point release (hopefully 8.6.2), and work towards implementing your more robust solution for 8.8. Does that sound reasonable?
Sounds reasonable to me, although I'm unsure if we should target 8.8 for the more robust fix rather than 8.10.
When #15760 is fixed, decomposeType in th-abstraction that you linked would have to start to care about parentheses as well, so I believe it's better to do both changes at once. And since the merge window for 8.8 closes in a couple of days, and these are breaking changes, then a more realistic target is probably 8.10 – what do you think?