[GHC] #8178: Need TypeRep for Symbol and numeric type literals; and Typeable instances
GHC
ghc-devs at haskell.org
Tue Aug 27 11:45:29 UTC 2013
#8178: Need TypeRep for Symbol and numeric type literals; and Typeable instances
------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
Nicolas Trangez points out that we don't have a `TypeRep` for types
involving literal strings or numerics. E.g. what is `(typeRep (undefined
:: Proxy "foo"))`?
Here is Nicolas's example:
{{{
{-# LANGUAGE DataKinds,
KindSignatures,
DeriveFunctor,
DeriveDataTypeable #-}
module Main where
import Data.Typeable
import GHC.TypeLits
data NoSymbol n a b = NoSymbol a b
deriving (Typeable)
data WithSymbol (n :: Symbol) a b = WithSymbol a b
deriving (Typeable)
data Sym
deriving (Typeable)
main :: IO ()
main = do
print $ typeOf (undefined :: NoSymbol Sym Int Int)
let d = undefined :: WithSymbol "sym" Int Int
{-
print $ typeOf d
No instance for (Typeable Symbol "sym")
arising from a use of ‛typeOf’
-}
return ()
}}}
Just as types contain literal strings and natural numbers, so too must
`TypeRep`, in some way. Once we have a suitable `TypeRep` we can make
built-in instance for `Typeable` that return the appropriate
representation.
At the moment we have (in `Data.Typeable.Internals`):
{{{
data TypeRep = TypeRep {-# UNPACK #-} !Fingerprint TyCon [TypeRep]
data TyCon = TyCon {
tyConHash :: {-# UNPACK #-} !Fingerprint,
tyConPackage :: String,
tyConModule :: String,
tyConName :: String
}
}}}
with instances for Eq and Ord. Perhaps we need
{{{
data TypeRep
= TcApp {-# UNPACK #-} !Fingerprint TyCon [TypeRep]
| TcSym String
| TcNat Integer
}}}
or something like that? I'm not certain. I think Iavor is going to think
about it.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8178>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list