[GHC] #14578: Incorrect parenthesization of types in -ddump-deriv

GHC ghc-devs at haskell.org
Wed Dec 13 15:13:52 UTC 2017


#14578: Incorrect parenthesization of types in -ddump-deriv
-------------------------------------+-------------------------------------
           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:
-------------------------------------+-------------------------------------
 Compiling this program on GHC 8.2 or later:

 {{{#!hs
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# OPTIONS_GHC -ddump-deriv #-}
 module Bug where

 import Control.Applicative
 import Data.Functor.Compose
 import Data.Semigroup

 newtype App f a = MkApp (f a)
   deriving (Functor, Applicative)

 instance (Applicative f, Semigroup a) => Semigroup (App f a) where
   (<>) = liftA2 (<>)

 newtype Wat f g a = MkWat (App (Compose f g) a)
   deriving Semigroup
 }}}

 Will result in some incorrectly pretty-printed types in the `-ddump-deriv`
 output:

 {{{
 $ /opt/ghc/8.2.2/bin/ghci Bug.hs -dsuppress-uniques
 GHCi, version 8.2.2: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )

 ==================== Derived instances ====================
 Derived class instances:

   <elided for brevity>

   instance (Data.Semigroup.Semigroup a, GHC.Base.Applicative g,
             GHC.Base.Applicative f) =>
            Data.Semigroup.Semigroup (Bug.Wat f g a) where
     (Data.Semigroup.<>)
       = GHC.Prim.coerce
           @(Bug.App Data.Functor.Compose.Compose f g a
             -> Bug.App Data.Functor.Compose.Compose f g a
                -> Bug.App Data.Functor.Compose.Compose f g a)
           @(Bug.Wat f g a -> Bug.Wat f g a -> Bug.Wat f g a)
           (Data.Semigroup.<>)
     Data.Semigroup.sconcat
       = GHC.Prim.coerce
           @(Data.List.NonEmpty.NonEmpty Bug.App
 Data.Functor.Compose.Compose f g a
             -> Bug.App Data.Functor.Compose.Compose f g a)
           @(Data.List.NonEmpty.NonEmpty Bug.Wat f g a -> Bug.Wat f g a)
           Data.Semigroup.sconcat
     Data.Semigroup.stimes
       = GHC.Prim.coerce
           @(forall (b :: TYPE GHC.Types.LiftedRep).
             GHC.Real.Integral b =>
             b
             -> Bug.App Data.Functor.Compose.Compose f g a
                -> Bug.App Data.Functor.Compose.Compose f g a)
           @(forall (b :: TYPE GHC.Types.LiftedRep).
             GHC.Real.Integral b => b -> Bug.Wat f g a -> Bug.Wat f g a)
           Data.Semigroup.stimes
 }}}

 Notice that is shows `Bug.App Data.Functor.Compose.Compose f g a`, which
 is wrong. It should be `Bug.App (Data.Functor.Compose.Compose f g) a`.

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


More information about the ghc-tickets mailing list