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

GHC ghc-devs at haskell.org
Tue Jun 27 21:13:06 UTC 2017


#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


More information about the ghc-tickets mailing list