
I'm trying to build a nicer interface over the one generated by jvm-bridge. I'm using fancy type classes to remove the need to mangle method names. I would like methods to be automatcially inherited, following an inheritance hierarcy defined with another set of type classes. My basic classes look like this class HasFooMethod cls args result | cls args -> result where foo :: cls -> args -> result If I have classes A and B with foo methods like foo_JA_Jint :: ClassA -> Jint -> Bool foo_JB_Jboolean :: ClassB -> Bool -> Jint then I can make instances instance HasFooMethod ClassA Jint Bool instance HasFooMethod ClassB Bool Jint Now I can just use foo everywhere. I would like to avoid declaring an instance for every class though. In java methods are inherited from a superclass, and I would like to inherit methods automatically as well. In the bindings jvm-bridge generates a method is invoked with a function mangled after the highest ancestor that defined that particular overloading, so the implementation of HasFooMethod at a particular overloading is the same for any descendant. So I defined a class to model the inheritance relationships class SubType super sub | sub -> super where upCast :: sub -> super Now I can define a default instance of HasFooMethod: instance (HasFooMethod super args result, SubClass super sub) => HasFooMethod sub args result where foo sub args = foo (upCast sub) args This will propagate foo methods down the inheritance hierarcy. If a new class C is derived from A, I just need to say instance SubClass ClassA ClassC and ClassC gets a foo method. (In the actually code I piggy-back on a transitive subclass relation jvm-bridge defines that already includes an upcast method, so upCast has a default that should always be acceptable). The problem comes when interfaces are added to the mix. Interfaces are treated just like classes by jvm-bridge, and even though no implementation is inherited from instances in Java, the method accessors generated by jvm-bridge should be inherited. One problem is that the subclass relationship needs the functional dependency so that the default instance of HasFooMethod will respects the functional dependencies of HasFooMethod, so I can't declare subclass instances for multiple inheritance. On the other hand, if I don't use the functional dependency on HasFooMethod I end up needing to annotate most of the return values in a program. I run into similar problems trying to use numeric literals as arguments, because they are also overloaded. Does anyone know of clever solutions that would model multiple inheritance while preserving the functional dependencies (unsafe compiler flags are fine too), or ways to reduce the pain of overloading resolution without the functional dependency? One alternative is generating seperate HasFooMethod instances for every class in the system. The problem is that this would require alterating the bit of jvm-bridge that uses JNI to find information on classes, which currently only reports newly defined methods. JNI is black magic to me. Thanks Brandon

On 25/09/2003, at 7:22 AM, Brandon Michael Moore wrote:
I'm trying to build a nicer interface over the one generated by jvm-bridge. I'm using fancy type classes to remove the need to mangle method names. I would like methods to be automatcially inherited, following an inheritance hierarcy defined with another set of type classes. ...
Hi Brandon, it looks like the way that you're modelling inheritance and OO-style overloading is basically the same way that I did in my thesis: http://www.algorithm.com.au/mocha The actual implementation of the thesis will be up in CVS in ~24 hours, I'm just waiting from an email back from the people I'm getting it hosted with. If you want a quick run-down on how I did the OO-style overloading without delving into the paper, let me know and I'll post a quick summary. I've only skimmed your email, but I think that the problem you're having with interfaces is solved with the way I'm modelling OO overloading and class inheritance. -- % Andre Pang : trust.in.love.to.save

On Thu, 25 Sep 2003 ozone@algorithm.com.au wrote:
On 25/09/2003, at 7:22 AM, Brandon Michael Moore wrote:
I'm trying to build a nicer interface over the one generated by jvm-bridge. I'm using fancy type classes to remove the need to mangle method names. I would like methods to be automatcially inherited, following an inheritance hierarcy defined with another set of type classes. ...
Hi Brandon, it looks like the way that you're modelling inheritance and OO-style overloading is basically the same way that I did in my thesis:
http://www.algorithm.com.au/mocha
The actual implementation of the thesis will be up in CVS in ~24 hours, I'm just waiting from an email back from the people I'm getting it hosted with.
If you want a quick run-down on how I did the OO-style overloading without delving into the paper, let me know and I'll post a quick summary. I've only skimmed your email, but I think that the problem you're having with interfaces is solved with the way I'm modelling OO overloading and class inheritance.
Thanks. I think I could use the summary. I already found and skimmed your thesis, and I don't think it gives me exactly what I want. All you do in chapter 3 is represent a multiple inheritance hierarcy. I want default instances that will propagate method definitions along the hierarcy. I'm not sure that's possible though. I want something like this: data Object data ClassA data ClassB data ClassC class SubClass super sub <???> instance SubClass Object ClassA instance SubClass Object ClassB instance SubClass ClassA ClassC instance SubClass ClassB ClassC class HasFooMethod cls args result ?> foo :: cls -> args -> result instance SubClass super sub, HasFooMethod super args result ,??? => HasFooMethod sub args result where foo obj args = foo (upCast obj) args instance HasFooMethod Object int int where foo = id (now all four classes have a foo method) Brandon

