diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 2004-04-23 10:01:34 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 2004-04-23 10:01:34 +0000 |
commit | 32077394fe46c8c21f9cfe8a8fe66a9194fa9973 (patch) | |
tree | df96170efc83571ed9bb01b550cfc89377af59b9 | |
parent | 0cc9f02c30bb1422d26842ab6698c8fb5cd7a0c5 (diff) |
Ajout Map.is_empty, Map.compare, Map.equal
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6250 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | stdlib/map.ml | 41 | ||||
-rw-r--r-- | stdlib/map.mli | 13 | ||||
-rw-r--r-- | stdlib/moreLabels.mli | 5 |
3 files changed, 56 insertions, 3 deletions
diff --git a/stdlib/map.ml b/stdlib/map.ml index 26c4d23c0..81b3396f3 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 diff --git a/stdlib/map.mli b/stdlib/map.mli index ea8cc68f4..71d6e269c 100644 --- a/stdlib/map.mli +++ b/stdlib/map.mli @@ -49,6 +49,9 @@ module type S = val empty: 'a t (** The empty map. *) + val is_empty: 'a t -> bool + (** Test whether a map is empty or not. *) + val add: key -> 'a -> 'a t -> 'a t (** [add x y m] returns a map containing the same bindings as [m], plus a binding of [x] to [y]. If [x] was already bound @@ -90,6 +93,16 @@ module type S = where [k1 ... kN] are the keys of all bindings in [m] (in increasing order), and [d1 ... dN] are the associated data. *) + val compare: ('a -> 'a -> int) -> 'a t -> 'a t -> int + (** Total ordering between maps. The first argument is a total ordering + used to compare data associated with equal keys in the two maps. *) + + val equal: ('a -> 'a -> bool) -> 'a t -> 'a t -> bool + (** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are + equal, that is, contain equal keys and associate them with + equal data. [cmp] is the equality predicate used to compare + the data associated with the keys. *) + end (** Output signature of the functor {!Map.Make}. *) diff --git a/stdlib/moreLabels.mli b/stdlib/moreLabels.mli index 299a7e657..fbf848cba 100644 --- a/stdlib/moreLabels.mli +++ b/stdlib/moreLabels.mli @@ -72,6 +72,7 @@ module Map : sig type key and (+'a) t val empty : 'a t + val is_empty: 'a t -> bool val add : key:key -> data:'a -> 'a t -> 'a t val find : key -> 'a t -> 'a val remove : key -> 'a t -> 'a t @@ -82,7 +83,9 @@ module Map : sig val fold : f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b - end + val compare: cmp:('a -> 'a -> int) -> 'a t -> 'a t -> int + val equal: cmp:('a -> 'a -> bool) -> 'a t -> 'a t -> bool + end module Make : functor (Ord : OrderedType) -> S with type key = Ord.t end |