summaryrefslogtreecommitdiffstats
path: root/stdlib/set.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/set.ml')
-rw-r--r--stdlib/set.ml5
1 files changed, 5 insertions, 0 deletions
diff --git a/stdlib/set.ml b/stdlib/set.ml
index 84a8a942c..f0434f265 100644
--- a/stdlib/set.ml
+++ b/stdlib/set.ml
@@ -22,6 +22,7 @@ module type S =
val equal: t -> t -> bool
val iter: (elt -> 'a) -> t -> unit
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
+ val cardinal: t -> int
val elements: t -> elt list
val choose: t -> elt
end
@@ -212,6 +213,10 @@ module Make(Ord: OrderedType): (S with elt = Ord.t) =
Empty -> accu
| Node(l, v, r, _) -> fold f l (f v (fold f r accu))
+ let rec cardinal = function
+ Empty -> 0
+ | Node(l, v, r, _) -> cardinal l + 1 + cardinal r
+
let rec elements_aux accu = function
Empty -> accu
| Node(l, v, r, _) -> elements_aux (v :: elements_aux accu r) l