Brandon Michael Moore wrote:
So I defined a class to model the inheritance relationships
class SubType super sub | sub -> super where upCast :: sub -> super
Now I can define a default instance of HasFooMethod: instance (HasFooMethod super args result, SubClass super sub) => HasFooMethod sub args result where foo sub args = foo (upCast sub) args
This will propagate foo methods down the inheritance hierarcy. If a new class C is derived from A, I just need to say
One problem is that the subclass relationship needs the functional dependency
Does anyone know of clever solutions that would model multiple inheritance while preserving the functional dependencies (unsafe compiler flags are fine too), or ways to reduce the pain of overloading resolution without the functional dependency?
Yes. The code included. The solution is trivial: in case of a multiple inheritance, a class has a _sequence_ of superclasses rather than a single superclass. Like instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB -- Multiple inheritance (including the diamond!) instance SubClass (ClassA,(ClassB,())) ClassC instance SubClass (ClassA,(ClassB,(ClassC,()))) ClassD And we need some intelligence to traverse the sequence. But even a computer can do that. I would like to propose a different solution: a dual of typeclasses in the value domain. Function foo is just a regular function foo:: Object -> Int -> Int foo x y = y We then need a class MApplicable fn args result with a method mapply. The trick is that the method should take any object of a type castable and cast it to the type of the first argument of fn. The cast can be made safe and statically checkable, using the type heap. Actually, we can use the type heap to model the dispatch table (whose rows are functions and columns are object/classes). Given a function and an object, we can search in many way for the applicable combination. And now, the code for the solution that works. Compiler flags: -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassC = ClassC data ClassD = ClassD class SubClass super sub | sub -> super where upCast :: sub -> super instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB -- Multiple inheritance (including the diamond!) instance SubClass (ClassA,(ClassB,())) ClassC instance SubClass (ClassA,(ClassB,(ClassC,()))) ClassD class HasFooMethod cls args result where foo :: cls -> args -> result instance (SubClass supers sub, HasFooMethod supers args result) => HasFooMethod sub args result where foo obj args = foo (upCast obj) args instance (HasFooMethod cls args result) => HasFooMethod (cls,()) args result where foo (x,()) = foo x instance (HasFooMethod cls args result) => HasFooMethod (x,cls) args result where foo (x,y) = foo y instance HasFooMethod Object Int Int where foo _ x = x test1::Int = foo Object (1::Int) test2::Int = foo ClassA (2::Int) test3::Int = foo ClassD (3::Int) -- Likewise for another method: class HasBarMethod cls args result where bar :: cls -> args -> result instance (SubClass supers sub, HasBarMethod supers args result) => HasBarMethod sub args result where bar obj args = bar (upCast obj) args instance (HasBarMethod cls args result) => HasBarMethod (cls,()) args result where bar (x,()) = bar x instance (HasBarMethod cls args result) => HasBarMethod (x,cls) args result where bar (x,y) = bar y instance HasBarMethod ClassB Bool Bool where bar _ x = x test4::Bool = bar ClassB True test5::Bool = bar ClassC True test6::Bool = bar ClassD True

