Question

Consider the following :

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

If I load this into ghci, then I get the following for the type of result :

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

How can I print the type Container Char Tree from within the program? I was trying to adapt the solution given at Haskell — get TypeRep from concrete type instance but I got stuck because I could not find a way to use typeOf in conjunction with type constructors of kind * -> *

[EDIT] : Some of the methods in this post have been deprecated in ghc 7.8.1 Release notes for version 7.8.1 :

Typeable is now poly-kinded, making Typeable1, Typeable2, etc., obsolete, deprecated, and relegated to Data.OldTypeable. Furthermore, user-written instances of Typeable are now disallowed: use deriving or the new extension -XAutoDeriveTypeable, which will create Typeable instances for every datatype declared in the module.

Was it helpful?

Solution

One possibility would be to create a Typeable instance yourself. I struggled a bit with creating TyCon for Container, maybe there is a better way how to do it:

{-# 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

Take it with a grain of salt, I'm not very experienced with Typeable.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top