[Haskell-cafe] TypeLits & Typeable

José Pedro Magalhães jpm at cs.uu.nl
Mon Aug 26 10:19:04 CEST 2013


Hi Nicolas,

It's not intentional, but Iavor is aware of this, and we want to change it.
I'm CC-ing him as he might know more about what the current plan is.


Cheers,
Pedro


On Sat, Aug 24, 2013 at 3:20 PM, Nicolas Trangez <nicolas at incubaid.com>wrote:

> Hello Cafe,
>
> I was playing around with TypeLits in combination with Typeable (using
> GHC 7.7.7.20130812 FWIW), but was surprised to find Symbols aren't
> Typeable, and as such the following doesn't work. Is this intentional,
> or am I missing something?
>
> Thanks,
>
> Nicolas
>
> {-# 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 ()
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130826/3bee5895/attachment.htm>


More information about the Haskell-Cafe mailing list