summaryrefslogtreecommitdiff
path: root/stdlib/map.mli
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 15:42:07 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 15:42:07 +0000
commit69d5ded20407463aaf991c3c7be7df585ffe4097 (patch)
tree36b3728857e6e7a5f4a2782427bce3b2dbda0907 /stdlib/map.mli
parent6e02025f61ffe36683eef2ee614f30676a157d70 (diff)
downloadocaml-69d5ded20407463aaf991c3c7be7df585ffe4097.tar.gz
correction comments
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4096 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/map.mli')
-rw-r--r--stdlib/map.mli59
1 files changed, 49 insertions, 10 deletions
diff --git a/stdlib/map.mli b/stdlib/map.mli
index 272894c91d..e703681cdf 100644
--- a/stdlib/map.mli
+++ b/stdlib/map.mli
@@ -37,16 +37,55 @@ module type OrderedType = sig type t val compare : t -> t -> int end
module type S =
sig
type key
- type +'a t
- val empty : 'a t
- val add : key -> 'a -> 'a t -> 'a t
- val find : key -> 'a t -> 'a
- val remove : key -> 'a t -> 'a t
- val mem : key -> 'a t -> bool
- val iter : (key -> 'a -> unit) -> 'a t -> unit
- val map : ('a -> 'b) -> 'a t -> 'b t
- val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
- val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
+ (** The type of the map keys. *)
+
+ type (+'a) t
+ (** The type of maps from type [key] to type ['a]. *)
+
+ val empty: 'a t
+ (** The empty map. *)
+
+ val add: key -> 'a -> 'a t -> 'a 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: key -> 'a t -> 'a
+ (** [find x m] returns the current binding of [x] in [m],
+ or raises [Not_found] if no such binding exists. *)
+
+ val remove: key -> 'a t -> 'a 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: key -> 'a t -> bool
+ (** [mem x m] returns [true] if [m] contains a binding for [x],
+ and [false] otherwise. *)
+
+ val iter: (key -> 'a -> unit) -> 'a 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: ('a -> 'b) -> 'a t -> 'b 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: (key -> 'a -> 'b) -> 'a t -> 'b t
+ (** Same as {!Map.S.map}, but the function receives as arguments both the
+ key and the associated value for each binding of the map. *)
+
+ val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
+ (** [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. *)
end
module Make (Ord : OrderedType) : S with type key = Ord.t