module Data.Typeable.Internal(module Data.Typeable.Internal) where import Prelude() import Data.Char_Type import Data.List_Type import System.IO.MD5 type Typeable :: forall k . k -> Constraint class Typeable a where typeRep :: forall proxy . proxy a -> TypeRep data TypeRep = TypeRep MD5CheckSum TyCon [TypeRep] trMd5 :: TypeRep -> MD5CheckSum trMd5 (TypeRep md5 _ _) = md5 mkTyConApp :: TyCon -> [TypeRep] -> TypeRep mkTyConApp tc@(TyCon cmd5 _ _) trs = TypeRep md5 tc trs where md5 = md5Combine (cmd5 : f trs) f [] = [] f (x:xs) = trMd5 x : f xs data TyCon = TyCon MD5CheckSum String String mkTyCon :: String -> String -> TyCon mkTyCon m n = TyCon md5 m n where md5 = md5String (m ++ ("."::String) ++ n)