[GHC] #14682: Atrocious parenthesization in -ddump-deriv output

GHC ghc-devs at haskell.org
Wed Jan 17 21:00:43 UTC 2018


#14682: Atrocious parenthesization in -ddump-deriv output
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:  deriving       |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Debugging
  Unknown/Multiple                   |  information is incorrect
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The next installment in "RyanGlScott finds parenthesization bugs". This
 time, we're featuring `-ddump-deriv`. Just look at this garbage:

 {{{
 $ /opt/ghc/8.2.2/bin/ghci
 GHCi, version 8.2.2: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 λ> import Data.Ix
 λ> import Language.Haskell.TH.Syntax
 λ> import Data.Data
 λ> :set -ddump-deriv -XDeriveLift -XDeriveDataTypeable
 λ> data Foo = Foo Int Int deriving (Show, Lift, Data, Eq, Ord, Ix)

 ==================== Derived instances ====================
 Derived class instances:
   instance GHC.Show.Show Ghci1.Foo where
     GHC.Show.showsPrec a_a6me Ghci1.Foo b1_a6mf b2_a6mg
       = GHC.Show.showParen
           (a_a6me GHC.Classes.>= 11)
           ((GHC.Base..)
              (GHC.Show.showString "Foo ")
              ((GHC.Base..)
                 (GHC.Show.showsPrec 11 b1_a6mf)
                 ((GHC.Base..) GHC.Show.showSpace (GHC.Show.showsPrec 11
 b2_a6mg))))
     GHC.Show.showList = GHC.Show.showList__ (GHC.Show.showsPrec 0)

   instance Language.Haskell.TH.Syntax.Lift Ghci1.Foo where
     Language.Haskell.TH.Syntax.lift Ghci1.Foo a1_a6mh a2_a6mi
       = Language.Haskell.TH.Lib.appE
           (Language.Haskell.TH.Lib.appE
              (Language.Haskell.TH.Lib.conE
                 (Language.Haskell.TH.Syntax.mkNameG_d "interactive"
 "Ghci1" "Foo"))
              (Language.Haskell.TH.Syntax.lift a1_a6mh))
           (Language.Haskell.TH.Syntax.lift a2_a6mi)

   instance Data.Data.Data Ghci1.Foo where
     Data.Data.gfoldl k_a6mj z_a6mk Ghci1.Foo a1_a6ml a2_a6mm
       = ((z_a6mk Ghci1.Foo `k_a6mj` a1_a6ml) `k_a6mj` a2_a6mm)
     Data.Data.gunfold k_a6mn z_a6mo _
       = k_a6mn (k_a6mn (z_a6mo Ghci1.Foo))
     Data.Data.toConstr Ghci1.Foo _ _ = Ghci1.$cFoo
     Data.Data.dataTypeOf _ = Ghci1.$tFoo

   instance GHC.Classes.Eq Ghci1.Foo where
     (GHC.Classes.==)
       (Ghci1.Foo a1_a6mp a2_a6mq)
       (Ghci1.Foo b1_a6mr b2_a6ms)
       = (((a1_a6mp GHC.Classes.== b1_a6mr))
            GHC.Classes.&& ((a2_a6mq GHC.Classes.== b2_a6ms)))
     (GHC.Classes./=) a_a6mt b_a6mu
       = GHC.Classes.not ((GHC.Classes.==) a_a6mt b_a6mu)

   instance GHC.Classes.Ord Ghci1.Foo where
     GHC.Classes.compare a_a6mv b_a6mw
       = case a_a6mv of {
           Ghci1.Foo a1_a6mx a2_a6my
             -> case b_a6mw of {
                  Ghci1.Foo b1_a6mz b2_a6mA
                    -> case (GHC.Classes.compare a1_a6mx b1_a6mz) of
                         GHC.Types.LT -> GHC.Types.LT
                         GHC.Types.EQ -> (a2_a6my `GHC.Classes.compare`
 b2_a6mA)
                         GHC.Types.GT -> GHC.Types.GT } }
     (GHC.Classes.<) a_a6mB b_a6mC
       = case a_a6mB of {
           Ghci1.Foo a1_a6mD a2_a6mE
             -> case b_a6mC of {
                  Ghci1.Foo b1_a6mF b2_a6mG
                    -> case (GHC.Classes.compare a1_a6mD b1_a6mF) of
                         GHC.Types.LT -> GHC.Types.True
                         GHC.Types.EQ -> (a2_a6mE GHC.Classes.< b2_a6mG)
                         GHC.Types.GT -> GHC.Types.False } }
     (GHC.Classes.<=) a_a6mH b_a6mI
       = GHC.Classes.not ((GHC.Classes.<) b_a6mI a_a6mH)
     (GHC.Classes.>) a_a6mJ b_a6mK = (GHC.Classes.<) b_a6mK a_a6mJ
     (GHC.Classes.>=) a_a6mL b_a6mM
       = GHC.Classes.not ((GHC.Classes.<) a_a6mL b_a6mM)

   instance GHC.Arr.Ix Ghci1.Foo where
     GHC.Arr.range
       (Ghci1.Foo a1_a6mN a2_a6mO, Ghci1.Foo b1_a6mP b2_a6mQ)
       = [Ghci1.Foo c1_a6mR c2_a6mS |
            c1_a6mR <- GHC.Arr.range (a1_a6mN, b1_a6mP),
            c2_a6mS <- GHC.Arr.range (a2_a6mO, b2_a6mQ)]
     GHC.Arr.unsafeIndex
       (Ghci1.Foo a1_a6mT a2_a6mU, Ghci1.Foo b1_a6mV b2_a6mW)
       Ghci1.Foo c1_a6mX c2_a6mY
       = (GHC.Arr.unsafeIndex (a2_a6mU, b2_a6mW) c2_a6mY
            GHC.Num.+
              (GHC.Arr.unsafeRangeSize (a2_a6mU, b2_a6mW)
                 GHC.Num.* GHC.Arr.unsafeIndex (a1_a6mT, b1_a6mV) c1_a6mX))
     GHC.Arr.inRange
       (Ghci1.Foo a1_a6oj a2_a6ok, Ghci1.Foo b1_a6ol b2_a6om)
       Ghci1.Foo c1_a6on c2_a6oo
       = (GHC.Arr.inRange (a1_a6oj, b1_a6ol) c1_a6on
            GHC.Classes.&& GHC.Arr.inRange (a2_a6ok, b2_a6om) c2_a6oo)

   Ghci1.$con2tag_Hv18APskVh1Gg9kT3PCwD2 :: Ghci1.Foo -> GHC.Prim.Int#
   Ghci1.$con2tag_Hv18APskVh1Gg9kT3PCwD2 Ghci1.Foo _ _ = 0#
   Ghci1.$tFoo :: Data.Data.DataType
   Ghci1.$cFoo :: Data.Data.Constr
   Ghci1.$tFoo = Data.Data.mkDataType "Foo" [Ghci1.$cFoo]
   Ghci1.$cFoo
     = Data.Data.mkConstr Ghci1.$tFoo "Foo" [] Data.Data.Prefix
 }}}

 There are several lines where `Foo` must be surrounded with parentheses to
 typecheck, but aren't. They are:

 * In the `Show` instance:
   {{{
   GHC.Show.showsPrec a_a8sa Ghci11.Foo b1_a8sb b2_a8sc
   }}}
 * In the `Lift` instance:
   {{{
   Language.Haskell.TH.Syntax.lift Ghci11.Foo a1_a8sd a2_a8se
   }}}
 * In the `Data` instance:
   {{{
   Data.Data.gfoldl k_a8sf z_a8sg Ghci11.Foo a1_a8sh a2_a8si
   ...
   Data.Data.toConstr Ghci11.Foo _ _ = Ghci11.$cFoo
   }}}
 * In the auxiliary bindings (technically, these aren't legal definitions
 in the first place, but it does look jarring):
   {{{
     Ghci11.$con2tag_GrjBmXmdiewCS4g3vLeGMg :: Ghci11.Foo -> GHC.Prim.Int#
     Ghci11.$con2tag_GrjBmXmdiewCS4g3vLeGMg Ghci11.Foo _ _ = 0#
   }}}

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


More information about the ghc-tickets mailing list