[GHC] #13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: newcomer | 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: -------------------------------------+------------------------------------- If you run this program: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Foo where import Language.Haskell.TH main :: IO () main = do putStrLn $([d| data a :~: b where Refl1 :: a :~: a |] >>= stringE . pprint) putStrLn $([d| data a :~~: b = a ~ b => Refl2 |] >>= stringE . pprint) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs data :~:_0 a_1 b_2 where Refl1_3 :: :~:_0 a_4 a_4 data :~~:_0 a_1 b_2 = a_1 ~ b_2 => Refl2_3 }}} It'll print the output incorrectly. Those infix names `:~:` and `:~~:` ought to be surrounded by parentheses, since they're used in prefix position. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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 ak3n): I am not sure, but I think that it's enough to change `pprName' Alone` to `pprName' Applied` [https://git.haskell.org/ghc.git/blob/HEAD:/libraries /template-haskell/Language/Haskell/TH/PprLib.hs#l123 here]. There are 8 failed tests in `testsuite/tests/th` because of this change: - `GHC.Types.:` becomes `(GHC.Types.:)` - `Data.Type.Equality.~` becomes `(Data.Type.Equality.~)` - and something else There is another way to fix it. Change `ppr t` to `pprName' Applied t` [https://git.haskell.org/ghc.git/blob/HEAD:/libraries/template- haskell/Language/Haskell/TH/Ppr.hs#l401 here], which outputs: {{{ data (:~:_0) a_1 b_2 where Refl1_3 :: :~:_0 a_4 a_4 data (:~~:_0) a_1 b_2 = a_1 ~ b_2 => Refl2_3 }}} This [https://git.haskell.org/ghc.git/blob/HEAD:/libraries/template- haskell/Language/Haskell/TH/Ppr.hs#l402 line] is responsible for the kind of `Refl1_3`, but I haven't figured out how to fix it yet. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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): Thanks for looking into this, ak3n! I don't believe changing the implementation of `pprName` is what you want here, since that will affect far more than just infix datatypes names, which is what you really care about. I think your second suggestion (changing uses of `ppr` to `pprName' Applied`) is on the right track. As far as why the type of `Refl1_3` is pretty-printed incorrectly, I //think// it's due to the pretty-printer for `Type`. It has a case for `ConT` [https://git.haskell.org/ghc.git/blob/HEAD:/libraries/template- haskell/Language/Haskell/TH/Ppr.hs#l682 here]: {{{#!hs pprParendType (ConT c) = ppr c }}} I think this should be `pprName' Applied c` instead. This is consistent with the pretty-printer's [https://git.haskell.org/ghc.git/blob/3c4537ea1c940966eddcb9cb418bf8e39b8f0f1... /template-haskell/Language/Haskell/TH/Ppr.hs#l128 treatment] for `Exp` as well: {{{#!hs pprExp _ (ConE c) = pprName' Applied c }}} So that feels like the right solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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 ak3n): Yep, I tried to run the whole test suite and it finished with 417 unexpected failures. Thanks for pointing out `pprParendType`! I didn't find it yesterday. Also, should we change `pprParendType (VarT v) = ppr v` too? Because of `pprExp _ (VarE v) = pprName' Applied v`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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 ak3n): * owner: (none) => ak3n -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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:3 ak3n]:
Yep, I tried to run the whole test suite and it finished with 417 unexpected failures.
Well, chances are that most of the tests were pretty-printing information incorrectly, so this perhaps isn't so surprising. Make sure to eyeball the new test results to confirm that they look correct, and if so, you can run `make accept TEST="Test1 Test2 ... TestN"` to have GHC accept the new results. (If you're not sure, feel free to consult.)
Also, should we change `pprParendType (VarT v) = ppr v` too? Because of `pprExp _ (VarE v) = pprName' Applied v`.
Good question. For consistency, I think we probably should apply this change to `VarE` as well. That being said, I'm not sure if you can actually have a type-level variable that's syntactically infix, so I don't think you can actually observe this behavior in practice. For instance, I tried this: {{{ λ> $([d| type F ((**) :: * -> * -> *) x y = x ** y |] >>= stringE . pprint) <interactive>:30:14: error: Unexpected type ‘((**) :: * -> * -> *)’ In the type declaration for ‘F’ A type declaration should have form type F a b c = ... }}} But in case this ever changes, it would be nice to have Template Haskell Just Work™, so I'd be fine with this change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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:D3717 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ak3n): * differential: => Phab:D3717 Comment: Oh, sorry, I was unclear, there were 417 unexpected failures with bad `pprName` version. The variant with proper `pprName' Applied` is fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names
in data declarations
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: ak3n
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.1
Resolution: | Keywords: newcomer
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:D3717
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: ak3n Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: newcomer 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:D3717 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: ak3n Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: newcomer 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:D3717, Wiki Page: | Phab:D3802 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: Phab:D3717 => Phab:D3717, Phab:D3802 Comment: I found yet another example of this sort of thing: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TemplateHaskell #-} module Main where import Data.Proxy import GHC.Generics import Language.Haskell.TH main :: IO () main = do putStrLn $([t| Proxy (:*:) |] >>= stringE . pprint) putStrLn $([t| Proxy '(:*:) |] >>= stringE . pprint) putStrLn $([t| Proxy '(:) |] >>= stringE . pprint) }}} {{{ Data.Proxy.Proxy (GHC.Generics.:*:) Data.Proxy.Proxy 'GHC.Generics.:*: Data.Proxy.Proxy 'GHC.Types.: }}} Unfortunately, we must have overlooked applying this fix to //promoted// infix constructors. I've got a patch at Phab:D3802 which addresses this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13887#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names
in data declarations
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: ak3n
Type: bug | Status: closed
Priority: normal | Milestone: 8.2.1
Component: Template Haskell | Version: 8.0.1
Resolution: fixed | Keywords: newcomer
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:D3717,
Wiki Page: | Phab:D3802
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC