/usr/lib/ocaml/extlib/pMap.mli is in libextlib-ocaml-dev 1.6.1-1.
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 | (*
* PMap - Polymorphic maps
* Copyright (C) 1996-2003 Xavier Leroy, Nicolas Cannasse, Markus Mottl
*
* This library is free software; you can redistribute it and/or
* modify it under the terms of the GNU Lesser General Public
* License as published by the Free Software Foundation; either
* version 2.1 of the License, or (at your option) any later version,
* with the special exception on linking described in file LICENSE.
*
* This library is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public
* License along with this library; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
*)
(** Polymorphic Map.
This is a polymorphic map, similar to standard library [Map] module
but in a defunctorized style.
*)
type ('a, 'b) t
val empty : ('a, 'b) t
(** The empty map, using [compare] as key comparison function. *)
val is_empty : ('a, 'b) t -> bool
(** returns true if the map is empty. *)
val create : ('a -> 'a -> int) -> ('a, 'b) t
(** creates a new empty map, using the provided function for key comparison.*)
val add : 'a -> 'b -> ('a, 'b) t -> ('a, 'b) t
(** [add x y m] returns a map containing the same bindings as
[m], plus a binding of [x] to [y]. If [x] was already bound
in [m], its previous binding disappears. *)
val find : 'a -> ('a, 'b) t -> 'b
(** [find x m] returns the current binding of [x] in [m],
or raises [Not_found] if no such binding exists. *)
val remove : 'a -> ('a, 'b) t -> ('a, 'b) t
(** [remove x m] returns a map containing the same bindings as
[m], except for [x] which is unbound in the returned map. *)
val mem : 'a -> ('a, 'b) t -> bool
(** [mem x m] returns [true] if [m] contains a binding for [x],
and [false] otherwise. *)
val exists : 'a -> ('a, 'b) t -> bool
(** same as [mem]. *)
val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
(** [iter f m] applies [f] to all bindings in map [m].
[f] receives the key as first argument, and the associated value
as second argument. The order in which the bindings are passed to
[f] is unspecified. Only current bindings are presented to [f]:
bindings hidden by more recent bindings are not passed to [f]. *)
val map : ('b -> 'c) -> ('a, 'b) t -> ('a, 'c) t
(** [map f m] returns a map with same domain as [m], where the
associated value [a] of all bindings of [m] has been
replaced by the result of the application of [f] to [a].
The order in which the associated values are passed to [f]
is unspecified. *)
val mapi : ('a -> 'b -> 'c) -> ('a, 'b) t -> ('a, 'c) t
(** Same as [map], but the function receives as arguments both the
key and the associated value for each binding of the map. *)
val fold : ('b -> 'c -> 'c) -> ('a , 'b) t -> 'c -> 'c
(** [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)],
where [k1 ... kN] are the keys of all bindings in [m],
and [d1 ... dN] are the associated data.
The order in which the bindings are presented to [f] is
unspecified. *)
val foldi : ('a -> 'b -> 'c -> 'c) -> ('a , 'b) t -> 'c -> 'c
(** Same as [fold], but the function receives as arguments both the
key and the associated value for each binding of the map. *)
val enum : ('a, 'b) t -> ('a * 'b) Enum.t
(** creates an enumeration for this map. *)
val of_enum : ?cmp:('a -> 'a -> int) -> ('a * 'b) Enum.t -> ('a, 'b) t
(** creates a map from an enumeration, using the specified function
for key comparison or [compare] by default. *)
|