caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] Is a Cow an Animal?
@ 2002-04-17 23:40 Pixel
  2002-04-18  2:17 ` John Max Skaller
  2002-04-18 18:58 ` james woodyatt
  0 siblings, 2 replies; 12+ messages in thread
From: Pixel @ 2002-04-17 23:40 UTC (permalink / raw)
  To: caml-list

Based on
  http://www.visviva.com/transframe/papers/covar.htm
  http://pauillac.inria.fr/~remy/work/virtual/virtual005.html

I made
  http://merd.net/pixel/language-study/various/is-a-cow-an-animal/
and especially
  http://merd.net/pixel/language-study/various/is-a-cow-an-animal/ocaml2.listing

Please help with some pbs!

- since class equivalence is based on methods and not on class-name, I have to
put dummy methods for ensuring the subtyping relation. 
Is there a nicer/official way?

- I know one can't downcast, but is there no way to have some RTTI? must it be
done by hand? (adding a C++-typeinfo-like method)

FYI the C++ version is:

void is_human_food(const Food &food) {
  if (dynamic_cast<const Carrot*>(&food) == NULL &&
      dynamic_cast<const Meat*>(&food) == NULL)
    mythrow((string) "human doesn't accept food " + typeid(food).name());
}


- I can't manage to create a "human" which would accept any type of "food", it
only accepts exact "food", needing an upcast from "carrot"... to "food".

using a parametric class for human:

