
Hello, I'm in process of rewriting the old Java application. While this is for sure lots of fun, there're some problems in modeling the java interfaces. Here's the common Java scenario (it's actually the pattern, common for all OO-languages, so there should be no problems in understanding it): interface MyInterface { int foo(); } class MyImplementation1 implements MyInterface { int foo() {...} } class MyImplementation2 implements MyInterface { int foo() {...} } And, somewhere in the code: int bar(List<MyInterface> list) { .... sum up all foos & return .... } I've found quite an obvious translation of it to Haskell: module Ex where class MyInterface a where foo :: a -> Int data AnyMyInterface = forall a. (MyInterface a) => AnyMyInterface a instance MyInterface AnyMyInterface where foo (AnyMyInterface a) = foo a data MyImplementation1 = MyImplementation1 Int instance MyInterface MyImplementation1 where foo(MyImplementation1 i) = i data MyImplementation2 = MyImplementation2 Int instance MyInterface MyImplementation2 where foo(MyImplementation2 i) = i type MyList = [AnyMyInterface] list1 :: MyList list1 = [AnyMyInterface (MyImplementation1 10), AnyMyInterface (MyImplementation2 20)] bar :: MyList -> Int bar l = sum (map foo l) However there're some problems with this way to go: 1. It's quite verbose. I already have a dozen of such interfaces, and I'm a bit tired of writing all this AnyInterface stuff. I'm already thinking about writing the Template Haskell code to generate it. Is anything similar available around? 2. I don't like the fact that I need to wrap all implementations inside the AnyMyInterface when returning values (see list1). Any way to get rid of it? 3. The big problem. I can't make AnyMyInterface to be an instance of Eq. I write: data AnyMyInterface = forall a. (MyInterface a, Eq a) => AnyMyInterface a instance Eq AnyMyInterface where (==) (AnyMyInterface a1) (AnyMyInterface a2) = a1 == a2 And it gives me an error (ghc 6.2.1): Inferred type is less polymorphic than expected Quantified type variable `a1' is unified with another quantified type variable `a' When checking an existential match that binds a1 :: a a2 :: a1 The pattern(s) have type(s): AnyMyInterface AnyMyInterface The body has type: Bool In the definition of `==': == (AnyMyInterface a1) (AnyMyInterface a2) = a1 == a2 In the definition for method `==' Honestly, I don't understand what's going on. My guess is that the problem comes from the fact that a1 & a2 might be of different Implementations. Is it right? Any way to define the Eq instance of AnyMyInterface? So, it looks like that existential data types do allow you to mimic the polymorphic data structures, found in OO languages. But it results in much more verbose code. Are there any other ways to do the same stuff?