/usr/lib/ocaml/set.mli is in ocaml-nox 4.05.0-10ubuntu1.
This file is owned by root:root, with mode 0o644.
The actual contents of the file can be viewed below.
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 | (**************************************************************************)
(* *)
(* 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 Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the 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 map: (elt -> elt) -> t -> t
(** [map f s] is the set whose elements are [f a0],[f a1]... [f
aN], where [a0],[a1]...[aN] are the elements of [s].
The elements are passed to [f] in increasing order
with respect to the ordering over the type of the elements.
If no element of [s] is changed by [f], [s] is returned
unchanged. (If each output of [f] is physically equal to its
input, the returned set is physically equal to [s].)
@since 4.04.0 *)
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 min_elt_opt: t -> elt option
(** Return the smallest element of the given set
(with respect to the [Ord.compare] ordering), or [None]
if the set is empty.
@since 4.05
*)
val max_elt: t -> elt
(** Same as {!Set.S.min_elt}, but returns the largest element of the
given set. *)
val max_elt_opt: t -> elt option
(** Same as {!Set.S.min_elt_opt}, but returns the largest element of the
given set.
@since 4.05
*)
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 choose_opt: t -> elt option
(** Return one element of the given set, or [None] if
the set is empty. Which element is chosen is unspecified,
but equal elements will be chosen for equal sets.
@since 4.05
*)
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 find_opt: elt -> t -> elt option
(** [find_opt x s] returns the element of [s] equal to [x] (according
to [Ord.compare]), or [None] if no such element
exists.
@since 4.05 *)
val find_first: (elt -> bool) -> t -> elt
(** [find_first f s], where [f] is a monotonically increasing function,
returns the lowest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
For example, [find_first (fun e -> Ord.compare e x >= 0) s] will return
the first element [e] of [s] where [Ord.compare e x >= 0] (intuitively:
[e >= x]), or raise [Not_found] if [x] is greater than any element of
[s].
@since 4.05
*)
val find_first_opt: (elt -> bool) -> t -> elt option
(** [find_first_opt f s], where [f] is a monotonically increasing function,
returns an option containing the lowest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05
*)
val find_last: (elt -> bool) -> t -> elt
(** [find_last f s], where [f] is a monotonically decreasing function,
returns the highest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
@since 4.05
*)
val find_last_opt: (elt -> bool) -> t -> elt option
(** [find_last_opt f s], where [f] is a monotonically decreasing function,
returns an option containing the highest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05
*)
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. *)
|