Ajout de Hashtbl.fold (PR#195)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3544 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2001-06-25 08:33:25 +00:00
parent 8c7b0cae7d
commit 371e5b9cde
2 changed files with 26 additions and 1 deletions

View File

@ -141,6 +141,20 @@ let iter f h =
do_bucket d.(i)
done
let fold f h init =
let rec do_bucket b accu =
match b with
Empty ->
accu
| Cons(k, d, rest) ->
do_bucket rest (f k d accu) in
let d = h.data in
let accu = ref init in
for i = 0 to Array.length d - 1 do
accu := do_bucket d.(i) !accu
done;
!accu
(* Functorial interface *)
module type HashedType =
@ -163,6 +177,7 @@ module type S =
val replace : 'a t -> key -> 'a -> unit
val mem : 'a t -> key -> bool
val iter: (key -> 'a -> unit) -> 'a t -> unit
val fold: f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b
end
module Make(H: HashedType): (S with type key = H.t) =
@ -243,6 +258,6 @@ module Make(H: HashedType): (S with type key = H.t) =
H.equal k key || mem_in_bucket rest in
mem_in_bucket h.data.((H.hash key) mod (Array.length h.data))
let iter = iter
let fold = fold
end

View File

@ -70,6 +70,15 @@ val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
[f] is unspecified. Each binding is presented exactly once
to [f]. *)
val fold : f:(key:'a -> data:'b -> 'c -> 'c) -> ('a, 'b) t -> init:'c -> 'c
(* [Hashtbl.fold f tbl init] computes
[(f kN dN ... (f k1 d1 init)...)],
where [k1 ... kN] are the keys of all bindings in [tbl],
and [d1 ... dN] are the associated values.
The order in which the bindings are passed to
[f] is unspecified. Each binding is presented exactly once
to [f]. *)
(*** Functorial interface *)
module type HashedType =
@ -104,6 +113,7 @@ module type S =
val replace : 'a t -> key:key -> data:'a -> unit
val mem: 'a t -> key -> bool
val iter: f:(key:key -> data:'a -> unit) -> 'a t -> unit
val fold: f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b
end
module Make(H: HashedType): (S with type key = H.t)