diff options
Diffstat (limited to 'stdlib/set.ml')
-rw-r--r-- | stdlib/set.ml | 7 |
1 files changed, 7 insertions, 0 deletions
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 |