summaryrefslogtreecommitdiffstats
path: root/stdlib/map.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/map.ml')
-rw-r--r--stdlib/map.ml20
1 files changed, 20 insertions, 0 deletions
diff --git a/stdlib/map.ml b/stdlib/map.ml
index 1e7338bf2..578fac6f0 100644
--- a/stdlib/map.ml
+++ b/stdlib/map.ml
@@ -24,6 +24,7 @@ module type S =
val empty: 'a t
val add: key -> 'a -> 'a t -> 'a t
val find: key -> 'a t -> 'a
+ val remove: key -> 'a t -> 'a t
val iter: (key -> 'a -> 'b) -> 'a t -> unit
val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
end
@@ -96,6 +97,25 @@ module Make(Ord: OrderedType) = struct
if c = 0 then d
else find x (if c < 0 then l else r)
+ let rec merge t1 t2 =
+ match (t1, t2) with
+ (Empty, t) -> t
+ | (t, Empty) -> t
+ | (Node(l1, v1, d1, r1, h1), Node(l2, v2, d2, r2, h2)) ->
+ bal l1 v1 d1 (bal (merge r1 l2) v2 d2 r2)
+
+ let rec remove x = function
+ Empty ->
+ Empty
+ | Node(l, v, d, r, h) as t ->
+ let c = Ord.compare x v in
+ if c = 0 then
+ merge l r
+ else if c < 0 then
+ bal (remove x l) v d r
+ else
+ bal l v d (remove x r)
+
let rec iter f = function
Empty -> ()
| Node(l, v, d, r, _) ->