[GHC] #10835: Regression in standalone Data deriving for phantom types

GHC ghc-devs at haskell.org
Mon Sep 12 17:37:42 UTC 2016


#10835: Regression in standalone Data deriving for phantom types
-------------------------------------+-------------------------------------
        Reporter:  Feuerbach         |                Owner:  bgamari
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:  8.0.1
       Component:  Compiler          |              Version:  7.10.2
      Resolution:  fixed             |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by bgamari):

 * status:  new => closed
 * resolution:   => fixed
 * milestone:   => 8.0.1


Comment:

 With GHC 8.0 the polykinded example can be made to compile by adding a
 `Typeable` constraint on the kind of `t`,
 {{{#!hs
 {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving, PolyKinds, TypeInType
 #-}
 module M where
 import Data.Data
 import Data.Typeable

 data Phantom t = Phantom
   deriving Typeable
 deriving instance (Typeable k, Typeable (t::k)) => Data (Phantom t)
 }}}

 It also compiles without `PolyKinds`, although only with a `Data t`
 constraint,
 {{{#!hs
 {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
 module M where
 import Data.Data
 import Data.Typeable

 data Phantom t = Phantom
   deriving Typeable
 deriving instance (Data t) => Data (Phantom t)
 }}}

 If one replaces the `Data` constraint with `Typeable` typechecking fails
 with,
 {{{
 Hi2.hs:8:1: error:
     • Could not deduce (Data t) arising from a use of ‘f’
       from the context: Typeable t
         bound by the instance declaration at Hi2.hs:8:1-50
       or from: Typeable t1
         bound by the type signature for:
                    dataCast1 :: Typeable t1 =>
                                 (forall d. Data d => c (t1 d)) -> Maybe (c
 (Phantom t))
         at Hi2.hs:8:1-50
       Possible fix:
         add (Data t) to the context of
           the type signature for:
             dataCast1 :: Typeable t1 =>
                          (forall d. Data d => c (t1 d)) -> Maybe (c
 (Phantom t))
           or the instance declaration
     • In the first argument of ‘gcast1’, namely ‘f’
       In the expression: gcast1 f
       In an equation for ‘dataCast1’: dataCast1 f = gcast1 f
       When typechecking the code for ‘dataCast1’
         in a derived instance for ‘Data (Phantom t)’:
         To see the code I am typechecking, use -ddump-deriv
 }}}

 The reason for this is that GHC generates the following instance,
 {{{#!hs
 instance Typeable t => Data (Phantom t) where
     ...
     dataCast1 :: forall s c. (Typeable s)
               => (forall d. Data d => c (s d))
               -> Maybe (c (Phantom t))
     dataCast1 f = Data.Typeable.gcast1 f

 -- where
 Data.Typeable.gcast1 ::
   forall k k1 (c :: k -> *) (t :: k1 -> k) (t' :: k1 -> k) (a :: k1).
   (Typeable t, Typeable t') =>
   c (t a) -> Maybe (c (t' a))
 }}}

 Consequently the derived instance forces the `t ~ d` (WRT the type binders
 of `dataCast1` above). `dataCast1` requires `Data d`, hence the error.
 This all seems to be working as expected in GHC 8.0.1. Indeed, 7.8.4 also
 appears to require a `Data t` constraint despite the claim in the ticket
 summary, so I think all is well here.

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


More information about the ghc-tickets mailing list