[GHC] #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ()))
GHC
ghc-devs at haskell.org
Thu Oct 13 13:54:15 UTC 2016
#12438: DeriveDataTypeable - deriving instance Data (Mu (Const ()))
-------------------------------------+-------------------------------------
Reporter: lspitzner | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I had to make some changes to your code to get that exact error message.
Here is what I tried:
{{{#!hs
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, StandaloneDeriving #-}
module T12438 where
import Control.Applicative (Const(..))
import qualified Data.Data
data Mu f = Mu (f (Mu f))
deriving instance Data.Data.Data (Mu (Const ()))
}}}
Note the addition of `FlexibleInstances`. Also, `Const` wasn't in scope in
your original program — I assume you are referring to the `Const` from
`Control.Applicative`? If so, there's a simple explanation for why that
program won't compile — `Const` doesn't have a `Data` instance. Sure
enough, this program compiles just fine:
{{{#!hs
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, StandaloneDeriving #-}
module T12438 where
import Control.Applicative (Const(..))
import qualified Data.Data
deriving instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data
(Const a b)
data Mu f = Mu (f (Mu f))
deriving instance Data.Data.Data (Mu (Const ()))
}}}
In light of this, there's no bug in `DeriveDataTypeable` - it's just a
Haskell library design question of whether `Const` should have a `Data`
instance or not (I wouldn't be opposed to introducing one).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12438#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list