On Thu, 25 Sep 2003 oleg@pobox.com wrote:
Brandon Michael Moore wrote:
So I defined a class to model the inheritance relationships
class SubType super sub | sub -> super where upCast :: sub -> super
Now I can define a default instance of HasFooMethod: instance (HasFooMethod super args result, SubClass super sub) => HasFooMethod sub args result where foo sub args = foo (upCast sub) args
This will propagate foo methods down the inheritance hierarcy. If a new class C is derived from A, I just need to say
One problem is that the subclass relationship needs the functional dependency
Does anyone know of clever solutions that would model multiple inheritance while preserving the functional dependencies (unsafe compiler flags are fine too), or ways to reduce the pain of overloading resolution without the functional dependency?
Yes. The code included. The solution is trivial: in case of a multiple inheritance, a class has a _sequence_ of superclasses rather than a single superclass. Like
instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB
-- Multiple inheritance (including the diamond!) instance SubClass (ClassA,(ClassB,())) ClassC instance SubClass (ClassA,(ClassB,(ClassC,()))) ClassD
And we need some intelligence to traverse the sequence. But even a computer can do that.
That should solve my problem. Putting all the superclasses in a tuple should work. I'm worried about large class hierarchies. If it works on the java.* classes I should be fine. Have you used this approach before? I'm worried about compile time, runtime costs from the casts (hopefully they compile out), and maybe exceeding maximum stack depth in context reduction. This is a clever solution. I like it. Now, is anyone up to encoding the Dylan MRO in Haskell type classes? ;)
I would like to propose a different solution: a dual of typeclasses in the value domain. Function foo is just a regular function
foo:: Object -> Int -> Int foo x y = y
We then need a class MApplicable fn args result with a method mapply. The trick is that the method should take any object of a type castable and cast it to the type of the first argument of fn. The cast can be made safe and statically checkable, using the type heap. Actually, we can use the type heap to model the dispatch table (whose rows are functions and columns are object/classes). Given a function and an object, we can search in many way for the applicable combination.
What type heap? It sounds like you are talking about information from an OO runtime, or are you talking about the collection of instances. I tried a system where method names were also represented by data types, but without your solution for multiple inheritance I couldn't get the implementation inheritance I wanted. How would you implement this dispatch table? What are the advantages of this approach over the type class encoding? I'm worried that generating bindings would be a problem if the dispatch table needs to be a monolithic value with a very interesting type in some file. Brandon
And now, the code for the solution that works. Compiler flags: -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances
data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassC = ClassC data ClassD = ClassD
class SubClass super sub | sub -> super where upCast :: sub -> super
instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB -- Multiple inheritance (including the diamond!) instance SubClass (ClassA,(ClassB,())) ClassC instance SubClass (ClassA,(ClassB,(ClassC,()))) ClassD
class HasFooMethod cls args result where foo :: cls -> args -> result
instance (SubClass supers sub, HasFooMethod supers args result) => HasFooMethod sub args result where foo obj args = foo (upCast obj) args
instance (HasFooMethod cls args result) => HasFooMethod (cls,()) args result where foo (x,()) = foo x
instance (HasFooMethod cls args result) => HasFooMethod (x,cls) args result where foo (x,y) = foo y
instance HasFooMethod Object Int Int where foo _ x = x
test1::Int = foo Object (1::Int) test2::Int = foo ClassA (2::Int) test3::Int = foo ClassD (3::Int)
-- Likewise for another method:
class HasBarMethod cls args result where bar :: cls -> args -> result
instance (SubClass supers sub, HasBarMethod supers args result) => HasBarMethod sub args result where bar obj args = bar (upCast obj) args
instance (HasBarMethod cls args result) => HasBarMethod (cls,()) args result where bar (x,()) = bar x
instance (HasBarMethod cls args result) => HasBarMethod (x,cls) args result where bar (x,y) = bar y
instance HasBarMethod ClassB Bool Bool where bar _ x = x
test4::Bool = bar ClassB True test5::Bool = bar ClassC True test6::Bool = bar ClassD True

