Type classes and type equality

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

At Mon, 16 Apr 2007 13:44:13 +0100, Neil Mitchell wrote:
Hi,
So my question is if this is safe? Will the compiler always pick the "right one"? Is there a better way to do this?
I noticed that the results can be a bit suprising sometimes. See if you can predict the answers to these (in ghci):
same 1 1
let x = (undefined :: a) in same x x
f :: a -> Bool f a = same a a
f (undefined :: a)
Here is what ghci says: *Main> same 1 1 False *Main> :t 1 1 :: forall t. (Num t) => t *Main> let x = (undefined :: a) in same x x False
f :: a -> Bool f a = same a a
*Main> f (undefined :: a) True I'm not saying anything is wrong here. Just be careful how you use it :) j.

Jeremy Shaw wrote:
I noticed that the results can be a bit suprising sometimes. See if you can predict the answers to these (in ghci):
Interesting examples. Here's another one that I would find problematic: *SameType> same Nothing (Just "xyzzy") False *SameType> same (Nothing :: Maybe String) (Just "xyzzy") True And of course, the case with the integers lifts right up: *SameType> same (Just 1) (Just 1) False
participants (3)
-
Clifford Beshers
-
Jeremy Shaw
-
Neil Mitchell