[Haskell-cafe] RE: Modelling Java Interfaces with Existential data types

Ralf Laemmel Ralf.Laemmel at cwi.nl
Wed Jun 9 14:38:08 EDT 2004


Mike Aizatsky wrote:

>It's quite good. It reminds me the quirks Alexandrescu does in his "Modern
>C++ Design" or here
>http://osl.iu.edu/~tveldhui/papers/Template-Metaprograms/meta-art.html .
>Since type system allows implementation of natural arithmetic, do you know,
>is it Turing-complete?
>
Yes, C. McBride and T. Hallgren and others have done earlier examples of 
what they or we
call faked dependently programming or type-level programming. It is not 
just Turing complete,
it is phantastic. By using type equality and other goodies, we got 
pretty far.

>But I still would like to write type signatures for methods, operating with
>HLists. Or should I make all my list processing functions to be classes
>(like hfold) and to add type constraints in class definition? This sounds
>like a serious development overhead for me.
>
Yes, we favour a dedicated class per method.
Everything beyond that is future work / current research.
Agreed: faking is faking. We want better support for this style.

>>(i) I like comparing Haskell datatypes with Java classes.
>>    
>>
>
>But Java classes also contain t methods. What would you call methods in
>Haskell? Functions on datatypes?
>
Java's methods end up in Haskell as methods in the type classes.
Clearly, the data part can still comprise higher-order functions.

BTW: if you like, think of Java methods as AspectJ introductions.
Java classes are empty (with regard to methods) when you begin.
One way to think of it. So with AspectJ you can modularise in ways
that Haskell suggests anyhow :-)

>You end up
>with creating quite a complicate and non-trivial library for just
>implementing something like List<Interface>.
>
Heterogeneous lists are perhaps an overkill for polymorphic lists modulo 
subtyping.
But there are *many* tradeoffs. For instance, the perhaps easier to 
comprehend version
with existentials and type-safe cast has these problems:
- the \exists makes the data opaque; so one better anticipates all 
operations that are eventually needed in constraints.
- polymorphic recursion and existstentials don't quite nicely go together.
- you need the wrapper constructor to point out existential quantification.

>>I don't see a way to store functions in a file. That's the task Clean
>>Dynamics solve.
>>
I guess others know better than I.
Storing functions isn't possible AFAIK, with Haskell's 
Dynamics/Read/Show, what else?
Similar problems for existentially quantified data.
For the rest, read/show and variations are Ok.
Yes, Clean's Dynamics are cool.

>>-- Yet another heterogeneous equality
>>yaHEq :: (Typeable a, Typeable b, Eq a)  => a -> b -> Bool
>>yaHEq a b = case cast b of
>>             Just a' -> a == a'
>>             Nothing -> False
>>    
>>
>
>Cool! Do you know anything about cast performance?
>
It is implemented rather efficiently in Data.Dynamics,
say one Int per type. So it is basically the cost of Int comparison,
but I don't have performance figures at hand.
There is certainly a kind of startup overhead. Say all the
Ints have to be produced and registered somewhere, but
once all types are around it should be like Int comparison.

>The only issue is to get rid of AnyMyInterface around the code. Can you
>explain me why 
>
>type MyList = forall a. (MyInterface a) => [a]
>list1 :: MyList
>list1 = [MyImplementation1 10, MyImplementation2 20]
>
>doesn't work? Ghc gives pretty obscure (for me) error message:
>
>    Cannot unify the type-signature variable `a'
>        with the type `MyImplementation1'
>        Expected type: a
>        Inferred type: MyImplementation1
>    In the application `MyImplementation1 10'
>    In the list element: MyImplementation1 10
>
I guess you want the forall to be an existential quantifier.
Anyway, the way the forall is placed, it is really a universal one.
So you are saying that you want to get a list of polymorphic
implementations, but your actual list comprises actual implementations.
So the error message is right.
Perhaps enjoy some of this discussion:
http://www.haskell.org/pipermail/haskell/2004-February/013600.html

>PS The sample in your previous post doesn't run due to lack of hMapOut
>  
>
Do you mean that I did not include the hMapOut code?

-- Map a heterogeneous list to a homogeneous one

class HMapOut f r e
 where
  hMapOut :: f -> r -> [e]

instance HMapOut f HNil e
 where
  hMapOut _ _ = []

instance ( HMapOut f l e'
         , HApply f e e'
         )
      =>   HMapOut f (HCons e l) e'
 where
  hMapOut f (HCons e l) = hApply f e : hMapOut f l

I double-checked that the downloadable sources run:
 > ghci gh-users-040607.hs
works.

BTW, yesterday,
I really forgot to include this interesting Eq instance:

instance Eq AnyMyInterface
 where
  (AnyMyInterface x) == (AnyMyInterface y) = x `yaHEq` y
 
Cheers,
Ralf




More information about the Haskell-Cafe mailing list