From d48c6cfaea74da36e8268888cce3429a883a8395 Mon Sep 17 00:00:00 2001 From: Xavier Leroy Date: Fri, 28 Jul 2000 12:24:25 +0000 Subject: [PATCH] Ajout de Hashtbl.replace. Pas d'allocation dans Hashtbl.find git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3262 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02 --- stdlib/hashtbl.ml | 61 ++++++++++++++++++++++++++++++++++------------ stdlib/hashtbl.mli | 8 ++++++ 2 files changed, 53 insertions(+), 16 deletions(-) diff --git a/stdlib/hashtbl.ml b/stdlib/hashtbl.ml index 9be4a1906..d39fd28a2 100644 --- a/stdlib/hashtbl.ml +++ b/stdlib/hashtbl.ml @@ -79,6 +79,12 @@ let remove h key = let i = (hash key) mod (Array.length h.data) in h.data.(i) <- remove_bucket h.data.(i) +let rec find_rec key = function + Empty -> + raise Not_found + | Cons(k, d, rest) -> + if key = k then d else find_rec key rest + let find h key = match h.data.((hash key) mod (Array.length h.data)) with Empty -> raise Not_found @@ -91,14 +97,7 @@ let find h key = match rest2 with Empty -> raise Not_found | Cons(k3, d3, rest3) -> - if key = k3 then d3 else begin - let rec find = function - Empty -> - raise Not_found - | Cons(k, d, rest) -> - if key = k then d else find rest - in find rest3 - end + if key = k3 then d3 else find_rec key rest3 let find_all h key = let rec find_in_bucket = function @@ -108,6 +107,21 @@ let find_all h key = if k = key then d :: find_in_bucket rest else find_in_bucket rest in find_in_bucket h.data.((hash key) mod (Array.length h.data)) +let replace h key info = + let rec replace_bucket = function + Empty -> + raise Not_found + | Cons(k, i, next) -> + if k = key + then Cons(k, info, next) + else Cons(k, i, replace_bucket next) in + let i = (hash key) mod (Array.length h.data) in + let l = h.data.(i) in + try + h.data.(i) <- replace_bucket l + with Not_found -> + h.data.(i) <- Cons(key, info, l) + let mem h key = let rec mem_in_bucket = function | Empty -> @@ -146,6 +160,7 @@ module type S = val remove: 'a t -> key -> unit val find: 'a t -> key -> 'a val find_all: 'a t -> key -> 'a list + val replace : 'a t -> key -> 'a -> unit val mem : 'a t -> key -> bool val iter: (key -> 'a -> unit) -> 'a t -> unit end @@ -175,6 +190,12 @@ module Make(H: HashedType): (S with type key = H.t) = let i = (H.hash key) mod (Array.length h.data) in h.data.(i) <- remove_bucket h.data.(i) + let rec find_rec key = function + Empty -> + raise Not_found + | Cons(k, d, rest) -> + if H.equal key k then d else find_rec key rest + let find h key = match h.data.((H.hash key) mod (Array.length h.data)) with Empty -> raise Not_found @@ -187,14 +208,7 @@ module Make(H: HashedType): (S with type key = H.t) = match rest2 with Empty -> raise Not_found | Cons(k3, d3, rest3) -> - if H.equal key k3 then d3 else begin - let rec find = function - Empty -> - raise Not_found - | Cons(k, d, rest) -> - if H.equal key k then d else find rest - in find rest3 - end + if H.equal key k3 then d3 else find_rec key rest3 let find_all h key = let rec find_in_bucket = function @@ -206,6 +220,21 @@ module Make(H: HashedType): (S with type key = H.t) = else find_in_bucket rest in find_in_bucket h.data.((H.hash key) mod (Array.length h.data)) + let replace h key info = + let rec replace_bucket = function + Empty -> + raise Not_found + | Cons(k, i, next) -> + if H.equal k key + then Cons(k, info, next) + else Cons(k, i, replace_bucket next) in + let i = (H.hash key) mod (Array.length h.data) in + let l = h.data.(i) in + try + h.data.(i) <- replace_bucket l + with Not_found -> + h.data.(i) <- Cons(key, info, l) + let mem h key = let rec mem_in_bucket = function | Empty -> diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli index 41ab86df8..04bcab320 100644 --- a/stdlib/hashtbl.mli +++ b/stdlib/hashtbl.mli @@ -56,6 +56,13 @@ val remove : ('a, 'b) t -> 'a -> unit restoring the previous binding if it exists. It does nothing if [x] is not bound in [tbl]. *) +val replace : ('a, 'b) t -> key:'a -> data:'b -> unit + (* [Hashtbl.replace tbl x y] replaces the current binding of [x] + in [tbl] by a binding of [x] to [y]. If [x] is unbound in [tbl], + a binding of [x] to [y] is added to [tbl]. + This is functionally equivalent to [Hashtbl.remove tbl x] + followed by [Hashtbl.add tbl x y]. *) + val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit (* [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl]. [f] receives the key as first argument, and the associated value @@ -94,6 +101,7 @@ module type S = val remove: 'a t -> key -> unit val find: 'a t -> key -> 'a val find_all: 'a t -> key -> 'a list + 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 end