[GHC] #8950: Typeable instances for promoted lists and tuples

#8950: Typeable instances for promoted lists and tuples ------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Please have a look at the following sample module: {{{ {-# LANGUAGE DataKinds, KindSignatures, PolyKinds, AutoDeriveTypeable #-} {-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-} import Data.Proxy import Data.Typeable data Foo (xs :: [*]) (p :: (*, *)) main :: IO () main = print (typeRep (Proxy :: Proxy (Foo '[Int] '(Bool, Char)))) -- Code above checks only with these instances, but shouldn't they -- be predefined? -- -- deriving instance Typeable '[] -- deriving instance Typeable '(:) -- deriving instance Typeable '(,) }}} The good news is that the code does in principle work, but as the comments say, I would have expected this to work without having to define additional instances. (A somewhat related question is whether concrete type literals such as `3 :: Nat` or `"foo" :: Symbol` should be instances of `Typeable`. They don't seem to be, and `deriving` does not work in these cases.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * cc: dreixel, goldfire (added) Comment: Quite right. If we are deriving `Typeable` for a data type, we should also do so for its promoted data constructors. Pedro or Richard, might you look into this? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by kosmikus): Just to clarify: `Typeable` works fine if I promote my own datatypes. It just doesn't work for the built-in lists and tuples. For example, this variant of my program above compiles fine: {{{ {-# LANGUAGE DataKinds, KindSignatures, PolyKinds, AutoDeriveTypeable, TypeOperators #-} import Data.Proxy import Data.Typeable data Foo (xs :: MyList *) (p :: MyPair * *) data MyList a = Cons a (MyList a) | Nil data MyPair a b = MyPair a b main :: IO () main = print (typeRep (Proxy :: Proxy (Foo (Int `Cons` Nil) ('MyPair Bool Char)))) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): What's the desired behavior here? There are several cases to consider: 1. No `AutoDeriveTypeable`, no `DataKinds`, `deriving` clause on a promotable datatype 2. No `AutoDeriveTypeable`, no `DataKinds`, standalone deriving on a promotable datatype 3. No `AutoDeriveTypeable`, yes `DataKinds`, `deriving` clause on a promotable dataype 4. No `AutoDeriveTypeable`, yes `DataKinds`, standalone deriving on a promotable datatype 5. Yes `AutoDeriveTypeable`, no `DataKinds`, no explicit `deriving` 6. Yes `AutoDeriveTypeable`, yes `DataKinds`, no explicit `deriving` 7. Yes `AutoDeriveTypeable`, no `DataKinds`, explicit `deriving` somewhere 8. Yes `AutoDeriveTypeable`, yes `DataKinds`, explicit `deriving` somewhere Currently, 1, 2, and 5 do their thing for the unpromoted datatype. 3, 4, and 6 work for both the unpromoted and the promoted datatypes. Curiously, 7 & 8 don't work! That is, if you say {{{ {-# LANGUAGE AutoDeriveTypeable #-} data Foo = Bar deriving (Eq) }}} you '''don't''' get `Typeable` instances. This seems to be a bug. It seems to be trying to prevent duplicate instances, but any `deriving` clause (even standalone) triggers the filter. (See around line 550 of !TcDeriv.) I propose: all 8 derive for both the promoted and unpromoted datatype. I can't see a downside to too many `Typeable` instances. Thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): I was slightly wrong above. Case 8 actually derives `Typeable` for the promoted datatype, but not the unpromoted one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): How should we treat this: {{{ data Foo = Bar deriving instance Typeable Foo deriving instance Typeable Bar }}} Is that an error (duplicate instance `Typeable Bar`)? Is it a warning? Silently ignored? What if the `deriving`s are in different modules? And, regardless of specific answers to the above, are we aiming for 7.8 with this? That is, should I be rushing this, or can I get to it when I clump together some GHC tasks? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples
-------------------------------------+------------------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8950: Typeable instances for promoted lists and tuples -------------------------------------+------------------------------------ Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): OK, well, I got sucked into this and spent a couple of hours refactoring `TcDeriv` (again). Man, if I had a pound for each hour I've spent on `deriving`, I'd be a rich bunny. Anyway, the design I have implemented is this: * If you say `AutoDeriveTypeable`, and you do not manually derive `Typeable`, then it's done automatically. * If you derive `Typeable` with `DataKinds` enabled, then you also get `Typeable` instances for the promoted data constructors. * For a data/newtype declared in this module, there is no difference between * putting `Typeable` in the `deriving` clause on a data type declaration * using standalone `deriving instance Typeable T` * However, standalone `deriving` can also derive `Typeable` for * imported types * data families * `AutoDeriveTypeable` derives `Typeable` for * all data/newtypes * all data families * all classes declared in this module. Indeed `AutoDeriveTypeable` is currently the ''only'' way to derive `Typeable` for classes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples
-------------------------------------+------------------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8950: Typeable instances for promoted lists and tuples -------------------------------------------------+------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple deriving/should_compile/T8950 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by goldfire): * testcase: => deriving/should_compile/T8950 Comment: Just added the test case I had written during my first pass. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8950: Typeable instances for promoted lists and tuples
-------------------------------------------------+-------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version:
Resolution: | 7.8.1-rc2
Operating System: Unknown/Multiple | Keywords:
Type of failure: None/Unknown | Architecture:
Test Case: | Unknown/Multiple
deriving/should_compile/T8950 | Difficulty:
Blocking: | Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Simon Peyton Jones

#8950: Typeable instances for promoted lists and tuples -------------------------------------------------+------------------------- Reporter: kosmikus | Owner: Type: bug | Status: Priority: normal | closed Component: libraries/base | Milestone: Resolution: fixed | Version: Operating System: Unknown/Multiple | 7.8.1-rc2 Type of failure: None/Unknown | Keywords: Test Case: | Architecture: deriving/should_compile/T8950 | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: This actually slightly changes which Typeable instances are generated, so I suppose we'd better not merge it to the 7.8 branch unless it gets into 7.8.1 (and it's probably too late for that). Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8950#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC