[GHC] #8950: Typeable instances for promoted lists and tuples
GHC
ghc-devs at haskell.org
Wed Apr 2 18:51:55 UTC 2014
#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
More information about the ghc-tickets
mailing list