{-# LANGUAGE UndecidableInstances, OverlappingInstances, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances #-} -- -- .$Header: c:/Source/Haskell/Type/Data/Type/RCS/Eq.hs,v 1.3 2011/03/05 00:30:04 dosuser Exp dosuser $ module Data.Type.Eq where import Data.Type.Bool class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x class TypeEq x y b | x y -> b instance TypeEq x x TTrue instance TypeCast TFalse b => TypeEq x y b -- vim: expandtab:tabstop=4:shiftwidth=4