caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Re: Caml-list] Sets and home-made ordered types
       [not found] <20090917030607.927BCBCA9@yquem.inria.fr>
@ 2009-09-17  6:21 ` CUOQ Pascal
  2009-09-17  8:45   ` [Caml-list] " Matthias Puech
  0 siblings, 1 reply; 7+ messages in thread
From: CUOQ Pascal @ 2009-09-17  6:21 UTC (permalink / raw)
  To: caml-list

[-- Attachment #1: Type: text/plain, Size: 1091 bytes --]


David Allsopp wrote :
> Is it not possible to model your requirement using Map.Make instead - where
> the keys represent the equivalence classes and the values whatever data
> you're associating with them? 

Matthias Puech wrote:
>Yes, that's exactly the workaround I ended up using, although I'm not
>very happy with it because, among other things, these keys/class
>disciminant get duplicated (once inside the key, once inside the
>element). I'm getting more concrete below.

Since you already have the "compare" function between objects of
type t, why don't you make your map associate values of type t to
identical values of type t instead of trying to have different type
for keys and elements?

You can even do it generically, and obtain with little effort an
implementation of sets that supports find.

module Set_With_Find(X:Set.OrderedType) = 
struct
      module M = Map.Make(X)
      type t = X.t M.t (* with invariant that value v is always associated to v *)
      let find = M.find
      let add v s = M.add v v s
      .......
end

Pascal




[-- Attachment #2: winmail.dat --]
[-- Type: application/ms-tnef, Size: 3196 bytes --]

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

* Re: [Caml-list] Sets and home-made ordered types
  2009-09-17  6:21 ` Caml-list] Sets and home-made ordered types CUOQ Pascal
@ 2009-09-17  8:45   ` Matthias Puech
  2009-09-17  9:07     ` CUOQ Pascal
  0 siblings, 1 reply; 7+ messages in thread
From: Matthias Puech @ 2009-09-17  8:45 UTC (permalink / raw)
  To: CUOQ Pascal; +Cc: caml-list

Hello and thanks to all for your answers,

If I understand correctly, you're all (David, Elnatan, Vincent, 
Tiphaine, Pascal) suggesting more or less the same solution (the one 
below). Do you have an idea of its memory overhead compared to just 
using Sets? I guess the value is not copied twice but shared between 
keys and elements right? So what, one pointer more for each association 
in the Map? That would be rather acceptable (but still not ideal, sorry 
I'm very demanding).

Thanks again,

    -- Matthias

CUOQ Pascal a écrit :
> Since you already have the "compare" function between objects of
> type t, why don't you make your map associate values of type t to
> identical values of type t instead of trying to have different type
> for keys and elements?
>
> You can even do it generically, and obtain with little effort an
> implementation of sets that supports find.
>
> module Set_With_Find(X:Set.OrderedType) = 
> struct
>       module M = Map.Make(X)
>       type t = X.t M.t (* with invariant that value v is always associated to v *)
>       let find = M.find
>       let add v s = M.add v v s
>       .......
> end
>
> Pascal
>
>
>
>   
> ------------------------------------------------------------------------
>
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>   


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

* Re: Sets and home-made ordered types
  2009-09-17  8:45   ` [Caml-list] " Matthias Puech
@ 2009-09-17  9:07     ` CUOQ Pascal
  0 siblings, 0 replies; 7+ messages in thread
From: CUOQ Pascal @ 2009-09-17  9:07 UTC (permalink / raw)
  To: Matthias Puech; +Cc: caml-list

> So what, one pointer more for each association 
> in the Map? That would be rather acceptable (but still not ideal, sorry 
> I'm very demanding).

You were already paying the price of "one pointer more"
many times over and were not even thinking about it. One
more will not make any difference.

You have to realize that each node already carries a height,
two pointers to subtrees, and take into account the one-word
overhead for the block header. We're not doubling the size of
each tree node here, we're increasing it from 5 to 6 words.

Pascal
PS: You make up for the overhead by having dynamic structures
that are just the right size, and by taking advantage of sharing,
of course.


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

* Re: [Caml-list] Sets and home-made ordered types
  2009-09-16 21:38   ` [Caml-list] " Matthias Puech
  2009-09-17  7:31     ` Vincent Aravantinos
  2009-09-17  8:39     ` David Allsopp
@ 2009-09-23 10:46     ` Goswin von Brederlow
  2 siblings, 0 replies; 7+ messages in thread
From: Goswin von Brederlow @ 2009-09-23 10:46 UTC (permalink / raw)
  To: Matthias Puech; +Cc: caml-list

Matthias Puech <puech@cs.unibo.it> writes:

> David Allsopp a écrit :
>> Is it not possible to model your requirement using Map.Make instead - where
>> the keys represent the equivalence classes and the values whatever data
>> you're associating with them?
>
> Yes, that's exactly the workaround I ended up using, although I'm not
> very happy with it because, among other things, these keys/class
> disciminant get duplicated (once inside the key, once inside the
> element). I'm getting more concrete below.

If your key is part of the value then you could use the value itself
as key. You still get a key and a value but they would point to the
same object in memory.

>> In terms of a strictly pure implementation of a functional Set, it would be
>> odd to have a "find" function - you'll also get some interesting undefined
>> behaviour with these sets if you try to operations like union and
>> intersection but I guess you're already happy with that!
>
> It seems to me rather natural to have it: otherwise, what's the point of
> being able to provide your own compare, beside just checking for
> membership of the class? The implementation of the function is
> straightforward: just copy mem and  make it return the element in case
> of success:
>
> let rec find x = function
>     Empty -> raise Not_found
>   | Node(l, v, r, _) ->
>       let c = Ord.compare x v in
>       if c = 0 then v else
>         find x (if c < 0 then l else r)
>
> For union and inter, I don't see how their behavior would be undefined,
> since neither the datastructure nor the functions are changed.
>
>
> Here is what I want to do: Given a purely first-order datastructure,
> let's say:
> type t = F of t | G of t * t | A | B
> I want to index values of type t according to their first constructor.
> So in my set structure, there will be at most one term starting with
> each constructor, and:
> find (F(A)) (add (F(B)) empty) will return F(B)
>
> With a Set.find, it's easy:
>
> let compare x y = match x,y with
> | (F,F | G,G | A,A | B,B) -> 0
> | _ -> Pervasives.compare x y
>
> module S = Set.Make ...
>
> With the Map solution, i'm obliged to define:
>
> type cstr = F' | G' | A' | B'
> let cstr_of x = F _ -> F' | G _ -> G' etc.
>
> and then make a Map : cstr |--> t, which duplicates the occurrence of
> the constructor (F' in the key, F in the element). Besides, I'm
> responsible for making sure that the pair e.g. (G', F(A)) is not added.

Don't define a cstr but use the t as key and value. You still need to
make sure (A, B) isn't added but you can trivialy wrap the Map module
with functions like

let add m x = Map.add m x x

that hide the duplication of key and value.

The problem I see with your approach though is that you can't

find m (F)

but must use

find m (F(A))

You need a dummy value for F to create a F key.


Idealy I think type prefixes could solve your problem. But ocaml
doesn't have them.

MfG
        Goswin


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

* RE: [Caml-list] Sets and home-made ordered types
  2009-09-16 21:38   ` [Caml-list] " Matthias Puech
  2009-09-17  7:31     ` Vincent Aravantinos
@ 2009-09-17  8:39     ` David Allsopp
  2009-09-23 10:46     ` Goswin von Brederlow
  2 siblings, 0 replies; 7+ messages in thread
From: David Allsopp @ 2009-09-17  8:39 UTC (permalink / raw)
  To: 'Matthias Puech', caml-list

Matthias Puech wrote:
> David Allsopp a écrit :
> > Is it not possible to model your requirement using Map.Make instead -
> > where the keys represent the equivalence classes and the values whatever
> > data you're associating with them?
> 
> Yes, that's exactly the workaround I ended up using, although I'm not
> very happy with it because, among other things, these keys/class
> disciminant get duplicated (once inside the key, once inside the
> element). I'm getting more concrete below.

While I agree that the duplication is unfortunate, it is only one word (the
number needed in each instance to store the Constructor value for the key -
you get the Constructor "for free" with a tuple as it's "stored" in the tag
of the block allocated to hold the tuple.)

> > In terms of a strictly pure implementation of a functional Set, it
> > would be odd to have a "find" function - you'll also get some
interesting
> > undefined behaviour with these sets if you try to operations like union
and
> > intersection but I guess you're already happy with that!

<snip - see other posts>

> For union and inter, I don't see how their behavior would be undefined,
> since neither the datastructure nor the functions are changed.

The element put into the sets on intersection and union is undefined. Say
you have the trivial case with just one equivalence class 

type u = A of int
module MySet = Set.Make(struct type t = u let compare x y = 0 end)

So your sets will all be singletons. What is the result of:

MySet.inter (MySet.singleton (A 1)) (MySet.singleton (A 2))

In 3.11.1, it's the singleton set containing [A 2] but the definition
intersection reasonably allows for it to be [A 1] instead. However, this of
itself isn't an argument against having [find] - it's just that what you're
doing already isn't really a set.

<snip>

> Besides, I'm responsible for making sure that the pair e.g. (G', F(A)) is
not added.

Jacques Garrigue has a syntax extension (PolyMap, I think is its name) which
may help you here - it allows you to enforce this invariant automatically
(and provides neater syntax for it). But I agree that for your case adding a
"find" method to a custom (i.e. copied) version of Set is probably the way
forward - I'm just not sure that you'll convince the guys at Inria to add
the method to the standard library's version of Set.Make!


David


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

* Re: [Caml-list] Sets and home-made ordered types
  2009-09-16 21:38   ` [Caml-list] " Matthias Puech
@ 2009-09-17  7:31     ` Vincent Aravantinos
  2009-09-17  8:39     ` David Allsopp
  2009-09-23 10:46     ` Goswin von Brederlow
  2 siblings, 0 replies; 7+ messages in thread
From: Vincent Aravantinos @ 2009-09-17  7:31 UTC (permalink / raw)
  To: Matthias Puech; +Cc: caml-list

[-- Attachment #1: Type: text/plain, Size: 2833 bytes --]


Le 16 sept. 09 à 23:38, Matthias Puech a écrit :

>> In terms of a strictly pure implementation of a functional Set, it  
>> would be
>> odd to have a "find" function - you'll also get some interesting  
>> undefined
>> behaviour with these sets if you try to operations like union and
>> intersection but I guess you're already happy with that!
>
> It seems to me rather natural to have it: otherwise, what's the  
> point of
> being able to provide your own compare, beside just checking for
> membership of the class?

I think that the ability to define your own 'compare' function in the  
original
Set module is more there to deal with different *orders* rather than  
different
equalities.

> type t = F of t | G of t * t | A | B
> I want to index values of type t according to their first constructor.
> So in my set structure, there will be at most one term starting with
> each constructor, and:
> find (F(A)) (add (F(B)) empty) will return F(B)
>
> With a Set.find, it's easy:
>
> let compare x y = match x,y with
> | (F,F | G,G | A,A | B,B) -> 0
> | _ -> Pervasives.compare x y
>
> module S = Set.Make ...
>
> With the Map solution, i'm obliged to define:
>
> type cstr = F' | G' | A' | B'
> let cstr_of x = F _ -> F' | G _ -> G' etc.
>
> and then make a Map : cstr |--> t, which duplicates the occurrence of
> the constructor (F' in the key, F in the element). Besides, I'm
> responsible for making sure that the pair e.g. (G', F(A)) is not  
> added.

But maybe that's not so much of a duplicate that you think.
Actually cstr is the type of your class equivalence on type t.
It happens that you can have a representative for each class
equivalence, which you store in your map, but that's not the class
equivalence itself.

What I mean is that if you see this through this particular
interpretation, it's rather natural to have two types for two different
kinds of objects. I think furthermore that this is easier to reason
about. For instance the 'compare' function you define is actually not
meant to compare objects of type t but their equivalence class
representatives. Defining a good compare when reasoning about type t
may be hard while when you are aware that you actually want a compare
between class representatives this can turn out to be much easier
(I ran recently in this kind of problem and this was definitely the
case). Actually that's just one of the usual advantages of using
distinct types to represent distinct notions. But your problem being
trivially solved by your extension of Set with a 'find' function I
understand that you would prefer this solution.

Cheers,
--
Vincent Aravantinos
PhD Student - LIG - CAPP Team
Grenoble, France
+33.6.11.23.34.72
vincent.aravantinos@imag.fr
http://membres-lig.imag.fr/aravantinos/


[-- Attachment #2: Type: text/html, Size: 6457 bytes --]

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

* Re: [Caml-list] Sets and home-made ordered types
       [not found] ` <002e01ca36fd$37656c60$a6304520$@metastack.com>
@ 2009-09-16 21:38   ` Matthias Puech
  2009-09-17  7:31     ` Vincent Aravantinos
                       ` (2 more replies)
  0 siblings, 3 replies; 7+ messages in thread
From: Matthias Puech @ 2009-09-16 21:38 UTC (permalink / raw)
  To: caml-list

David Allsopp a écrit :
> Is it not possible to model your requirement using Map.Make instead - where
> the keys represent the equivalence classes and the values whatever data
> you're associating with them? 

Yes, that's exactly the workaround I ended up using, although I'm not
very happy with it because, among other things, these keys/class
disciminant get duplicated (once inside the key, once inside the
element). I'm getting more concrete below.

> In terms of a strictly pure implementation of a functional Set, it would be
> odd to have a "find" function - you'll also get some interesting undefined
> behaviour with these sets if you try to operations like union and
> intersection but I guess you're already happy with that! 

It seems to me rather natural to have it: otherwise, what's the point of
being able to provide your own compare, beside just checking for
membership of the class? The implementation of the function is
straightforward: just copy mem and  make it return the element in case
of success:

let rec find x = function
     Empty -> raise Not_found
   | Node(l, v, r, _) ->
       let c = Ord.compare x v in
       if c = 0 then v else
         find x (if c < 0 then l else r)

For union and inter, I don't see how their behavior would be undefined,
since neither the datastructure nor the functions are changed.


Here is what I want to do: Given a purely first-order datastructure,
let's say:
type t = F of t | G of t * t | A | B
I want to index values of type t according to their first constructor.
So in my set structure, there will be at most one term starting with
each constructor, and:
find (F(A)) (add (F(B)) empty) will return F(B)

With a Set.find, it's easy:

let compare x y = match x,y with
| (F,F | G,G | A,A | B,B) -> 0
| _ -> Pervasives.compare x y

module S = Set.Make ...

With the Map solution, i'm obliged to define:

type cstr = F' | G' | A' | B'
let cstr_of x = F _ -> F' | G _ -> G' etc.

and then make a Map : cstr |--> t, which duplicates the occurrence of
the constructor (F' in the key, F in the element). Besides, I'm
responsible for making sure that the pair e.g. (G', F(A)) is not added.

Thanks for your answer anyway!

	-- Matthias



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

end of thread, other threads:[~2009-09-23 10:46 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
     [not found] <20090917030607.927BCBCA9@yquem.inria.fr>
2009-09-17  6:21 ` Caml-list] Sets and home-made ordered types CUOQ Pascal
2009-09-17  8:45   ` [Caml-list] " Matthias Puech
2009-09-17  9:07     ` CUOQ Pascal
2009-09-16 16:40 Matthias Puech
     [not found] ` <002e01ca36fd$37656c60$a6304520$@metastack.com>
2009-09-16 21:38   ` [Caml-list] " Matthias Puech
2009-09-17  7:31     ` Vincent Aravantinos
2009-09-17  8:39     ` David Allsopp
2009-09-23 10:46     ` Goswin von Brederlow

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).