Brandon Michael Moore wrote regarding the first solution: chain of super-classes:
I'm worried about large class hierarchies. If it works on the java.* classes I should be fine. Have you used this approach before? I'm worried about compile time, runtime costs from the casts (hopefully they compile out), and maybe exceeding maximum stack depth in context reduction.
I didn't use the approach for anything as complex as all java.* classes. The only run-time costs are evaluating the chain of fst . snd . fst . .... The length and the composition of the chain is statically known. Perhaps the compiler can do something smart here. The maximum length of the chain is the maximum depth of the inheritance tree. It shouldn't be too big. A cast from a subclass to a superclass has to be executed anyway (if not by your code then by JVM). If the maximum stack depth is exceeded, we can repeat the compilation with a compiler flag to allocate a bigger stack. In my experience the only time I've seen the derivation stack depth exceeded is when the derivation truly diverges.
What type heap? It sounds like you are talking about information from an OO runtime, or are you talking about the collection of instances.
The other solution I talked so confusingly before is that of generic functions. For that, we need a way to obtain a value representation of a type. Several such representations exists: e.g., Typable, representation as an integer, etc. All our objects must be members of the class Typable. A method (generic function foo) would have the following signature: foo:: (Typable object) => object -> Int ->Int For example, if foo is defined for ClassA object only, we can write foo obj arg = if inherit_from (typeof obj) (typeof (undefined::ClassA)) then particular_instance_foo (coerce obj) arg else error "miscast" If bar is defined for classB and redefined in classC, we can write bar obj arg = if inherit_from (typeof obj) (typeof (undefined::ClassC)) then particular_instance1_bar (coerce obj) arg else if inherit_from (typeof obj) (typeof (undefined::ClassB)) then particular_instance2_bar (coerce obj) arg else error "miscast" The functions inherit_from and coerce avail themselves of a table that records the relationship between types using their value representations. The disadvantage of this approach is that the cast errors become run-time errors. OTH, because type representations and the whole inheritance graph are values, we can do much more. We can check for proper and improper diamond inheritance, we can do a rather sophisticated dispatch. Types heap and several ways of doing safe casts are discussed in http://www.haskell.org/pipermail/haskell/2003-August/012372.html http://www.haskell.org/pipermail/haskell/2003-August/012355.html See also: http://citeseer.nj.nec.com/cheney02lightweight.html http://citeseer.nj.nec.com/context/1670116/0 The Sketch of a Polymorphic Symphony http://homepages.cwi.nl/~ralf/polymorphic-symphony/

On Fri, 26 Sep 2003 oleg@pobox.com wrote:
Brandon Michael Moore wrote regarding the first solution: chain of super-classes:
I'm worried about large class hierarchies. If it works on the java.* classes I should be fine. Have you used this approach before? I'm worried about compile time, runtime costs from the casts (hopefully they compile out), and maybe exceeding maximum stack depth in context reduction.
I didn't use the approach for anything as complex as all java.* classes. The only run-time costs are evaluating the chain of fst . snd . fst . ....
I think I can use the pair types as phantom types on a reference type, so my casts will hopefully be the identity function. (.) should be small enough to inline, so GHC probably compiles id . id ... id to id. Correct?
The length and the composition of the chain is statically known. Perhaps the compiler can do something smart here. The maximum length of the chain is the maximum depth of the inheritance tree. It shouldn't be too big. A cast from a subclass to a superclass has to be executed anyway (if not by your code then by JVM). If the maximum stack depth is exceeded, we can repeat the compilation with a compiler flag to allocate a bigger stack. In my experience the only time I've seen the derivation stack depth exceeded is when the derivation truly diverges.
Same for me, but I've never tried to model the java.* hierarchy either. I think you get a cast (fst in your code) for each parent of each ancestor along the inheritance path, which probably increses the count some. Your code doesn't quite work. The instances you gave only allow you to inherit from the rightmost parent. GHC's inference algorithm seems to pick one rule for a goal and try just that. To find instances in the first parent and in other parents it needs to try both. I think I'll just give up on inheriting methods, and generate unrelated instances for each class that needs one. Brandon

