[Haskell-cafe] Type classes and type equality

Neil Mitchell ndmitchell at gmail.com
Mon Apr 16 08:44:13 EDT 2007


Hi,

I'm looking for a type class which checks whether two types are the
same or not. My first guess is:

class Same a b where
   same :: a -> b -> Bool

instance Same a a where
   same _ _ = True

instance Same a b where
   same _ _ = False

In Hugs this seems to work with overlapping instances (not requiring
unsafe overlapping instances).

GHC requires {-# LANGUAGE MultiParamTypeClasses, IncoherentInstances #-}

So my question is if this is safe? Will the compiler always pick the
"right one"? Is there a better way to do this?

The alternative I thought of is using Typeable, but this is not
supported particularly well on Hugs (no deriving Typeable) and would
require modifications to the existing data structures (additional
derivings) so is not such a good choice.

Thanks

Neil


More information about the Haskell-Cafe mailing list