Map.remove returns the original map when the binding to be removed is not present in the map

master
iguer 2015-04-22 14:19:27 +02:00
parent 5db98d0074
commit 81ca324ef3
3 changed files with 22 additions and 6 deletions

View File

@ -153,14 +153,13 @@ module Make(Ord: OrderedType) = struct
let rec remove x = function
Empty ->
Empty
| Node(l, v, d, r, h) ->
| (Node(l, v, d, r, h) as t) ->
let c = Ord.compare x v in
if c = 0 then
merge l r
if c = 0 then merge l r
else if c < 0 then
bal (remove x l) v d r
let ll = remove x l in if l == ll then t else bal ll v d r
else
bal l v d (remove x r)
let rr = remove x r in if r == rr then t else bal l v d rr
let rec iter f = function
Empty -> ()

View File

@ -87,7 +87,9 @@ module type S =
val remove: key -> 'a t -> 'a t
(** [remove x m] returns a map containing the same bindings as
[m], except for [x] which is unbound in the returned map. *)
[m], except for [x] which is unbound in the returned map.
If [x] was not in [m], [m] is returned unchanged
(the result of the function is then physically equal to [m]). *)
val merge:
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t

View File

@ -132,3 +132,18 @@ let rmap() =
let _ =
Random.init 42;
for i = 1 to 10000 do test (rkey()) (rdata()) (rmap()) (rmap()) done
let () =
(* check that removing a binding from a map that is not present in this map
(1) doesn't allocate and (2) return the original map *)
let m1 = ref M.empty in
for i = 1 to 10 do m1 := M.add i (float i) !m1 done;
let m2 = ref !m1 in
let a0 = Gc.allocated_bytes () in
let a1 = Gc.allocated_bytes () in
for i = 11 to 30 do m2 := M.remove i !m2 done;
let a2 = Gc.allocated_bytes () in
assert (!m2 == !m1);
assert(a2 -. a1 = a1 -. a0)