[GHC] #13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations
GHC
ghc-devs at haskell.org
Fri Jul 28 20:20:01 UTC 2017
#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
More information about the ghc-tickets
mailing list