Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-15 Thread Sven Panne
Ralf Laemmel wrote:
[...]
find . -name configure.ac -print


to find all dirs that need autoreconf (not autoconf anymore)

autoreconf
(cd ghc; autoreconf)
(cd libraries; autoreconf)
FYI: Just issue autoreconf at the toplevel, and you're done. It will
descend into all necessary subdirectories, just like configure itself.
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-06 Thread Brandon Michael Moore


On Wed, 5 Nov 2003, Simon Peyton-Jones wrote:

 | More overlapping:
 | Allow any overlapping rules, and apply the most specific rule that
 | matches our target. Only complain if there is a pair of matching
 | rules neither of which is more specific than the other.
 | This follow the spirit of the treatment of duplicate imports...

 Happy days.  I've already implemented this change in the HEAD.  If you
 can build from source, you can try it.

Great. But I can't build from the source: I'm getting errors about a
missing config.h.in in mk. I'm just trying autoconf, comfigure. I'll look
closer over the weekend.

 | Backtracking search:
 | If several rules matched your target, and the one you picked didn't
 | work, go back and try another.
 |
 | This isn't as well through out: you probably want to backtrack through
 all
 | the matching rules even if some are unordered by being more specific.
 It
 | would probably be godd enough to respect specificity, and make other
 | choices arbitrarilily (line number, filename, etc. maybe Prolog has a
 | solution?). This probably isn't too hard if you can just add
 | nondeterminism to the monad the code already lives in.

 I didn't follow the details of this paragraph.  But it looks feasible.

It's an unclear paragraph. I meant that if we are just looking for the
first match, we should try more specific rules before less specific rule.
That doesn't give us a complete ordering so we might do something
arbitrary for the rest, unless there is a better solution.

I think we should make sure that there are not multiple solutions, but we
want more specific rules to take priority. Order the solutions
lexicographically by how specific each rule in the derivation was and
complain if there isn't a least element in this set of solutions.  To
implement, if at each step there is a most specific rule in the set we
haven't tried, and making that choice at every step gives us a solution,
we know we have the most specific solution and don't need to keep
searching.

I don't want to be too strict about having a unique solution because
that can prevent modelling multiple inheritance

Brandon

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-06 Thread Ralf Laemmel
Brandon Michael Moore wrote:

Great. But I can't build from the source: I'm getting errors about a
missing config.h.in in mk. I'm just trying autoconf, comfigure. I'll look
closer over the weekend.
 

Use the following (more specifically autoREconf).
The GHC build guide is behind.
cvs -d cvs.haskell.org:/home/cvs/root checkout fpconfig
or use anonymous access.

cd fptools
cvs checkout ghc hslibs libraries testsuite
testsuite is optional and many other nice things are around.

find . -name configure.ac -print
to find all dirs that need autoreconf (not autoconf anymore)

autoreconf
(cd ghc; autoreconf)
(cd libraries; autoreconf)
./configure
allmost done

cp mk/build.mk.sample mk/build.mk
Better this sample than no mk/build.mk at all.

gmake
Builds a nice stage2 compiler if you have ghc for bootstrap, alex, 
happy, ...,
but otherwise configure would have told you.

