[Haskell-cafe] TypeLits & Typeable

Nicolas Trangez nicolas at incubaid.com
Sat Aug 24 15:20:33 CEST 2013


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 ()





More information about the Haskell-Cafe mailing list