1 (***********************************************************************)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
12 (***********************************************************************)
16 (** Association tables over ordered types.
18 This module implements applicative association tables, also known as
19 finite maps or dictionaries, given a total ordering function
21 All operations over maps are purely applicative (no side-effects).
22 The implementation uses balanced binary trees, and therefore searching
23 and insertion take time logarithmic in the size of the map.
26 module type OrderedType
=
29 (** The type of the map keys. *)
30 val compare
: t
-> t
-> int
31 (** A total ordering function over the keys.
32 This is a two-argument function [f] such that
33 [f e1 e2] is zero if the keys [e1] and [e2] are equal,
34 [f e1 e2] is strictly negative if [e1] is smaller than [e2],
35 and [f e1 e2] is strictly positive if [e1] is greater than [e2].
36 Example: a suitable ordering function is the generic structural
37 comparison function {!Pervasives.compare}. *)
39 (** Input signature of the functor {!Map.Make}. *)
44 (** The type of the map keys. *)
47 (** The type of maps from type [key] to type ['a]. *)
52 val is_empty
: 'a t
-> bool
53 (** Test whether a map is empty or not. *)
55 val add
: key
-> 'a
-> 'a t
-> 'a t
56 (** [add x y m] returns a map containing the same bindings as
57 [m], plus a binding of [x] to [y]. If [x] was already bound
58 in [m], its previous binding disappears. *)
60 val find
: key
-> 'a t
-> 'a
61 (** [find x m] returns the current binding of [x] in [m],
62 or raises [Not_found] if no such binding exists. *)
64 val remove
: key
-> 'a t
-> 'a t
65 (** [remove x m] returns a map containing the same bindings as
66 [m], except for [x] which is unbound in the returned map. *)
68 val mem
: key
-> 'a t
-> bool
69 (** [mem x m] returns [true] if [m] contains a binding for [x],
70 and [false] otherwise. *)
72 val iter
: (key
-> 'a
-> unit) -> 'a t
-> unit
73 (** [iter f m] applies [f] to all bindings in map [m].
74 [f] receives the key as first argument, and the associated value
75 as second argument. The bindings are passed to [f] in increasing
76 order with respect to the ordering over the type of the keys.
77 Only current bindings are presented to [f]:
78 bindings hidden by more recent bindings are not passed to [f]. *)
80 val map
: ('a
-> 'b
) -> 'a t
-> 'b t
81 (** [map f m] returns a map with same domain as [m], where the
82 associated value [a] of all bindings of [m] has been
83 replaced by the result of the application of [f] to [a].
84 The bindings are passed to [f] in increasing order
85 with respect to the ordering over the type of the keys. *)
87 val mapi
: (key
-> 'a
-> 'b
) -> 'a t
-> 'b t
88 (** Same as {!Map.S.map}, but the function receives as arguments both the
89 key and the associated value for each binding of the map. *)
91 val fold
: (key
-> 'a
-> 'b
-> 'b
) -> 'a t
-> 'b
-> 'b
92 (** [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)],
93 where [k1 ... kN] are the keys of all bindings in [m]
94 (in increasing order), and [d1 ... dN] are the associated data. *)
96 val compare
: ('a
-> 'a
-> int) -> 'a t
-> 'a t
-> int
97 (** Total ordering between maps. The first argument is a total ordering
98 used to compare data associated with equal keys in the two maps. *)
100 val equal
: ('a
-> 'a
-> bool) -> 'a t
-> 'a t
-> bool
101 (** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are
102 equal, that is, contain equal keys and associate them with
103 equal data. [cmp] is the equality predicate used to compare
104 the data associated with the keys. *)
107 (** Output signature of the functor {!Map.Make}. *)
109 module Make
(Ord
: OrderedType
) : S
with type key
= Ord.t
110 (** Functor building an implementation of the map structure
111 given a totally ordered type. *)