class ['a] human energy = object 
  inherit [dead_human, 'a] animal energy (new dead_human) drop
  constraint 'a = #food 
  method foo_human  = () 
end

it seems that 'a is free and gets infered with every use, ie after:

  a_human#eat carrot ;

'a is instanciated to carrot = < eaten : int; foo_carrot : unit >

and refuses

  a_human#eat a_beef ;

is it possible to *set* 'a to #food as wanted?


thanks!

--
Pixel
programming languages addict      http://merd.net/pixel/language-study/
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-17 23:40 [Caml-list] Is a Cow an Animal? Pixel
@ 2002-04-18  2:17 ` John Max Skaller
  2002-04-18 10:19   ` Pixel
  2002-04-18 18:58 ` james woodyatt
  1 sibling, 1 reply; 12+ messages in thread
From: John Max Skaller @ 2002-04-18  2:17 UTC (permalink / raw)
  To: Pixel; +Cc: caml-list

Pixel wrote:

>
>- since class equivalence is based on methods and not on class-name, I have to
>put dummy methods for ensuring the subtyping relation. 
>Is there a nicer/official way?
>
>- I know one can't downcast, but is there no way to have some RTTI? must it be
>done by hand? (adding a C++-typeinfo-like method)
>

You ask in the title "Is a cow an animal?". The answer is no.
Use a variant, give up on classes:

type Animal = Horse of horse | Cow of cow
type horse = Shetland of shetland | Arabian of arabian
...

That is a heterogenous tree structure modelling
the taxonomy. There is no polymorphism here.
There is no subtyping. It is pretty much the exact
opposite: this is unification, the aggregation of
utterly distinct types into a common type.

You can do a bit better sometimes, by recognising
some commonality:

type Animal = {
  animal_common:animal_part;
  animal_variant:animal_split
}

type animal_split = Horse of horse | Cow of cow
...

so that the horse type only contains features unique
to horses. But you should really forget abstraction,
and just build concrete data structures: its really
just a large in memory database, after all:
you really won't gain much hiding the representation here.

>-- 
>John Max Skaller, mailto:skaller@ozemail.com.au
>snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
>voice:61-2-9660-0850
>
>


-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18  2:17 ` John Max Skaller
@ 2002-04-18 10:19   ` Pixel
  2002-04-18 12:09     ` Pixel
  0 siblings, 1 reply; 12+ messages in thread
From: Pixel @ 2002-04-18 10:19 UTC (permalink / raw)
  To: John Max Skaller; +Cc: caml-list

John Max Skaller <skaller@ozemail.com.au> writes:

[...]

> You ask in the title "Is a cow an animal?". The answer is no.

well, it depends how you define your animal. It *can* be as seen at

http://pauillac.inria.fr/~remy/work/virtual/virtual005.html
(written by famous guys :)

> Use a variant, give up on classes:

[...]

> You can do a bit better sometimes, by recognising
> some commonality:
> 
> type Animal = {
>   animal_common:animal_part;
>   animal_variant:animal_split
> }
> 
> type animal_split = Horse of horse | Cow of cow
> ...
> 
> so that the horse type only contains features unique
> to horses. But you should really forget abstraction,
> and just build concrete data structures: its really
> just a large in memory database, after all:
> you really won't gain much hiding the representation here.

well, i don't *want* to give up concrete data structures, I'm just trying to
write the thing. I don't care wether if it's abstract or not. Any working
solution accepted.

http://merd.net/pixel/language-study/various/is-a-cow-an-animal/ocaml.listing
uses a variant for the kind (I just changed it, it was a string)

I've still kept the class to allow sharing of fields.

BUT this solution doesn't allow a stricter checking alike ocaml2.listing or
c++2.listing. The reason is that you can't parameter the class with values
(like (Vegetable Carrot)) only types. 

Maybe this is possible with polymorphic variants (?), I'll try...
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 10:19   ` Pixel
@ 2002-04-18 12:09     ` Pixel
  2002-04-18 12:52       ` Jacques Garrigue
  0 siblings, 1 reply; 12+ messages in thread
From: Pixel @ 2002-04-18 12:09 UTC (permalink / raw)
  To: John Max Skaller; +Cc: caml-list

Pixel <pixel@mandrakesoft.com> writes:

[...]

> http://merd.net/pixel/language-study/various/is-a-cow-an-animal/ocaml.listing
> uses a variant for the kind (I just changed it, it was a string)
> 
> I've still kept the class to allow sharing of fields.
> 
> BUT this solution doesn't allow a stricter checking alike ocaml2.listing or
> c++2.listing. The reason is that you can't parameter the class with values
> (like (Vegetable Carrot)) only types. 
> 
> Maybe this is possible with polymorphic variants (?), I'll try...

done: http://merd.net/pixel/language-study/various/is-a-cow-an-animal/ocaml3.listing

it's quite nice. The advantage over the all-in-class solution is that it's
easier to check the types:

* one pb was:

let is_meat_ = function
  | `Beef | `Dead_rabbit | `Dead_human -> true
  | _ -> false

which type "[> `Beef | `Dead_rabbit | `Dead_human] -> bool" doesn't allow 
  is_meat_ (food : [`Grass])

whereas
  let is_meat e = is_meat_ (e :> food_kind)
  is_meat (food : [`Grass])
is allowed (since is_meat : [< food_kind] -> bool)



* I still can't manage to have:

 new_human : int -> ([ `Dead_human], [< food_kind]) animal
all i got is
 new_human : int -> ([ `Dead_human], _[< food_kind]) animal


Please help!
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 12:09     ` Pixel
@ 2002-04-18 12:52       ` Jacques Garrigue
  2002-04-18 13:03         ` Pixel
  0 siblings, 1 reply; 12+ messages in thread
From: Jacques Garrigue @ 2002-04-18 12:52 UTC (permalink / raw)
  To: pixel; +Cc: caml-list

From: Pixel <pixel@mandrakesoft.com>

> * one pb was:
> 
> let is_meat_ = function
>   | `Beef | `Dead_rabbit | `Dead_human -> true
>   | _ -> false
> 
> which type "[> `Beef | `Dead_rabbit | `Dead_human] -> bool" doesn't allow 
>   is_meat_ (food : [`Grass])

This is to avoid _too_ weak typings, which would allow for bad typos.
The more direct solution is
  let is_meat_ = function
    | #meat_kind -> true
    | #vegetable_kind -> false

> * I still can't manage to have:
> 
>  new_human : int -> ([ `Dead_human], [< food_kind]) animal
> all i got is
>  new_human : int -> ([ `Dead_human], _[< food_kind]) animal

Classical solution is eta-expansion
  let new_human n : ([`Dead_human],  [< food_kind ]) animal =
    new animal `Human  `Dead_human n
should work.

Basically, for closed world problems polymorphic variants work
generally better than object encodings. If you want it open world,
this gets more subtle.

Jacques Garrigue
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 12:52       ` Jacques Garrigue
@ 2002-04-18 13:03         ` Pixel
  0 siblings, 0 replies; 12+ messages in thread
From: Pixel @ 2002-04-18 13:03 UTC (permalink / raw)
  To: Jacques Garrigue; +Cc: caml-list

Jacques Garrigue <garrigue@kurims.kyoto-u.ac.jp> writes:

[...]

> > which type "[> `Beef | `Dead_rabbit | `Dead_human] -> bool" doesn't allow 
> >   is_meat_ (food : [`Grass])
> 
> This is to avoid _too_ weak typings, which would allow for bad typos.
> The more direct solution is
>   let is_meat_ = function
>     | #meat_kind -> true
>     | #vegetable_kind -> false

ok

> > all i got is
> >  new_human : int -> ([ `Dead_human], _[< food_kind]) animal
> 
> Classical solution is eta-expansion
>   let new_human n : ([`Dead_human],  [< food_kind ]) animal =
>     new animal `Human  `Dead_human n
> should work.

/me is bad, i should have thought about this :-(

alas, it doesn't solve the real problem, it just moves it one step later:

# new_human 300;;
- : ([ `Dead_human], _[< food_kind]) animal = <obj>


thanks.
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-17 23:40 [Caml-list] Is a Cow an Animal? Pixel
  2002-04-18  2:17 ` John Max Skaller
@ 2002-04-18 18:58 ` james woodyatt
  2002-04-18 22:44   ` Pixel
  2002-04-19  0:21   ` Remi VANICAT
  1 sibling, 2 replies; 12+ messages in thread
From: james woodyatt @ 2002-04-18 18:58 UTC (permalink / raw)
  To: Pixel; +Cc: caml-list

On Wednesday, April 17, 2002, at 04:40 PM, Pixel wrote:

> Based on
>   http://www.visviva.com/transframe/papers/covar.htm
>   http://pauillac.inria.fr/~remy/work/virtual/virtual005.html
>
> I made
>   http://merd.net/pixel/language-study/various/is-a-cow-an-animal/
> and especially
>   http://merd.net/pixel/language-study/various/is-a-cow-an-
> animal/ocaml2.listing
>
> Please help with some pbs!

Your problem is an extension of the one documented by Didier Remy, and 
it's very similar to one I faced with the Iox library I posted 
recently.  I suspect it's a really, really common problem.

I read the statement on your page, and took a swing at it.  Wasn't too 
difficult.

I borrowed a technique I learned here from Brian Rogoff that uses an 
abstract type with a contravariant type parameter for passing the type 
of energy a food object contains to an animal object that can eat it.  
(I wish I were smart enough to know the name for this technique.)

I also used the functional style because the problem statement had some 
language about ensuring that animals are never slaughtered twice.  You 
really can't do that at compile time in Caml, but you could pretty 
easily modify the code I present below so that it raises Failure if the 
'consume' method is called on the same meat object more than once, or if 
an energy value is fed to more than one animal.

I think the code demonstrates more flexibility as I show it here.

(*======================= pixelworld.mli ======================*)
type -'diet energy

class ['diet] thing:
     int ->
     object
         val energy: 'a energy
         method energy: int
     end

class type ['diet] food =
     object('a)
         inherit ['diet] thing
         method consume: 'diet energy * 'a option
     end

class type ['diet] vegetable = ['diet] food
class type ['diet] meat = ['diet] food

class grass: int -> [[ `E_cow ]] vegetable
class carrot: int -> [[ `E_rabbit | `E_human ]] vegetable
class type beef = [[ `E_human ]] meat
class type coney = [[ `E_human ]] meat
class type longpig = [[ `E_human ]] meat

class ['diet, 'eater] animal:
     int ->
     object('a)
         inherit ['diet] thing

         method feed: 'diet energy -> 'a
         method slaughter: 'eater meat
     end

class cow: int -> [[ `E_cow ], [ `E_human ]] animal
class rabbit: int -> [[ `E_rabbit ], [ `E_human ]] animal
class human: int -> [[ `E_human ], [ `E_human ]] animal

(* end of signature *)

(*======================= pixelworld.ml ======================*)
type 'diet energy = int

class ['diet] thing (e : int) =
     object
         val energy: 'diet energy = e
         method energy: int = energy
     end

class type ['diet] food =
     object('a)
         inherit ['diet] thing
         method consume: 'diet energy * 'a option
     end

class ['diet] vegetable e : ['diet] food =
     object
         inherit ['diet] thing e
         method consume = energy, Some {< >}
     end

class ['diet] meat e : ['diet] food =
     object(_:'a)
         inherit ['diet] thing e
         method consume = energy, (None : 'a option)
     end

class grass = [[ `E_cow ]] vegetable
class carrot = [[ `E_rabbit | `E_human ]] vegetable
class beef = [[ `E_human ]] meat
class coney = [[ `E_human ]] meat
class longpig = [[ `E_human ]] meat

class ['diet, 'eater] animal e =
     object
         inherit ['diet] thing e

         method slaughter = ((new meat energy) : 'eater meat)
         method feed (x : 'diet energy) = {< energy = energy + x >}
     end

class cow = [[ `E_cow ], [ `E_human ]] animal
class rabbit = [[ `E_rabbit ], [ `E_human ]] animal
class human = [[ `E_human ], [ `E_human ]] animal

(* end of module *)

--
j h woodyatt <jhw@wetware.com>

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 18:58 ` james woodyatt
@ 2002-04-18 22:44   ` Pixel
  2002-04-18 22:57     ` james woodyatt
  2002-04-19  0:21   ` Remi VANICAT
  1 sibling, 1 reply; 12+ messages in thread
From: Pixel @ 2002-04-18 22:44 UTC (permalink / raw)
  To: james woodyatt; +Cc: caml-list

james woodyatt <jhw@wetware.com> writes:

[...]

> I borrowed a technique I learned here from Brian Rogoff that uses an abstract
> type with a contravariant type parameter for passing the type of energy a food
> object contains to an animal object that can eat it.  (I wish I were smart
> enough to know the name for this technique.)

well, i don't really understand the """type 'diet energy = int""" stuff.

but neither is my ocaml's:

# let carrot = new carrot 2 ;;
# let cow = new cow 10 ;;
# let _ = cow#feed carrot#energy ;;

# cow#feed;;
- : [ `E_cow] energy -> cow = <fun>
# carrot#energy;;
- : [ `E_rabbit | `E_human] energy = 2
# (carrot#energy : [ `E_cow ] energy);;
- : [ `E_cow] energy = 2

what am i missing?


anyway i do understand the trick:

(* instead of having the animal tied with its accepted_food, *)
(* have the food tied with its eaters *)

which allow both "a_human#eat a_beef" and "a_human#eat carrot" with no
upcasting.


but... trying... thinking... trying... I really can't make this to work :-(



> I also used the functional style because the problem statement had some
> language about ensuring that animals are never slaughtered twice.  You really
> can't do that at compile time in Caml, but you could pretty easily modify the
> code I present below so that it raises Failure if the 'consume' method is
> called on the same meat object more than once, or if an energy value is fed to
> more than one animal.

i've added a functional version (ocaml5) which checks 10/11 should_fail.

the last check (a_beef is already eaten) i can't manage to achieve because i
can't overload "eat" on vegetable vs meat. I could have eat_vegetable and
eat_meat, but that would break the (somewhat implicit) rules of the game.


thanks!
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 22:44   ` Pixel
@ 2002-04-18 22:57     ` james woodyatt
  2002-04-18 23:31       ` Pixel
  0 siblings, 1 reply; 12+ messages in thread
From: james woodyatt @ 2002-04-18 22:57 UTC (permalink / raw)
  To: Pixel; +Cc: The Trade

On Thursday, April 18, 2002, at 03:44 PM, Pixel wrote:
>
> well, i don't really understand the """type 'diet energy = int""" stuff.
> but neither is my ocaml's:
>
> # let carrot = new carrot 2 ;;
> # let cow = new cow 10 ;;
> # let _ = cow#feed carrot#energy ;;
>
> # cow#feed;;
> - : [ `E_cow] energy -> cow = <fun>
> # carrot#energy;;
> - : [ `E_rabbit | `E_human] energy = 2
> # (carrot#energy : [ `E_cow ] energy);;
> - : [ `E_cow] energy = 2
>
> what am i missing?

It looks like the 'a energy type is not actually abstract in your trial 
above.  It has to be abstract or the technique doesn't work.

	# carrot#energy;;
	- : [ `E_rabbit | `E_human] energy = 2

Since the type is concrete, it resolves at compile time into an integer, 
and an integer is an integer is an integer.  Try compiling the .cmo file 
from the .ml and .mli files I posted and using the #load directive from 
the top-level.


--
j h woodyatt <jhw@wetware.com>

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 22:57     ` james woodyatt
@ 2002-04-18 23:31       ` Pixel
  0 siblings, 0 replies; 12+ messages in thread
From: Pixel @ 2002-04-18 23:31 UTC (permalink / raw)
  To: james woodyatt; +Cc: The Trade

james woodyatt <jhw@wetware.com> writes:

> On Thursday, April 18, 2002, at 03:44 PM, Pixel wrote:
> >
> > well, i don't really understand the """type 'diet energy = int""" stuff.

[...]

> It looks like the 'a energy type is not actually abstract in your trial above.
> It has to be abstract or the technique doesn't work.

/me is bad (bis)

and worse, it seems I'm still missing something since subsumption is still not
there.

What I now understand is that it allows to have 
  [ `E_rabbit | `E_human] T.energy
a subtype of 
  [ `E_rabbit ] T.energy
which is needed to have the food tied to its eaters instead instead of
having the animal tied to its accepted_food.


thanks!
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-18 18:58 ` james woodyatt
  2002-04-18 22:44   ` Pixel
@ 2002-04-19  0:21   ` Remi VANICAT
  2002-04-19  0:51     ` james woodyatt
  1 sibling, 1 reply; 12+ messages in thread
From: Remi VANICAT @ 2002-04-19  0:21 UTC (permalink / raw)
  To: caml-list

james woodyatt <jhw@wetware.com> writes:

> I borrowed a technique I learned here from Brian Rogoff that uses an
> abstract type with a contravariant type parameter for passing the type
> of energy a food object contains to an animal object that can eat it.
> (I wish I were smart enough to know the name for this technique.)
> 

the use of an abstract type with a covariant or contravariant type (or
even not variant) parameter, and where the actual implementation of
the type doesn't use this parameter (as in type 'a eater = int) is
often call phantom type.

one can read the very interesting mail about this in the archive of
this mailing list
http://caml.inria.fr/archives/200109/msg00097.html

-- 
Rémi Vanicat
vanicat@labri.u-bordeaux.fr
http://dept-info.labri.u-bordeaux.fr/~vanicat
-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

* Re: [Caml-list] Is a Cow an Animal?
  2002-04-19  0:21   ` Remi VANICAT
@ 2002-04-19  0:51     ` james woodyatt
  0 siblings, 0 replies; 12+ messages in thread
From: james woodyatt @ 2002-04-19  0:51 UTC (permalink / raw)
  To: Remi VANICAT; +Cc: caml-list

On Thursday, April 18, 2002, at 05:21 PM, Remi VANICAT wrote:
> james woodyatt <jhw@wetware.com> writes:
>>
>> I borrowed a technique I learned here from Brian Rogoff that uses an
>> abstract type with a contravariant type parameter for passing the type
>> of energy a food object contains to an animal object that can eat it.
>> (I wish I were smart enough to know the name for this technique.)
>
> the use of an abstract type with a covariant or contravariant type (or
> even not variant) parameter, and where the actual implementation of
> the type doesn't use this parameter (as in type 'a eater = int) is
> often call phantom type.
>
> one can read the very interesting mail about this in the archive of
> this mailing list
> http://caml.inria.fr/archives/200109/msg00097.html

That's precisely where I learned the technique.  It's true I forgot the 
"phantom type" terminology, but the contribution I was trying to make to 
the list is that such types are frequently useful in representing 
complicated associations between related class hierarchies.

I don't think Pixel's exercise is really covered well by the 
"subject-observer" pattern, and I wonder if the pattern I used in my 
solution is one that is already identified by a better name than the 
"association-by-phantom-type" pattern.

Surely somebody has already published a paper on this by now, right?


--
j h woodyatt <jhw@wetware.com>

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


^ permalink raw reply	[flat|nested] 12+ messages in thread

end of thread, other threads:[~2002-04-19  0:51 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2002-04-17 23:40 [Caml-list] Is a Cow an Animal? Pixel
2002-04-18  2:17 ` John Max Skaller
2002-04-18 10:19   ` Pixel
2002-04-18 12:09     ` Pixel
2002-04-18 12:52       ` Jacques Garrigue
2002-04-18 13:03         ` Pixel
2002-04-18 18:58 ` james woodyatt
2002-04-18 22:44   ` Pixel
2002-04-18 22:57     ` james woodyatt
2002-04-18 23:31       ` Pixel
2002-04-19  0:21   ` Remi VANICAT
2002-04-19  0:51     ` james woodyatt

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).