-------------------------------------------------------------------------------- -------------------------------------------------------------------------------- --Module : Data.Typeable.Extras --Author : Daniel Schüssler --License : BSD3 --Copyright : Daniel Schüssler -- --Maintainer : Daniel Schüssler --Stability : Experimental --Portability : Uses various GHC extensions -- -------------------------------------------------------------------------------- --Description : -------------------------------------------------------------------------------- -------------------------------------------------------------------------------- module Data.Typeable.Extras where import Control.Monad import Data.Typeable import System.IO.Unsafe -- this is just for the missing Ord instance for Data.Typeable.TypeRep import Data.Monoid import Data.Function import Control.Exception dynEq :: (Typeable a, Typeable b, Eq b) => a -> b -> Bool dynEq a b = case cast a of Just b' -> b' == b Nothing -> False compareTypeReps x y = -- compare the string representations first ((compare `on` show) x y) `mappend` -- not sure why 'typeRepKey' is in IO (unsafePerformIO (liftM2 compare (typeRepKey x) (typeRepKey y))) dynCompare :: (Typeable b, Typeable a, Ord b) => a -> b -> Ordering dynCompare a b = case cast a of Just b' -> compare b' b Nothing -> let r = compareTypeReps (typeOf a) (typeOf b) in assert (r/=EQ) r