-- vim: sw=2: ts=2: expandtab: -- | Usage: -- -- > > polyTypeOf id -- > a1 -> a1 -- -- > > freeTyVars (polyTypeOf id) -- > ["a1"] -- -- > > substTyVar ("a1",polyTypeOf(undefined::Int)) (polyTypeOf id) -- > Int -> Int -- -- > > polyTypeOf const -- > a1 -> a2 -> a1 -- -- > > freeTyVars (polyTypeOf const) -- > ["a1","a2"] -- -- > > substManyTyVars [("a1",polyTypeOf(undefined::Int)),("a2",polyTypeOf(undefined::Bool))] (polyTypeOf const) -- > Int -> Bool -> Int -- module Data.PolyTypeable.Utils where import Data.PolyTypeable import Data.Typeable import List (union) import Char (isLower) -- | collect free type variables (e.g. a1, a2, ...) without duplicates freeTyVars :: TypeRep -> [String] freeTyVars tyrep | isLower (head tcstr) = [tcstr] | otherwise = foldr union [] $ map freeTyVars tcargs where (tycon,tcargs) = splitTyConApp tyrep tcstr = tyConString tycon -- | substitue a type variable substTyVar :: (String, TypeRep) -> TypeRep -> TypeRep substTyVar p@(x, t) tyrep | x == tcstr = t | otherwise = tycon `mkTyConApp` map (substTyVar p) tcargs where (tycon,tcargs) = splitTyConApp tyrep tcstr = tyConString tycon -- | substitue many type variables substTyVars :: [(String,TypeRep)] -> TypeRep -> TypeRep substTyVars = foldr (.) id . zipWith ($) (repeat substTyVar)