~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to stdlib/map.mli

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
(*                                                                     *)
12
12
(***********************************************************************)
13
13
 
14
 
(* $Id: map.mli 9190 2009-03-21 16:35:48Z xleroy $ *)
 
14
(* $Id: map.mli 10632 2010-07-24 14:16:58Z garrigue $ *)
15
15
 
16
16
(** Association tables over ordered types.
17
17
 
52
52
    val is_empty: 'a t -> bool
53
53
    (** Test whether a map is empty or not. *)
54
54
 
 
55
    val mem: key -> 'a t -> bool
 
56
    (** [mem x m] returns [true] if [m] contains a binding for [x],
 
57
       and [false] otherwise. *)
 
58
 
55
59
    val add: key -> 'a -> 'a t -> 'a t
56
60
    (** [add x y m] returns a map containing the same bindings as
57
61
       [m], plus a binding of [x] to [y]. If [x] was already bound
58
62
       in [m], its previous binding disappears. *)
59
63
 
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 singleton: key -> 'a -> 'a t
 
65
    (** [singleton x y] returns the one-element map that contains a binding [y]
 
66
        for [x].
 
67
        @since 3.12.0
 
68
     *)
63
69
 
64
70
    val remove: key -> 'a t -> 'a t
65
71
    (** [remove x m] returns a map containing the same bindings as
66
72
       [m], except for [x] which is unbound in the returned map. *)
67
73
 
68
 
    val mem: key -> 'a t -> bool
69
 
    (** [mem x m] returns [true] if [m] contains a binding for [x],
70
 
       and [false] otherwise. *)
 
74
    val merge:
 
75
         (key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
 
76
    (** [merge f m1 m2] computes a map whose keys is a subset of keys of [m1]
 
77
        and of [m2]. The presence of each such binding, and the corresponding
 
78
        value, is determined with the function [f].
 
79
        @since 3.12.0
 
80
     *)
 
81
 
 
82
    val compare: ('a -> 'a -> int) -> 'a t -> 'a t -> int
 
83
    (** Total ordering between maps.  The first argument is a total ordering
 
84
        used to compare data associated with equal keys in the two maps. *)
 
85
 
 
86
    val equal: ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
 
87
    (** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are
 
88
       equal, that is, contain equal keys and associate them with
 
89
       equal data.  [cmp] is the equality predicate used to compare
 
90
       the data associated with the keys. *)
71
91
 
72
92
    val iter: (key -> 'a -> unit) -> 'a t -> unit
73
93
    (** [iter f m] applies [f] to all bindings in map [m].
75
95
       as second argument.  The bindings are passed to [f] in increasing
76
96
       order with respect to the ordering over the type of the keys. *)
77
97
 
 
98
    val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
 
99
    (** [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)],
 
100
       where [k1 ... kN] are the keys of all bindings in [m]
 
101
       (in increasing order), and [d1 ... dN] are the associated data. *)
 
102
 
 
103
    val for_all: (key -> 'a -> bool) -> 'a t -> bool
 
104
    (** [for_all p m] checks if all the bindings of the map
 
105
        satisfy the predicate [p].
 
106
        @since 3.12.0
 
107
     *)
 
108
 
 
109
    val exists: (key -> 'a -> bool) -> 'a t -> bool
 
110
    (** [exists p m] checks if at least one binding of the map
 
111
        satisfy the predicate [p].
 
112
        @since 3.12.0
 
113
     *)
 
114
 
 
115
    val filter: (key -> 'a -> bool) -> 'a t -> 'a t
 
116
    (** [filter p m] returns the map with all the bindings in [m]
 
117
        that satisfy predicate [p].
 
118
        @since 3.12.0
 
119
     *)
 
120
 
 
121
    val partition: (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
 
122
    (** [partition p m] returns a pair of maps [(m1, m2)], where
 
123
        [m1] contains all the bindings of [s] that satisfy the
 
124
        predicate [p], and [m2] is the map with all the bindings of
 
125
        [s] that do not satisfy [p].
 
126
        @since 3.12.0
 
127
     *)
 
128
 
 
129
    val cardinal: 'a t -> int
 
130
    (** Return the number of bindings of a map.
 
131
        @since 3.12.0
 
132
     *)
 
133
 
 
134
    val bindings: 'a t -> (key * 'a) list
 
135
    (** Return the list of all bindings of the given map.
 
136
       The returned list is sorted in increasing order with respect
 
137
       to the ordering [Ord.compare], where [Ord] is the argument
 
138
       given to {!Map.Make}.
 
139
        @since 3.12.0
 
140
     *)
 
141
 
 
142
    val min_binding: 'a t -> (key * 'a)
 
143
    (** Return the smallest binding of the given map
 
144
       (with respect to the [Ord.compare] ordering), or raise
 
145
       [Not_found] if the map is empty.
 
146
        @since 3.12.0
 
147
     *)
 
148
 
 
149
    val max_binding: 'a t -> (key * 'a)
 
150
    (** Same as {!Map.S.min_binding}, but returns the largest binding
 
151
        of the given map.
 
152
        @since 3.12.0
 
153
     *)
 
154
 
 
155
    val choose: 'a t -> (key * 'a)
 
156
    (** Return one binding of the given map, or raise [Not_found] if
 
157
       the map is empty. Which binding is chosen is unspecified,
 
158
       but equal bindings will be chosen for equal maps.
 
159
        @since 3.12.0
 
160
     *)
 
161
 
 
162
    val split: key -> 'a t -> 'a t * 'a option * 'a t
 
163
    (** [split x m] returns a triple [(l, data, r)], where
 
164
          [l] is the map with all the bindings of [m] whose key
 
165
        is strictly less than [x];
 
166
          [r] is the map with all the bindings of [m] whose key
 
167
        is strictly greater than [x];
 
168
          [data] is [None] if [m] contains no binding for [x],
 
169
          or [Some v] if [m] binds [v] to [x].
 
170
        @since 3.12.0
 
171
     *)
 
172
 
 
173
    val find: key -> 'a t -> 'a
 
174
    (** [find x m] returns the current binding of [x] in [m],
 
175
       or raises [Not_found] if no such binding exists. *)
 
176
 
78
177
    val map: ('a -> 'b) -> 'a t -> 'b t
79
178
    (** [map f m] returns a map with same domain as [m], where the
80
179
       associated value [a] of all bindings of [m] has been
86
185
    (** Same as {!Map.S.map}, but the function receives as arguments both the
87
186
       key and the associated value for each binding of the map. *)
88
187
 
89
 
    val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
90
 
    (** [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)],
91
 
       where [k1 ... kN] are the keys of all bindings in [m]
92
 
       (in increasing order), and [d1 ... dN] are the associated data. *)
93
 
 
94
 
    val compare: ('a -> 'a -> int) -> 'a t -> 'a t -> int
95
 
    (** Total ordering between maps.  The first argument is a total ordering
96
 
        used to compare data associated with equal keys in the two maps. *)
97
 
 
98
 
    val equal: ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
99
 
    (** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are
100
 
       equal, that is, contain equal keys and associate them with
101
 
       equal data.  [cmp] is the equality predicate used to compare
102
 
       the data associated with the keys. *)
103
188
 
104
189
  end
105
190
(** Output signature of the functor {!Map.Make}. *)