This message illustrates how to get the typechecker to traverse non-flat, non-linear trees of types in search of a specific type. We have thus implemented a depth-first tree lookup at the typechecking time, in the language of classes and instances. The following test is the best illustration:
instance HasBarMethod ClassA Bool Bool -- Specification of the derivation tree by adjacency lists instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB instance SubClass (ClassA,(ClassB,())) ClassCAB instance SubClass (ClassB,(ClassA,())) ClassCBA instance SubClass (Object,(ClassCBA,(ClassCAB,(Object,())))) ClassD instance SubClass (Object,(ClassB,(ClassD,(Object,())))) ClassE
test6::Bool = bar ClassE True
It typechecks. ClassE is not explicitly in the class HasBarMethod. But the compiler has managed to infer that fact, because ClassE inherits from ClassD, among other classes, ClassD inherits from ClassCBA, among others, and ClassCBA has somewhere among its parents ClassA. The typechecker had to traverse a notable chunk of the derivation tree to find that ClassA. Derivation failures are also clearly reported:
test2::Bool = bar ClassB True No instance for (HasBarMethodS () ClassA) arising from use of `bar' at /tmp/m1.hs:46 In the definition of `test2': bar ClassB True
Brandon Michael Moore wrote:
Your code doesn't quite work. The instances you gave only allow you to inherit from the rightmost parent. GHC's inference algorithm seems to pick one rule for a goal and try just that. To find instances in the first parent and in other parents it needs to try both.
The code below fixes that problem. It does the full traversal. Sorry for a delay in responding -- it picked a lot of fights with the typechecker. BTW, the GHC User Manual states:
However the rules are over-conservative. Two instance declarations can overlap, but it can still be clear in particular situations which to use. For example:
instance C (Int,a) where ... instance C (a,Bool) where ...
These are rejected by GHC's rules, but it is clear what to do when trying to solve the constraint C (Int,Int) because the second instance cannot apply. Yell if this restriction bites you.
I would like to quietly mention that the restriction has bitten me many times during the development of this code. I did survive though. The code follows. Not surprisingly it looks like a logical program. Actually it does look like a Prolog code -- modulo the case of the variables and constants. Also head :- ant, ant2, ant3 in Prolog is written instance (ant1, ant2, ant3) => head in Haskell. {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances #-} data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassCAB = ClassCAB data ClassCBA = ClassCBA data ClassD = ClassD data ClassE = ClassE class SubClass super sub | sub -> super where upCast:: sub -> super instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB instance SubClass (ClassA,(ClassB,())) ClassCAB instance SubClass (ClassB,(ClassA,())) ClassCBA instance SubClass (Object,(ClassCBA,(ClassCAB,(Object,())))) ClassD -- A quite bushy tree instance SubClass (Object,(ClassB,(ClassD,(Object,())))) ClassE class HasBarMethod cls args result where bar :: cls -> args -> result instance (SubClass supers sub, HasBarMethodS supers ClassA) => HasBarMethod sub args result where bar obj args = undefined -- let the JVM bridge handle the upcast class HasBarMethodS cls c instance HasBarMethodS (t,x) t instance (HasBarMethodS cls t) => HasBarMethodS (Object,cls) t instance (HasBarMethodS cls t) => HasBarMethodS ((),cls) t instance (SubClass supers c, HasBarMethodS (supers,cls) t) => HasBarMethodS (c,cls) t instance (HasBarMethodS (a,(b,cls)) t) => HasBarMethodS ((a,b),cls) t instance HasBarMethod ClassA Bool Bool where bar _ x = x test1::Bool = bar ClassA True --test2::Bool = bar ClassB True test3::Bool = bar ClassCAB True test4::Bool = bar ClassCBA True test5::Bool = bar ClassD True test6::Bool = bar ClassE True

This seems to work. The type checker picks one rule to use at each point so you can't get backtracking, but you explicitly build the sequence of base classes, and use the overloading resolution to stop if we find our goal. This is clever. It looks like prolog could be interesting. My first introduction to functional programming was Unlambda (and I didn't run screaming), and it seems the Haskell type class system is being my introduction to logic programming. I get into paradigms the oddest ways. Let's see if I understand the algorithm. It looks like the instances for HasBarMethods implement a search through the ancestors of a class, with an axiom that stops if the topmost class on the stack is the one we are looking for, discards the top class if is Object or (), unpacks it if it is a tuple, otherwise replaces it with the tuple of parents. I've modified the code to express searches for multiple base classes, but the list of classes defining a method needs to be hardcoded. I want a solution that doesn't require any global analysis of the interface I'm generating bindings for. I think I could do something similar with explicitly iterating over all the methods on all the classes I hit, with special merker types for each method name, but I haven't worked it out yet. P.S to implementors: backtracking search in the type class resolution would make this sort of thing much easier to code Brandon ---------------- Classes.hs {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Classes where data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassC = ClassC data ClassD = ClassD class SubClass super sub | sub -> super instance SubClass (Object,()) ClassA instance SubClass (Object,()) ClassB instance SubClass (ClassA,()) ClassC instance SubClass (ClassB,()) ClassD {- O / \ A B | | C D -} class HasBarMethod cls args result where bar :: cls -> args -> result instance HasAncestors cls (ClassA,(ClassB,())) => HasBarMethod cls args result where bar obj args = undefined instance HasBarMethod ClassA args result where bar obj args = undefined instance HasBarMethod ClassB args result where bar obj args = undefined class HasFooMethod cls args result where foo :: cls -> args -> result instance HasAncestor cls ClassA => HasFooMethod cls args result where foo obj args = undefined instance HasFooMethod ClassA args result where foo obj args = undefined class HasBazMethod cls args result where baz :: cls -> args -> result instance HasAncestor cls ClassB => HasBazMethod cls args result where baz obj args = undefined instance HasBazMethod ClassB args result where baz obj args = undefined class HasAncestor cls t --instance (SubClass supers cls,HasAncestorS supers t) => HasAncestor cls t instance (SubClass supers cls, HasAncestorS cls supers (t,())) => HasAncestor cls t class HasAncestors cls ts instance (SubClass supers cls, HasAncestorS cls supers ts) => HasAncestors cls ts class HasAncestorS start cls c instance HasAncestorS start (t,x) (t,y) instance (HasAncestorS start cls (t,ts)) => HasAncestorS start (Object,cls) (t,ts) instance (HasAncestorS start cls (t,ts)) => HasAncestorS start ((),cls) (t,ts) instance (SubClass supers c, HasAncestorS start (supers,cls) ts) => HasAncestorS start (c,cls) ts instance (SubClass supers start, HasAncestorS start supers ts) => HasAncestorS start () (t,ts) instance (HasAncestorS start (a,(b,cls)) (t,ts)) => HasAncestorS start ((a,b),cls) (t,ts) ------then in GHCI --test bar *Classes> bar ClassA 0 *** Exception: Prelude.undefined *Classes> bar ClassA 0 *** Exception: Prelude.undefined *Classes> bar ClassB 0 *** Exception: Prelude.undefined *Classes> bar ClassC 0 *** Exception: Prelude.undefined *Classes> bar ClassD 0 *** Exception: Prelude.undefined --test foo *Classes> foo ClassA 0 *** Exception: Prelude.undefined *Classes> foo ClassB 0 <interactive>:1: No instance for (HasAncestorS ClassB (Object, ()) ()) arising from use of `foo' at <interactive>:1 In the definition of `it': it = foo ClassB 0 *Classes> foo ClassC 0 *** Exception: Prelude.undefined *Classes> foo ClassD 0 <interactive>:1: No instance for (HasAncestorS ClassD (ClassB, ()) ()) arising from use of `foo' at <interactive>:1 In the definition of `it': it = foo ClassD 0 --test baz *Classes> baz ClassA 0 <interactive>:1: No instance for (HasAncestorS ClassA (Object, ()) ()) arising from use of `baz' at <interactive>:1 In the definition of `it': it = baz ClassA 0 *Classes> baz ClassB 0 *** Exception: Prelude.undefined *Classes> baz ClassC 0 <interactive>:1: No instance for (HasAncestorS ClassC (ClassA, ()) ()) arising from use of `baz' at <interactive>:1 In the definition of `it': it = baz ClassC 0 *Classes> baz ClassD 0 *** Exception: Prelude.undefined

One part of the solution that I didn't like is that the constraint on a method had to explicitly list all the classes that declared that method. That hampers generating the binding a class at a time, so I fixed it. I still don't match the type of the method against the types declared, but that shouldn't be too hard to add. Thanks for all your help, oleg. Brandon -----Classes.hs {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Classes where --marker types for the classes data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassC = ClassC data ClassD = ClassD data ClassE = ClassE --marker types for the methods data Foo = Foo instance SubClass () Foo foo :: (HasMethod Foo obj args result) => obj -> args -> result foo = call Foo data Bar = Bar instance SubClass () Bar bar :: (HasMethod Bar obj args result) => obj -> args -> result bar = call Bar data Baz = Baz instance SubClass () Baz baz :: (HasMethod Baz obj azgs result) => obj -> azgs -> result baz = call Baz --class and instances to record classes interface and ancestors --notice the information about which methods a class declares --is only stored here class Interface super sub | sub -> super instance Interface () Object instance Interface (Foo,(Bar,(Object,()))) ClassA instance Interface (Foo,(Baz,(Object,()))) ClassB instance Interface (ClassA,()) ClassC instance Interface (ClassB,()) ClassD instance Interface (ClassA,(ClassB,(ClassC,()))) ClassE --Ancestors Have Method --the "worker type class" to search for ancestors class AHM objs method instance AHM (t,x) t instance (AHM cls t) => AHM ((),cls) t instance (Interface items c, AHM (items,cs) t) => AHM (c,cs) t instance (AHM (a,(b,cls)) t) => AHM ((a,b),cls) t --now we can express the constraint that a class inherits a method class HasMethod method obj args result where call :: method -> obj -> args -> result instance (Interface items cls, AHM items method) => HasMethod method cls args result where call method obj args = undefined

Thanks for the clever code Oleg. I've tried to extend it again to track the types of methods as well as just the names, giving a functional dependancy from the class, method, and to result type. I can't get the overlapping instances to work out, so I'm handing it back to a master, and the rest of the list. We really should change GHC rather than keep trying to work around stuff like this. GHC will be my light reading for winter break. The core of the classes are here: --records superclasses and new methods. class Interface super sub | sub -> super --This has any new methods/overloadings, as well as superclasses. instance Interface (Foo Int Bool,(Bar Bool Int,(ClassC,(ClassA,())))) ClassB --the "worker type class" to search the ancestors for a method. --"Ancestors Have Method" class AHM objs (method :: * -> * -> *) args result | objs method args -> result --the first two instances conflict. instance AHM (m a r,x) m a r instance (AHM (x,(y,cs)) m a r) => AHM ((,) x y,cs) m a r instance (AHM cs m a r) => AHM ((),cs) m a r instance (Interface items c, AHM (items,cs) m a r) => AHM (c,cs) m a r The instances AHM (m a r,x) m a r and AHM ((,) x y,cs) m a r) are conflicting. Again, I'm willing to compute the inheritance once and have a tool write out instances for each overloading availible at each class, but it's just so much cooler to do this in the typeclass system. For anyone who hasn't been following this, the problem is a java interface. There are several classes, in a DAG. At several points in the DAG methods are declared, with an argument type and a return type. I want some statically checked way of resolving a call with the name, an object, and an argument list to a particular declaration of the method with the same arguments in one of the ancestors of the class. Bonus points for a functional dependancy from class+arguments to result. The practical upshot is being able to write code no more complicated than the java you are replacing: do frame <- new_JFrame () set_size frame (10,100) set_visible frame True ... vs. do frame <- new_JFrame () set_size_JFrame_JInt_JInt_JVoid frame (10,100) set_visible_JFrame_JBool_JVoid frame True ... and fun things like functions that work on any object with the correct interface, not just descendants of some particular class (hey, it's neat for statically-typed OO languages, okay?) Brandon

Hello! Let me describe (my understanding of) the problem first. Let us assume a Java-like OO language, but with multiple inheritance. Let us consider the following hierarchy: Object -- the root of the hierarchy ClassA: inherits from Object defines method Foo::Int -> Bool defines method Bar::Bool -> Int ClassB: inherits from Object and ClassA overloads the inherited method Foo with Foo:: Int->Int overrides method Bar:: Bool -> Int ClassC: inherits from ClassA -- defines no extra methods ClassD: inherits from ClassB overrides method Foo::Int->Bool it inherited from ClassA via ClassB ClassE: inherits from classes A, B, C, and D We would like to define a function foo that applies to an object of any class that implements or inherits method Foo. Likewise, we want a function bar be applicable to an object of any class that defines or inherits method Bar. We want the typechecker to guarantee the above properties. Furthermore, we want the typechecker to choose the most appropriate class that implements the desired method. That is, we want the typechecker to resolve overloading and overriding in multiple-inheritance hierarchies. The resolution depends not only on the name of the method but also on the type of its arguments _and_ the result. That is, we aim higher than most languages that command the most of the job postings. The code below is a trivial modification to the code Brandon Michael Moore posted the other month.
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} import Debug.Trace
marker types for the classes
data Object = Object data ClassA = ClassA data ClassB = ClassB data ClassC = ClassC data ClassD = ClassD data ClassE = ClassE
instance Show Object where { show _ = "Object" } instance Show ClassA where { show _ = "ClassA" } instance Show ClassB where { show _ = "ClassB" } instance Show ClassC where { show _ = "ClassC" } instance Show ClassD where { show _ = "ClassD" } instance Show ClassE where { show _ = "ClassE" }
marker types for the methods
data Foo arg result = Foo data Bar arg result = Bar
Let us encode the class hierarchy by a straightforward translation of the above class diagram. For each class, we specify the list of its _immediate_ parents.
class Interface super sub | sub -> super instance Interface () Object instance Interface (Object,()) ClassA instance Interface (Object,(ClassA,())) ClassB instance Interface (ClassA,()) ClassC instance Interface (ClassB,()) ClassD instance Interface (ClassD, (ClassA,(ClassB,(ClassC,())))) ClassE
Let us now describe the methods defined by each class. A method is specified by its full signature: Foo Int Bool is to be read as Foo:: Int -> Bool.
class Methods cls methods | cls -> methods instance Methods Object ()
instance Methods ClassA (Foo Int Bool, (Bar Bool Int, ())) instance Methods ClassB (Foo Int Int, (Bar Bool Int,())) instance Methods ClassC () -- adds no new methods instance Methods ClassD (Foo Int Bool,()) instance Methods ClassE () -- adds no new methods
The following is the basic machinery. It builds (figuratively speaking) the full transitive closure of Interface and Method relations and resolves the resolution. The tests are at the very end. First we define two "mutually recursive" classes that do the resolution of the overloading and overriding. By "mutually recursive" we mean that the typechecker must mutually recurse. A poor thing... Methods mtrace_om and mtrace_ahm will eventually tell the result of the resolution: the name of the concrete class that defines or overrides a particular signature.
class AHM objs method where mtrace_ahm:: objs -> method -> String
class OM methods objs obj method where mtrace_om:: methods -> objs -> obj -> method -> String
instance (Methods c methods, Interface super c, OM methods (super,cs) c method) => AHM (c,cs) method where mtrace_ahm _ = mtrace_om (undefined::methods) (undefined::(super,cs)) (undefined::c)
instance (AHM cls t) => AHM ((),cls) t where mtrace_ahm _ = mtrace_ahm (undefined::cls)
instance (Show c) => OM (method,x) objs c method where mtrace_om _ _ c _ = show c
instance (OM rest objs c method) => OM (x,rest) objs c method where mtrace_om _ = mtrace_om (undefined::rest)
instance (AHM objs method) => OM () objs c method where mtrace_om _ _ _ = mtrace_ahm (undefined::objs)
instance (AHM (a,(b,cls)) t) => AHM ((a,b),cls) t where mtrace_ahm _ = mtrace_ahm (undefined::(a,(b,cls)))
Now we can express the constraint that a class inherits a method
class HasMethod method obj args result where call :: method args result -> obj -> args -> result mtrace:: method args result -> obj -> String
instance (AHM (cls,()) (method args result)) => HasMethod method cls args result where call sig obj args = trace (mtrace sig obj) undefined mtrace sig _ = mtrace_ahm (undefined::(cls,())) sig
A polymorphic function foo can be applied to any thing that defines a polymorphic (overloaded) function Foo:
foo:: (HasMethod Foo cls args result) => (Foo args result) -> cls -> args -> result foo = call
Likewise, for 'bar'
bar:: (HasMethod Bar cls args result) => (Bar args result) -> cls -> args -> result bar = call
Finally, the tests
test1::Bool = foo Foo ClassA (1::Int)
test1 prints "ClassA" -- that is, applying foo to ClassA resolves to the method Foo defined in ClassA.
test2::Int = bar Bar ClassA True
test2 also prints "ClassA" -- for method Bar defined in ClassA.
test3::Bool = foo Foo ClassB (1::Int) test4::Int = foo Foo ClassB (1::Int)
test4 prints ClassB but test3 prints ClassA! We see the overloading in action: ClassB overloads Foo for the signature Foo::Int->Int. So, if applying foo to ClassB is expected to yield a Bool, the system finds us a method Foo::Int->Bool that ClassB inherited from ClassA. OTH, if we want the result of the application of foo to yield an Int, the system finds an overloaded instance introduced by ClassB itself. If we uncomment the following
--test4'::Int = foo Foo ClassA (1::Int)
We get: /tmp/b.lhs:192: No instance for (AHM () (Foo Int Int)) arising from use of `foo' at /tmp/b.lhs:192 In the definition of `test4'': foo Foo ClassA (1 :: Int) Indeed, ClassA has no method Foo::Int->Int. The resolution errors are determined _statically_. Note that the error message is clear.
test1c::Bool = foo Foo ClassC (1::Int) test1d::Bool = foo Foo ClassD (1::Int) test1e::Bool = foo Foo ClassE (1::Int)
test1c prints ClassA, test1d prints ClassD and test1e prints ClassD.
participants (3)
-
Brandon Michael Moore
-
oleg@pobox.com
-
ozone@algorithm.com.au