类型与类型构造函数 *->* / 打印程序内值的类型



考虑以下内容:

module Main where
data Tree a = EmptyTree | Node a (Tree a) (Tree a) deriving (Show, Read, Eq) 
data Container a b = Container{contField :: b a} deriving (Show)
result = Container {contField = Node 'a' EmptyTree EmptyTree}
main = do 
    print result

如果我将其加载到GHCI中,那么我将获得result的类型:

*Main> :t result
result :: Container Char Tree

如何从程序中打印Container Char Tree类型?我试图调整Haskell给出的解决方案 - 从混凝土类型实例中获取Typerep,但我被卡住了,因为我找不到与类型* -> *

的类型构造函数一起使用typeOf的方法

[编辑]:本文中的一些方法已在版本7.8.1的GHC 7.8.1发行说明中被弃用:

现在是poly kinded的,使typable1,typable2等,等等 过时,弃用并降级为data.oldtypable。此外, 现在不允许使用用户写入的实例:使用派生或 新的扩展-xautoderivetypyable,它将创建可典型的 在模块中声明的每个数据类型的实例。

一种可能性是自己创建一个Typeable实例。我在为Container创建TyCon方面有些挣扎,也许有更好的方法:

{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Main where
import Data.Dynamic
import Data.Typeable
data Tree a = EmptyTree | Node a (Tree a) (Tree a)
    deriving (Show, Read, Eq, Typeable)
-- copy a representation of a type constructor from 
-- an existing representation
copyTyCon :: Typeable a => a -> String -> TyCon
copyTyCon x = mkTyCon3 (tyConPackage tc) (tyConModule tc)
  where tc = typeRepTyCon (typeOf x)
data Dummy = Dummy -- just to get package/module names for Container
    deriving (Typeable)
data Container a b = Container { contField :: b a }
    deriving (Show)
instance (Typeable a, Typeable1 f) => Typeable (Container a f) where
    typeOf (Container x) = mkTyConApp (copyTyCon Dummy "Container")
                                      [typeOf (undefined :: a), typeOf1 x]

result = Container { contField = Node 'a' EmptyTree EmptyTree }
main = do 
    print $ typeOf result
    print result

用一粒盐来服用,我对Typeable的经验不太经验。

最新更新