[GHC] #11345: Template Haskell's handling of infix GADT constructors is broken

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There are several infelicities in the way that Template Haskell treats GADT constructors that are declared to be infix. To illustrate: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} module Main (main) where import Language.Haskell.TH infixr 7 :***: data GADT a where Prefix :: Int -> Int -> GADT Int (:***:) :: Int -> Int -> GADT Int $(return []) main :: IO () main = do putStrLn $(reify ''GADT >>= stringE . pprint) putStrLn "" putStrLn $(reify ''GADT >>= stringE . show) }}} This doesn't print out quite what you'd expect: {{{ data Main.GADT (a_0 :: *) = Main.Prefix :: GHC.Types.Int -> GHC.Types.Int -> Main.GADT GHC.Types.Int | GHC.Types.Int Main.:***: GHC.Types.Int TyConI (DataD [] Main.GADT [KindedTV a_1627394505 StarT] Nothing [GadtC [Main.Prefix] [(Bang NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int),(Bang NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int)] Main.GADT [ConT GHC.Types.Int],InfixC (Bang NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int) Main.:***: (Bang NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int)] []) }}} TH thinks that `GADT` is a Haskell98 data declaration when `pprint`-ing it because `(:***:)` is converted to an `InfixC` (see [http://git.haskell.org/ghc.git/blob/04f3524f787b2cbd3f460e058c753529d3f2f7ac... /template-haskell/Language/Haskell/TH/Ppr.hs#l362 here] for the relevant code). This causes the output to be a strange hodgepodge of Haskell98 and GADT syntax. Another issue is that even though I can reify `GADT`, I can't splice it back in! Compiling this: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} module Main (main) where import Language.Haskell.TH $(do gadtName <- newName "GADT" prefixName <- newName "Prefix" infixName <- newName ":***:" a <- newName "a" return [DataD [] gadtName [KindedTV a StarT] Nothing [GadtC [prefixName] [(Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int),(Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)] gadtName [ConT ''Int],InfixC (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int) infixName (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)] []]) $(return []) main :: IO () main = do putStrLn $(reify ''GADT >>= stringE . pprint) putStrLn "" putStrLn $(reify ''GADT >>= stringE . show) }}} Results in an error: {{{ InfixGADT.hs:12:3: error: Cannot mix GADT constructors with Haskell 98 constructors When splicing a TH declaration: data GADT_0 (a_1 :: *) = Prefix_2 :: GHC.Types.Int -> GHC.Types.Int -> GADT_0 GHC.Types.Int | GHC.Types.Int :***:_3 GHC.Types.Int }}} [http://git.haskell.org/ghc.git/blob/04f3524f787b2cbd3f460e058c753529d3f2f7ac... This code] is responsible. We have an issue where `InfixC` can be either Haskell98 or GADT syntax depending on the context, but in that particular context, there's not a good way to determine it. I can think of three solutions: 1. Add an `InfixGadtC` constructor. This adds more clutter to `Con`, but is the most straightforward fix. 2. Subsume infix GADT constructors under `GadtC`/`RecGadtC` (depending on if it has records), and treat `InfixC` as always being Haskell98. This wouldn't require any API changes, but it does leave a bit of asymmetry between the Haskell98 and GADT constructors, since there would be three of the former but two of the latter. 3. A radical approach (which subsumes option 2) would be to deprecate `InfixC`, subsume it under `NormalC`/`RecC`, and add an `InfixC` pattern synonym for compatibility. `InfixC` does seem extraneous anyway since you can just use `reifyFixity` to determine if a constructor is infix. That way, you have two Haskell98 and two GADT constructors (but you'd also have to deprecate `InfixC`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: => RyanGlScott Comment: Actually, I realized that I was a little too careless in writing solutions 2 and 3—to the point where I skipped over an important detail: `InfixC` and `reifyFixity` serve distinct purposes. `InfixC` just tells you that a constructor was ''declared'' infix rather than prefix, i.e., it's the difference between {{{#!hs data T1 a = T1 a a }}} and {{{#!hs data T2 a = a `T2` a }}} But it tells you nothing about its actual fixity ''when used as an infix operator''. In fact, calling `reifyFixity` on both `'T1` and `'T2` would yield the same answer (`Fixity 9 InfixL`) since neither have an explicit fixity declaration. This is a minor distinction, but an important one. As a motivating example, when a datatype has a derived `Show` instance: * If one of its constructors is declared prefix, then the constructor will be shown before its fields, and the fields will always be shown with precedence 11. This is regardless of whether a fixity declaration is present. * If one of its constructors is declared infix, then the constructor will be shown between its two arguments, and the fields will shown according to the precedence in the fixity declaration plus 1 (if none is present, it defaults to 9+1). This is extremely important for GADTs because it is a special case. A GADT constructor is only considered to be declared infix if (a) it is an operator symbol, (b) it has two arguments, (c) it has a fixity declaration. Only then would a derived `Show` instance for a GADT constructor show the constructor between its arguments. For these reasons, proposals 2 and 3 above aren't quite accurate: * `InfixC` can't be subsumed under `NormalC` neatly because they discern a property of the datatype declaration that can't necessarily be gleaned from `reifyFixity`. Unless you were to add another field to `NormalC` to mark whether it was declared infix, that it—but that is another breaking change. * `InfixC` can't be subsumed under `RecC` at all, since if a constructor has records, it is automatically considered not to be declared infix. Considering all this, proposal 1 looks by far the most attractive in terms of ease of implementation and the least API changes (barring `GadtC`/`RecGadtC`). I think I'll go ahead and add an `InfixGadtC` constructor to `Con`. Any objections? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): I think it would be better to add a field to `GadtC` that tells whether a constructor is an infix one or not. Correct me if I'm wrong, but information about infixity of a declaration is rarely needed. Adding a new constructor will force TH clients to implement handling of infix constructors even in situations where they don't care about infixity, whereas adding a new field to `GadtC` will be simple to handle - programmers can simply ignore that field in situations where it is irrelevant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Adding a new constructor will force TH clients to implement handling of infix constructors even in situations where they don't care about infixity, whereas adding a new field to `GadtC` will be simple to handle -
#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:2 jstolarek]: programmers can simply ignore that field in situations where it is irrelevant. Fair enough. By that logic, we don't need `InfixC` either, but I'll avoid making breaking changes for now. Let's see if I can get this done by the 8.0 release—fingers crossed! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hm... I might have been a bit too optimistic in my timeframe estimate. I ran into a very tricky stumbling block when trying to implement this. Namely, what happens when you try to splice an infix `GadtC` into source code in `Convert.hs`? Unlike `InfixC`, the infixity of a GADT constructor depends on the presence of a user-supplied fixity declaration. But AFAIK, there's no way to look up what things have fixity declarations in `CvtM`. I suppose you could just ignore the declaration fixity field of `GadtC` during splicing. But then if you don't also splice in a corresponding fixity declaration, you might actually end up with a non-infix GADT constructor in the end, even if you marked it otherwise. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, here's a better idea. My above comment shows that trying to encode whether a GADT constructor is declared infix directly into `GadtC` causes problems. But perhaps we don't need to do this. In theory, all we have to do is find out if there is a fixity declaration for the constructor. We're close to being able to do this in Template Haskell already through `reifyFixity`. The problem is that `reifyFixity` will return `defaultFixity` if it can't discover a user-defined fixity declaration for the argument, which leaves the programmer unable to know whether the user actually wrote that fixity, or if it's just `defaultFixity`. With a modest change to `reifyFixity`, {{{#!hs reifyFixity :: Name -> Maybe Fixity }}} where `Nothing` indicates the absence of a user-specified fixity declaration, then I think this would work! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D1744 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): I finally had a moment to take a closer look at the code and I have some concerns. Most importantly, I don't understand how we can actually have infix GADT constructors. Splicing creates an `HsDecl.ConDecl` data type, which can be either `ConDeclGADT` or `ConDeclH98`. The latter constructor has field `con_details :: HsConDeclDetails name`, where `HsConDeclDetails` is a type synonym to: {{{#!hs data HsConDetails arg rec = PrefixCon [arg] -- C p1 p2 p3 | RecCon rec -- C { x = p1, y = p2 } | InfixCon arg arg -- p1 `C` p2 }}} There is no such field in `ConDeclGADT` data constructor, so how can we mark a constructor declaration as infix? You're asking:
what happens when you try to splice an infix `GadtC` into source code in `Convert.hs`?
Indeed, what should happen in such a situation? I believe we should splice a normal GADT constructor because we have no way of expressing the infixity. Ryan, you also said in an earlier comment:
A GADT constructor is only considered to be declared infix if (a) it is an operator symbol, (b) it has two arguments, (c) it has a fixity declaration.
Can you show me where this happens in code? Your ticket reports actual problems in the implementation but I am not sure that the way you trying to address them is correct. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:7 jstolarek]:
There is no such field in `ConDeclGADT` data constructor, so how can we mark a constructor declaration as infix?
This was my mistake. I thought that infix GADT constructors were marked with their own constructor ''à la'' `InfixCon`, but that turns out not to be the case. Instead, GHC simply checks for three properties in a generalized `PrefixCon`.
what happens when you try to splice an infix `GadtC` into source code in `Convert.hs`?
Indeed, what should happen in such a situation? I believe we should splice a normal GADT constructor because we have no way of expressing the infixity.
Luckily, we don't need to express the infixity directly in the `GadtC`, as it suffices to splice in a `GadtC` with a symbol name and exactly two arguments, plus a separate fixity declaration. GHC takses care of the rest (see the test case in Phab:D1744 for proof).
A GADT constructor is only considered to be declared infix if (a) it is an operator symbol, (b) it has two arguments, (c) it has a fixity declaration.
Can you show me where this happens in code?
These are checked via [https://git.haskell.org/ghc.git/blob/c78fedde7055490ca6f6210ada797190f3c35d8... tcConIsInfixGADT]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): I'll move the discussion to Phab so that we can make comments on particular pieces of code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: RyanGlScott
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1744
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => merge * version: 8.1 => 8.0.1-rc1 * milestone: => 8.0.1 Comment: I guess this should go into 8.0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Indeed this has been merged as 9578cb21275b85f5f80e01d7ea70157d8b71e9eb. Thanks for noticing this, thomie! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1744, Wiki Page: | Phab:D1766 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: Phab:D1744 => Phab:D1744, Phab:D1766 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11345#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11345: Template Haskell's handling of infix GADT constructors is broken
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: RyanGlScott
Type: bug | Status: closed
Priority: normal | Milestone: 8.0.1
Component: Template Haskell | Version: 8.0.1-rc1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1744,
Wiki Page: | Phab:D1766
-------------------------------------+-------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC