[GHC] #12245: Deriving Data at higher kinds

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | 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: -------------------------------------+------------------------------------- Here's what [https://mail.haskell.org/pipermail/generics/2016-June/000564.html Lennart Spitzner wanted to do]: {{{
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-}
import Data.Data ( Data )
data Foo f = Foo (f Bool) (f Int)
deriving instance Data (Foo []) deriving instance Data (Foo Maybe) }}} Of course you can't derive `Data` for `Foo` because we don't know what `f` is, so Lennart is making multiple instances, one for each instance of `f`. It's a bit clumsy. What we would really like is {{{ deriving instance (forall a. Data => Data (f a)) => Data (Foo f) }}} but we don't have higher order instances yet! So Lennart is manually making two instances.
This should work, but he gets {{{
Main.hs: line 45, column 1: Multiple declarations of ‘$cr2C’ Declared at: Main.hs:44:1 Main.hs:45:1 Main.hs: line 45, column 1: Multiple declarations of ‘$tr2D’ Declared at: Main.hs:44:1 Main.hs:45:1 }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | 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: | -------------------------------------+------------------------------------- Comment (by goldfire): Adding implication (quantified) constraints seems to be the answer to the underlying problem. See #2256. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: simonpj
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: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T12245 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => deriving/should_compile/T12245 * resolution: => fixed Comment: The presenting bug is fixed. I agree that #2256 is a better solution, but it's much further off. Meanwhile I'll close this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T12245 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lspitzner): Oh, I was not even aware that this got fixed! (You either did not bother to notify me or I missed something. Also I must have messed up my search when opening the duplicate ticket, pretty sure I did some search; sorry about that). Anyways, thanks for the fix! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T12245 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => QuantifiedConstraints -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T12245 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): With [https://phabricator.haskell.org/D4353 D4353] this can be written as: {{{#!hs {-# Language QuantifiedConstraints #-} {-# Language StandaloneDeriving #-} {-# Language DeriveDataTypeable #-} {-# Language FlexibleInstances #-} {-# Language UndecidableInstances #-} {-# Language KindSignatures #-} {-# Language RankNTypes #-} {-# Language ConstraintKinds #-} import Data.Data (Data) import Data.Typeable import Data.Kind (Constraint) data Foo f = Foo (f Bool) (f Int) type LevelUp cls f = (forall xx. cls xx => cls (f xx) :: Constraint) deriving instance (Typeable f, LevelUp Data f) => Data (Foo f) }}} Can this ticket be closed? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12245#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC