
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.