diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 1996-04-04 15:57:00 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 1996-04-04 15:57:00 +0000 |
commit | cb1ae6ffdfd9604acb674435200768d535a67a03 (patch) | |
tree | 867f2fec699e83d6dc59cd34d222bffda80cc14a /stdlib/map.ml | |
parent | c4d10d8199213ce60075e30bc19b7b9fea0d94fd (diff) |
Ajout de Map.remove.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@739 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/map.ml')
-rw-r--r-- | stdlib/map.ml | 20 |
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, _) -> |