Ralf

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-05 Thread Ken Shan
Brandon Michael Moore [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in 
gmane.comp.lang.haskell.cafe:
 There are two extensions here:
 
 More overlapping: [...]
 Backtracking search: [...]
 
 Overloading resolution: [...]

I'm sorry if I am getting ahead of Simon or behind of you, but have you
looked at

Simon L. Peyton Jones, Mark Jones, and Erik Meijer. 1997.  Type classes:
An exploration of the design space.  In Proceedings of the Haskell
workshop, ed. John Launchbury.
http://research.microsoft.com/Users/simonpj/papers/type-class-design-space/

?  There is quite a bit of design discussion there, and I am not sure
how much has been obsoleted by more recent advances.  A primary
consideration seems to be that the compiler should be guaranteed to
terminate (so type checking must be decidable).

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
hqrtzdfg
aooieoia
pnkplptr
ywwywyyw

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-05 Thread Simon Peyton-Jones
| More overlapping:
| Allow any overlapping rules, and apply the most specific rule that
| matches our target. Only complain if there is a pair of matching
| rules neither of which is more specific than the other.
| This follow the spirit of the treatment of duplicate imports...

Happy days.  I've already implemented this change in the HEAD.  If you
can build from source, you can try it.

| Backtracking search:
| If several rules matched your target, and the one you picked didn't
| work, go back and try another.
| 
| This isn't as well through out: you probably want to backtrack through
all
| the matching rules even if some are unordered by being more specific.
It
| would probably be godd enough to respect specificity, and make other
| choices arbitrarilily (line number, filename, etc. maybe Prolog has a
| solution?). This probably isn't too hard if you can just add
| nondeterminism to the monad the code already lives in.

I didn't follow the details of this paragraph.  But it looks feasible.

| Overloading resolution:
| This one is really half-baked, but sometimes it would be nice if there
was
| some way to look at
| class MyNumber a where
|   one::a
| instance MyNumber Int where
|   one = 1
| 
| then see (one+1) and deduce that the 1 must have type Int, rather than
| complaining about being unable to deduce MyNumber a from Num a. This
is
| really nice for some cases, like a lifting class I wrote for an
Unlambda
| interpreter, with instances for LiftsToComb Comb and (LiftsToComb a =
| LiftsToComb (a - Comb)). With some closed world reasoning lift id and
| lift const might give you I and K rather than a type error. Also, for
| this work with modelling inheritance you almost always have to give
type
| signatures on numbers so you find the method that takes an Int, rather
| than not finding anything that takes any a with Num a. This obviously
| breaks down if you have instances for Int and Integer, and I don't yet
| know if it is worth the trouble for the benefits in the cases where it
| would help. Implementation is also a bit tricky. I think it requires
| unifying from both sides when deciding if a rule matches a goal.

I'm much less sure about this stuff.  Mark Shields and I did something
about closed classes in our OO paper
http://research.microsoft.com/~simonpj/Papers/oo-haskell/index.htm, and
Martin Sulzmann and colleagues have done lots of foundational work --
but the dust is still swirling I think.

Simon




___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-04 Thread Brandon Michael Moore
On Tue, 4 Nov 2003, Simon Peyton-Jones wrote:


 | We really should change GHC rather than keep trying to work around
 stuff
 | like this. GHC will be my light reading for winter break.

 Maybe so.  For the benefit of those of us who have not followed the
 details of your work, could you summarise, as precisely as possible,
 just what language extension you propose, and how it would be useful?  A
 kind of free-standing summary, not assuming the reader has already read
 the earlier messages.

 Simon

There are two extensions here:

More overlapping:
Allow any overlapping rules, and apply the most specific rule that
matches our target. Only complain if there is a pair of matching
rules neither of which is more specific than the other.

This follow the spirit of the treatment of duplicate imports, and
lets you do more interesting computations with type classes.
For example, the sort of type class hack Oleg and I have been writing much
easier. You use nested tuples to hold a list of values your search
is working over, have a rule that expands the head to a list of
subgoals, a rule that flattens lists with a head of that form,
and an axiom that stops the search if the head has a different
form, without needing the stop form to unify with a pair.

This extension would accept the code I just posted, and seems pretty
conservative.

Backtracking search:
If several rules matched your target, and the one you picked didn't
work, go back and try another.

This isn't as well through out: you probably want to backtrack through all
the matching rules even if some are unordered by being more specific. It
would probably be godd enough to respect specificity, and make other
choices arbitrarilily (line number, filename, etc. maybe Prolog has a
solution?). This probably isn't too hard if you can just add
nondeterminism to the monad the code already lives in.

This would give you OR. The example Integral a = MyClass a,
Fractional a = MyClass a would work just fine and give you a class that
is the union of integral and fractional. This class hierarchy search
could be done by a SubClass class that had an instance linking a class
to each of it's different parents, then the search just needs to backtrack
on which parent to look at:

class SubClass super sub

instance SubClass A C
instance SubClass B C

class HasFoo cls
  foo :: cls - Int
instance (SubClass super sub,HasFoo super) = HasFoo sub
instance HasFoo B

now look for an instance of HasFoo D
  uses first rule for HasFoo,.
  Needs an instance SubClass x D. Tries A, but can't derive HasFoo A.
  GHC backtracks to trying B as the parent, where it can
  use the second instance for HasFoo and finish the derivation.

Overloading resolution:
This one is really half-baked, but sometimes it would be nice if there was
some way to look at

class MyNumber a where
  one::a
instance MyNumber Int where
  one = 1

then see (one+1) and deduce that the 1 must have type Int, rather than
complaining about being unable to deduce MyNumber a from Num a. This is
really nice for some cases, like a lifting class I wrote for an Unlambda
interpreter, with instances for LiftsToComb Comb and (LiftsToComb a =
LiftsToComb (a - Comb)). With some closed world reasoning lift id and
lift const might give you I and K rather than a type error. Also, for
this work with modelling inheritance you almost always have to give type
signatures on numbers so you find the method that takes an Int, rather
than not finding anything that takes any a with Num a. This obviously
breaks down if you have instances for Int and Integer, and I don't yet
know if it is worth the trouble for the benefits in the cases where it
would help. Implementation is also a bit tricky. I think it requires
unifying from both sides when deciding if a rule matches a goal.

Improvements and better suggestions welcome. I'm only particularly
attached to the first idea.

Brandon

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-04 Thread oleg

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 

Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-03 Thread Brandon Michael Moore
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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Type tree traversals [Re: Modeling multiple inheritance]

2003-10-04 Thread oleg

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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Modeling multiple inheritance

2003-09-27 Thread Brandon Michael Moore
On Fri, 26 Sep 2003 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Modeling multiple inheritance

2003-09-26 Thread Brandon Michael Moore
On Thu, 25 Sep 2003 [EMAIL PROTECTED] 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




Re: Modeling multiple inheritance

2003-09-26 Thread oleg

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/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Modeling multiple inheritance

2003-09-25 Thread Simon Peyton-Jones
When Mark Shields and I tackled this problem we came up with
Object-Oriented Style Overloading for Haskell

http://research.microsoft.com/~simonpj/Papers/oo-haskell/index.htm

It describes an (unimplemented) extension to Haskell, rather than
modelling it in Haskell itself, but you may find it interesting none the
less. 

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Brandon Michael Moore
| Sent: 24 September 2003 22:22
| To: [EMAIL PROTECTED]
| Subject: Modeling multiple inheritance
| 
| 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
| 
| ___
| Haskell-Cafe mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Modeling multiple inheritance

2003-09-24 Thread Brandon Michael Moore
On Thu, 25 Sep 2003 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe