1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Module [Set]: sets over ordered types *)
|
|
|
|
|
|
|
|
(* This module implements the set data structure, given a total ordering
|
|
|
|
function over the set elements. All operations over sets
|
|
|
|
are purely applicative (no side-effects).
|
|
|
|
The implementation uses balanced binary trees, and is therefore
|
|
|
|
reasonably efficient: insertion and membership take time
|
|
|
|
logarithmic in the size of the set, for instance. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
module type OrderedType =
|
|
|
|
sig
|
|
|
|
type t
|
|
|
|
val compare: t -> t -> int
|
|
|
|
end
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The input signature of the functor [Set.Make].
|
|
|
|
[t] is the type of the set elements.
|
|
|
|
[compare] is a total ordering function over the set elements.
|
|
|
|
This is a two-argument function [f] such that
|
|
|
|
[f e1 e2] is zero if the elements [e1] and [e2] are equal,
|
|
|
|
[f e1 e2] is strictly negative if [e1] is smaller than [e2],
|
|
|
|
and [f e1 e2] is strictly positive if [e1] is greater than [e2].
|
|
|
|
Examples: a suitable ordering function for type [int]
|
1995-12-06 07:46:34 -08:00
|
|
|
is [(-)]. You can also use the generic structural comparison
|
1995-08-09 06:15:01 -07:00
|
|
|
function [compare]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
module type S =
|
|
|
|
sig
|
|
|
|
type elt
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The type of the set elements. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
type t
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The type of sets. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val empty: t
|
1995-08-09 06:15:01 -07:00
|
|
|
(* The empty set. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val is_empty: t -> bool
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Test whether a set is empty or not. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val mem: elt -> t -> bool
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [mem x s] tests whether [x] belongs to the set [s]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val add: elt -> t -> t
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [add x s] returns a set containing all elements of [s],
|
|
|
|
plus [x]. If [x] was already in [s], [s] is returned unchanged. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val remove: elt -> t -> t
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [remove x s] returns a set containing all elements of [s],
|
|
|
|
except [x]. If [x] was not in [s], [s] is returned unchanged. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val union: t -> t -> t
|
|
|
|
val inter: t -> t -> t
|
|
|
|
val diff: t -> t -> t
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Union, intersection and set difference. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val compare: t -> t -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Total ordering between sets. Can be used as the ordering function
|
|
|
|
for doing sets of sets. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val equal: t -> t -> bool
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [equal s1 s2] tests whether the sets [s1] and [s2] are
|
|
|
|
equal, that is, contain the same elements. *)
|
1997-05-10 08:38:17 -07:00
|
|
|
val subset: t -> t -> bool
|
|
|
|
(* [subset s1 s2] tests whether the set [s1] is a subset of
|
|
|
|
the set [s2]. *)
|
1997-10-31 04:59:29 -08:00
|
|
|
val iter: (elt -> unit) -> t -> unit
|
|
|
|
(* [iter f s] applies [f] in turn to all elements of [s].
|
|
|
|
The order in which the elements of [s] are presented to [f]
|
|
|
|
is unspecified. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [fold f s a] computes [(f xN ... (f x2 (f x1 a))...)],
|
|
|
|
where [x1 ... xN] are the elements of [s].
|
|
|
|
The order in which elements of [s] are presented to [f] is
|
1997-10-31 04:59:29 -08:00
|
|
|
unspecified. *)
|
1995-06-22 03:11:18 -07:00
|
|
|
val cardinal: t -> int
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the number of elements of a set. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val elements: t -> elt list
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the list of all elements of the given set.
|
1997-10-31 04:59:29 -08:00
|
|
|
The elements appear in the list in some unspecified order. *)
|
1995-05-30 06:33:57 -07:00
|
|
|
val choose: t -> elt
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return one element of the given set, or raise [Not_found] if
|
1997-10-31 04:59:29 -08:00
|
|
|
the set is empty. Which element is chosen is unspecified,
|
1995-08-09 06:15:01 -07:00
|
|
|
but equal elements will be chosen for equal sets. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
|
1995-10-01 06:39:43 -07:00
|
|
|
module Make(Ord: OrderedType): (S with type elt = Ord.t)
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Functor building an implementation of the set structure
|
|
|
|
given a totally ordered type. *)
|