[GHC] #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ()))

#12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving, PolyKinds #-} import qualified Data.Data data Mu f = Mu (f (Mu f)) deriving instance Data.Data.Data (Mu (Const ())) }}} produces {{{ • No instance for (Data (Const () (Mu (Const ())))) arising from a use of ‘k’ • In the expression: (z Mu `k` a1) In an equation for ‘gfoldl’: gfoldl k z (Mu a1) = (z Mu `k` a1) When typechecking the code for ‘gfoldl’ in a derived instance for ‘Data (Mu (Const ()))’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Data (Mu (Const ()))’ }}} while other type constructors work, e.g. {{{#!hs deriving instance Data.Data.Data (Mu []) deriving instance Data.Data.Data (Mu ((,) ())) }}} i am not sure if #10835 is related. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12438 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by lspitzner: @@ -2,1 +2,1 @@ - {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving, PolyKinds #-} + {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} New description: {{{#!hs {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} import qualified Data.Data data Mu f = Mu (f (Mu f)) deriving instance Data.Data.Data (Mu (Const ())) }}} produces {{{ • No instance for (Data (Const () (Mu (Const ())))) arising from a use of ‘k’ • In the expression: (z Mu `k` a1) In an equation for ‘gfoldl’: gfoldl k z (Mu a1) = (z Mu `k` a1) When typechecking the code for ‘gfoldl’ in a derived instance for ‘Data (Mu (Const ()))’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Data (Mu (Const ()))’ }}} while other type constructors work, e.g. {{{#!hs deriving instance Data.Data.Data (Mu []) deriving instance Data.Data.Data (Mu ((,) ())) }}} i am not sure if #10835 is related. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12438#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12438#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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): Phab:D2726 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D2726 * milestone: => 8.2.1 Comment: I've submitted a patch for this, as discussed at https://mail.haskell.org/pipermail/libraries/2016-November/027396.html. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12438#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12438: DeriveDataTypeable - deriving instance Data (Mu (Const ()))
-------------------------------------+-------------------------------------
Reporter: lspitzner | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
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): Phab:D2726
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2726 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12438#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC