diff options
author | Alain Frisch <alain@frisch.fr> | 2013-01-08 09:01:02 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-01-08 09:01:02 +0000 |
commit | 706f81545001043fc15d7cd5ea2324eab87c548b (patch) | |
tree | 2454b411dddd68b53e5f59552a699ad2d9a6d8d9 | |
parent | 2a7b2fc5f1ae5bf5ab38b96c177d572d8b774dd7 (diff) |
#5864: add a find operation to Set.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13211 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | Changes | 1 | ||||
-rw-r--r-- | ocamlbuild/my_std.ml | 4 | ||||
-rw-r--r-- | ocamlbuild/rule.ml | 2 | ||||
-rw-r--r-- | ocamlbuild/signatures.mli | 2 | ||||
-rw-r--r-- | stdlib/moreLabels.mli | 1 | ||||
-rw-r--r-- | stdlib/set.ml | 7 | ||||
-rw-r--r-- | stdlib/set.mli | 4 |
7 files changed, 17 insertions, 4 deletions
@@ -56,6 +56,7 @@ Feature wishes: - PR#5769: Allow propagation of Sys.big_endian in native code - PR#5771: Add primitives for reading 2, 4, 8 bytes in strings and bigarrays - PR#5774: Add bswap primitives for amd64 and arm +- PR#5864: Add a find operation to Set Tools: - OCamlbuild now features a bin_annot tag to generate .cmt files. diff --git a/ocamlbuild/my_std.ml b/ocamlbuild/my_std.ml index 42fc8c80f..aa25ecb13 100644 --- a/ocamlbuild/my_std.ml +++ b/ocamlbuild/my_std.ml @@ -62,7 +62,7 @@ module Set = struct module type S = sig include Set.S - val find : (elt -> bool) -> t -> elt + val find_elt : (elt -> bool) -> t -> elt val map : (elt -> elt) -> t -> t val of_list : elt list -> t val print : formatter -> t -> unit @@ -71,7 +71,7 @@ module Set = struct module Make (M : OrderedTypePrintable) : S with type elt = M.t = struct include Set.Make(M) exception Found of elt - let find p set = + let find_elt p set = try iter begin fun elt -> if p elt then raise (Found elt) diff --git a/ocamlbuild/rule.ml b/ocamlbuild/rule.ml index ca1a39ddd..d28833d1e 100644 --- a/ocamlbuild/rule.ml +++ b/ocamlbuild/rule.ml @@ -161,7 +161,7 @@ let call builder r = begin match exists2 List.find Resource.Cache.resource_has_changed r.deps with | Some r -> (`cache_miss_changed_dep r, false) | _ -> - begin match exists2 Resources.find Resource.Cache.resource_has_changed dyndeps with + begin match exists2 Resources.find_elt Resource.Cache.resource_has_changed dyndeps with | Some r -> (`cache_miss_changed_dyn_dep r, false) | _ -> begin match cached_digest r with diff --git a/ocamlbuild/signatures.mli b/ocamlbuild/signatures.mli index 7e64d5fd5..f1b038857 100644 --- a/ocamlbuild/signatures.mli +++ b/ocamlbuild/signatures.mli @@ -23,7 +23,7 @@ end module type SET = sig include Set.S - val find : (elt -> bool) -> t -> elt + val find_elt : (elt -> bool) -> t -> elt val map : (elt -> elt) -> t -> t val of_list : elt list -> t val print : Format.formatter -> t -> unit diff --git a/stdlib/moreLabels.mli b/stdlib/moreLabels.mli index 5037ce484..bc15cb4bf 100644 --- a/stdlib/moreLabels.mli +++ b/stdlib/moreLabels.mli @@ -159,6 +159,7 @@ module Set : sig val max_elt : t -> elt val choose : t -> elt val split: elt -> t -> t * bool * t + val find: elt -> t -> elt end module Make : functor (Ord : OrderedType) -> S with type elt = Ord.t end diff --git a/stdlib/set.ml b/stdlib/set.ml index 262629253..4e1f4be8c 100644 --- a/stdlib/set.ml +++ b/stdlib/set.ml @@ -47,6 +47,7 @@ module type S = val max_elt: t -> elt val choose: t -> elt val split: elt -> t -> t * bool * t + val find: elt -> t -> elt end module Make(Ord: OrderedType) = @@ -348,4 +349,10 @@ module Make(Ord: OrderedType) = let choose = min_elt + let rec find x = function + Empty -> raise Not_found + | Node(l, v, r, _) -> + let c = Ord.compare x v in + if c = 0 then v + else find x (if c < 0 then l else r) end diff --git a/stdlib/set.mli b/stdlib/set.mli index 22bb455a8..a7ee6b6cd 100644 --- a/stdlib/set.mli +++ b/stdlib/set.mli @@ -143,6 +143,10 @@ module type S = strictly greater than [x]; [present] is [false] if [s] contains no element equal to [x], or [true] if [s] contains an element equal to [x]. *) + + val find: elt -> t -> elt + (** [find x s] returns the element of [s] equal to [x], or raise + [Not_found] if no such element exists. *) end (** Output signature of the functor {!Set.Make}. *) |