Added Hashtbl.mem to test if a given key is bound into the table.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2271 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 1999-02-11 09:46:14 +00:00
parent 926b0d5a15
commit 36dea1c565
2 changed files with 24 additions and 2 deletions

View File

@ -5,7 +5,7 @@
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* en Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
@ -104,6 +104,14 @@ 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_param 10 100 key) mod (Array.length h.data))
let mem h key =
let rec mem_in_bucket = function
| Empty ->
false
| Cons(k, d, rest) ->
k = key || mem_in_bucket rest in
mem_in_bucket h.data.((hash_param 10 100 key) mod (Array.length h.data))
let iter f h =
let rec do_bucket = function
Empty ->
@ -134,6 +142,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 mem : 'a t -> key -> bool
val iter: (key -> 'a -> unit) -> 'a t -> unit
end
@ -193,5 +202,14 @@ 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 mem h key =
let rec mem_in_bucket = function
| Empty ->
false
| Cons(k, d, rest) ->
H.equal k key || mem_in_bucket rest in
mem_in_bucket h.data.((hash_param 10 100 key) mod (Array.length h.data))
let iter = iter
end

View File

@ -5,7 +5,7 @@
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* en Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
@ -47,6 +47,9 @@ val find_all : ('a, 'b) t -> 'a -> 'b list
The current binding is returned first, then the previous
bindings, in reverse order of introduction in the table. *)
val mem : ('a, 'b) t -> 'a -> bool
(* [Hashtbl.mem tbl x] checks if [x] is bound in [tbl]. *)
val remove : ('a, 'b) t -> 'a -> unit
(* [Hashtbl.remove tbl x] removes the current binding of [x] in [tbl],
restoring the previous binding if it exists.
@ -90,6 +93,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 mem: 'a t -> key -> bool
val iter: (key -> 'a -> unit) -> 'a t -> unit
end