[GHC] #13550: -ddump-splices doesn't parenthesize type/data families correctly in 8.2.1

GHC ghc-devs at haskell.org
Sat Apr 8 22:48:16 UTC 2017


#13550: -ddump-splices doesn't parenthesize type/data families correctly in 8.2.1
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Template       |           Version:  8.1
  Haskell                            |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #13199
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The pretty-printed code which `-ddump-splices` has regressed since 8.0. If
 you compile this code:

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# OPTIONS_GHC -ddump-splices #-}
 module Bug where

 $([d| type family Foo a b
       type instance Foo (Maybe a) b = Either (Maybe a) (Maybe b)

       data family Bar a b
       data instance Bar (Maybe a) b = BarMaybe (Maybe a) (Maybe b)
     |])
 }}}

 with GHC 8.0.2, you get this:

 {{{
 GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 Bug.hs:(6,3)-(11,6): Splicing declarations
     [d| type family Foo_a13C a_a13G b_a13H
         data family Bar_a13B a_a13E b_a13F

         data instance Bar_a13B (Maybe a_a13I) b_a13J
           = BarMaybe_a13D (Maybe a_a13I) (Maybe b_a13J)
         type instance Foo_a13C (Maybe a_a13K) b_a13L = Either (Maybe
 a_a13K) (Maybe b_a13L) |]
   ======>
     type family Foo_a3O6 a_a3O9 b_a3Oa
     type instance Foo_a3O6 (Maybe a_a3Ob) b_a3Oc = Either (Maybe a_a3Ob)
 (Maybe b_a3Oc)
     data family Bar_a3O7 a_a3Od b_a3Oe
     data instance Bar_a3O7 (Maybe a_a3Of) b_a3Og
       = BarMaybe_a3O8 (Maybe a_a3Of) (Maybe b_a3Og)
 }}}

 Looks good. But in GHC 8.2.1, the output of `-ddump-splices` lacks many
 sets of parentheses which are necessary for correctness!

 {{{
 GHCi, version 8.2.0.20170403: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 Bug.hs:(6,3)-(11,6): Splicing declarations
     [d| type family Foo_a1ty a_a1tC b_a1tD
         data family Bar_a1tx a_a1tA b_a1tB

         type instance Foo_a1ty (Maybe a_a1tG) b_a1tH = Either (Maybe
 a_a1tG) (Maybe b_a1tH)
         data instance Bar_a1tx (Maybe a_a1tE) b_a1tF
           = BarMaybe_a1tz (Maybe a_a1tE) (Maybe b_a1tF) |]
   ======>
     type family Foo_a4ia a_a4id b_a4ie
     type instance Foo_a4ia Maybe a_a4if b_a4ig = Either (Maybe a_a4if)
 (Maybe b_a4ig)
     data family Bar_a4ib a_a4ih b_a4ii
     data instance Bar_a4ib Maybe a_a4ij b_a4ik
       = BarMaybe_a4ic Maybe a_a4ij Maybe b_a4ik
 }}}

 This pops up both in the arguments to `type instance Foo ...` and `data
 instance Bar ...`, as well as the arguments to the data constructor
 `BarMaybe`.

 cc'ing alanz, since I suspect this is related to #13199.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13550>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list