Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations
If you run this program:
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |