
On Sat, Jul 20, 2013 at 12:31 AM, Carter Schonwald
the tricky part then is to add support for other types.
another approach to existentially package type classes with the data type!
eg data HasEq = forall a . HasEq ( Eq a => a) or its siblinng data HasEq a = Haseq (Eq a => a )
note this requires more planning in how you structure your program, but is a much more pleasant approach than using dynamic when you can get it to suite your application needs.
note its also late, so I've not type checked these examples ;)
Hi Carter, It doesn't seem like the existential one will work as-is, since ghc rejects this: {-# LANGUAGE ExistentialQuantification #-} data HEQ = forall a. Eq a => HEQ a usingHEQ :: HEQ -> HEQ -> Bool usingHEQ (HEQ a) (HEQ b) = a == b I think you were hinting at this option which is better than my first suggestion: {-# LANGUAGE ExistentialQuantification #-} import Data.Typeable data DYN = forall a. Typeable a => DYN (a, DYN -> Bool) mkDyn :: (Eq a, Typeable a) => a -> DYN mkDyn x = DYN (x, \(DYN (y, eq2)) -> case cast y of Just y' -> x == y' _ -> False) mkDyn' :: Typeable a => a -> DYN mkDyn' x = DYN (x, \_ -> False) eqDyn :: DYN -> DYN -> Bool eqDyn x@(DYN (_, fx)) y@(DYN (_,fy)) = fx y || fy x Maybe there's some way to get mkDyn' and mkDyn as the same function, without having to re-write all of the Eq instances as a 2-parameter class like http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap. -- Adam