summaryrefslogtreecommitdiff
path: root/stdlib/map.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/map.ml')
-rw-r--r--stdlib/map.ml41
1 files changed, 39 insertions, 2 deletions
diff --git a/stdlib/map.ml b/stdlib/map.ml
index 26c4d23c00..81b3396f33 100644
--- a/stdlib/map.ml
+++ b/stdlib/map.ml
@@ -24,6 +24,7 @@ module type S =
type key
type +'a t
val empty: 'a t
+ val is_empty: 'a t -> bool
val add: key -> 'a -> 'a t -> 'a t
val find: key -> 'a t -> 'a
val remove: key -> 'a t -> 'a t
@@ -32,6 +33,8 @@ module type S =
val map: ('a -> 'b) -> 'a t -> 'b t
val mapi: (key -> 'a -> 'b) -> 'a t -> 'b t
val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
+ val compare: ('a -> 'a -> int) -> 'a t -> 'a t -> int
+ val equal: ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
end
module Make(Ord: OrderedType) = struct
@@ -42,8 +45,6 @@ module Make(Ord: OrderedType) = struct
Empty
| Node of 'a t * key * 'a * 'a t * int
- let empty = Empty
-
let height = function
Empty -> 0
| Node(_,_,_,_,h) -> h
@@ -82,6 +83,10 @@ module Make(Ord: OrderedType) = struct
end else
Node(l, x, d, r, (if hl >= hr then hl + 1 else hr + 1))
+ let empty = Empty
+
+ let is_empty = function Empty -> true | _ -> false
+
let rec add x data = function
Empty ->
Node(Empty, x, data, Empty, 1)
@@ -158,4 +163,36 @@ module Make(Ord: OrderedType) = struct
| Node(l, v, d, r, _) ->
fold f l (f v d (fold f r accu))
+ type 'a enumeration = End | More of key * 'a * 'a t * 'a enumeration
+
+ let rec cons_enum m e =
+ match m with
+ Empty -> e
+ | Node(l, v, d, r, _) -> cons_enum l (More(v, d, r, e))
+
+ let compare cmp m1 m2 =
+ let rec compare_aux e1 e2 =
+ match (e1, e2) with
+ (End, End) -> 0
+ | (End, _) -> -1
+ | (_, End) -> 1
+ | (More(v1, d1, r1, e1), More(v2, d2, r2, e2)) ->
+ let c = Ord.compare v1 v2 in
+ if c <> 0 then c else
+ let c = cmp d1 d2 in
+ if c <> 0 then c else
+ compare_aux (cons_enum r1 e1) (cons_enum r2 e2)
+ in compare_aux (cons_enum m1 End) (cons_enum m2 End)
+
+ let equal cmp m1 m2 =
+ let rec equal_aux e1 e2 =
+ match (e1, e2) with
+ (End, End) -> true
+ | (End, _) -> false
+ | (_, End) -> false
+ | (More(v1, d1, r1, e1), More(v2, d2, r2, e2)) ->
+ Ord.compare v1 v2 = 0 && cmp d1 d2 &&
+ equal_aux (cons_enum r1 e1) (cons_enum r2 e2)
+ in equal_aux (cons_enum m1 End) (cons_enum m2 End)
+
end