192 lines
7.2 KiB
OCaml
192 lines
7.2 KiB
OCaml
(***********************************************************************)
|
|
(* *)
|
|
(* OCaml *)
|
|
(* *)
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
(* *)
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
|
(* *)
|
|
(***********************************************************************)
|
|
|
|
(** 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.
|
|
|
|
The [Make] functor constructs implementations for any type, given a
|
|
[compare] function.
|
|
For instance:
|
|
{[
|
|
module IntPairs =
|
|
struct
|
|
type t = int * int
|
|
let compare (x0,y0) (x1,y1) =
|
|
match Pervasives.compare x0 x1 with
|
|
0 -> Pervasives.compare y0 y1
|
|
| c -> c
|
|
end
|
|
|
|
module PairsSet = Set.Make(IntPairs)
|
|
|
|
let m = PairsSet.(empty |> add (2,3) |> add (5,7) |> add (11,13))
|
|
]}
|
|
|
|
This creates a new module [PairsSet], with a new type [PairsSet.t]
|
|
of sets of [int * int].
|
|
*)
|
|
|
|
module type OrderedType =
|
|
sig
|
|
type t
|
|
(** The type of the set elements. *)
|
|
val compare : t -> t -> int
|
|
(** 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].
|
|
Example: a suitable ordering function is the generic structural
|
|
comparison function {!Pervasives.compare}. *)
|
|
end
|
|
(** Input signature of the functor {!Set.Make}. *)
|
|
|
|
module type S =
|
|
sig
|
|
type elt
|
|
(** The type of the set elements. *)
|
|
|
|
type t
|
|
(** The type of sets. *)
|
|
|
|
val empty: t
|
|
(** The empty set. *)
|
|
|
|
val is_empty: t -> bool
|
|
(** Test whether a set is empty or not. *)
|
|
|
|
val mem: elt -> t -> bool
|
|
(** [mem x s] tests whether [x] belongs to the set [s]. *)
|
|
|
|
val add: elt -> t -> t
|
|
(** [add x s] returns a set containing all elements of [s],
|
|
plus [x]. If [x] was already in [s], [s] is returned unchanged
|
|
(the result of the function is then physically equal to [s]).
|
|
@before 4.03 Physical equality was not ensured. *)
|
|
|
|
val singleton: elt -> t
|
|
(** [singleton x] returns the one-element set containing only [x]. *)
|
|
|
|
val remove: elt -> t -> t
|
|
(** [remove x s] returns a set containing all elements of [s],
|
|
except [x]. If [x] was not in [s], [s] is returned unchanged
|
|
(the result of the function is then physically equal to [s]).
|
|
@before 4.03 Physical equality was not ensured. *)
|
|
|
|
val union: t -> t -> t
|
|
(** Set union. *)
|
|
|
|
val inter: t -> t -> t
|
|
(** Set intersection. *)
|
|
|
|
val diff: t -> t -> t
|
|
(** Set difference. *)
|
|
|
|
val compare: t -> t -> int
|
|
(** Total ordering between sets. Can be used as the ordering function
|
|
for doing sets of sets. *)
|
|
|
|
val equal: t -> t -> bool
|
|
(** [equal s1 s2] tests whether the sets [s1] and [s2] are
|
|
equal, that is, contain equal elements. *)
|
|
|
|
val subset: t -> t -> bool
|
|
(** [subset s1 s2] tests whether the set [s1] is a subset of
|
|
the set [s2]. *)
|
|
|
|
val iter: (elt -> unit) -> t -> unit
|
|
(** [iter f s] applies [f] in turn to all elements of [s].
|
|
The elements of [s] are presented to [f] in increasing order
|
|
with respect to the ordering over the type of the elements. *)
|
|
|
|
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
|
|
(** [fold f s a] computes [(f xN ... (f x2 (f x1 a))...)],
|
|
where [x1 ... xN] are the elements of [s], in increasing order. *)
|
|
|
|
val for_all: (elt -> bool) -> t -> bool
|
|
(** [for_all p s] checks if all elements of the set
|
|
satisfy the predicate [p]. *)
|
|
|
|
val exists: (elt -> bool) -> t -> bool
|
|
(** [exists p s] checks if at least one element of
|
|
the set satisfies the predicate [p]. *)
|
|
|
|
val filter: (elt -> bool) -> t -> t
|
|
(** [filter p s] returns the set of all elements in [s]
|
|
that satisfy predicate [p]. If [p] satisfies every element in [s],
|
|
[s] is returned unchanged (the result of the function is then
|
|
physically equal to [s]).
|
|
@before 4.03 Physical equality was not ensured.*)
|
|
|
|
val partition: (elt -> bool) -> t -> t * t
|
|
(** [partition p s] returns a pair of sets [(s1, s2)], where
|
|
[s1] is the set of all the elements of [s] that satisfy the
|
|
predicate [p], and [s2] is the set of all the elements of
|
|
[s] that do not satisfy [p]. *)
|
|
|
|
val cardinal: t -> int
|
|
(** Return the number of elements of a set. *)
|
|
|
|
val elements: t -> elt list
|
|
(** Return the list of all elements of the given set.
|
|
The returned list is sorted in increasing order with respect
|
|
to the ordering [Ord.compare], where [Ord] is the argument
|
|
given to {!Set.Make}. *)
|
|
|
|
val min_elt: t -> elt
|
|
(** Return the smallest element of the given set
|
|
(with respect to the [Ord.compare] ordering), or raise
|
|
[Not_found] if the set is empty. *)
|
|
|
|
val max_elt: t -> elt
|
|
(** Same as {!Set.S.min_elt}, but returns the largest element of the
|
|
given set. *)
|
|
|
|
val choose: t -> elt
|
|
(** Return one element of the given set, or raise [Not_found] if
|
|
the set is empty. Which element is chosen is unspecified,
|
|
but equal elements will be chosen for equal sets. *)
|
|
|
|
val split: elt -> t -> t * bool * t
|
|
(** [split x s] returns a triple [(l, present, r)], where
|
|
[l] is the set of elements of [s] that are
|
|
strictly less than [x];
|
|
[r] is the set of elements of [s] that are
|
|
strictly greater than [x];
|
|
[present] is [false] if [s] contains no element equal to [x],
|
|
or [true] if [s] contains an element equal to [x]. *)
|
|
|
|
val find: elt -> t -> elt
|
|
(** [find x s] returns the element of [s] equal to [x] (according
|
|
to [Ord.compare]), or raise [Not_found] if no such element
|
|
exists.
|
|
@since 4.01.0 *)
|
|
|
|
val of_list: elt list -> t
|
|
(** [of_list l] creates a set from a list of elements.
|
|
This is usually more efficient than folding [add] over the list,
|
|
except perhaps for lists with many duplicated elements.
|
|
@since 4.02.0 *)
|
|
end
|
|
(** Output signature of the functor {!Set.Make}. *)
|
|
|
|
module Make (Ord : OrderedType) : S with type elt = Ord.t
|
|
(** Functor building an implementation of the set structure
|
|
given a totally ordered type. *)
|