summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1995-10-01 13:39:43 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1995-10-01 13:39:43 +0000
commitdb7e46b25c70cbc553a17b1a6c8875c8cce3d704 (patch)
treed2bbc65490dba04198251f54a347342248026c33 /stdlib
parent62d9977ac1f0f65a35a0aa2b17c207f66ca88ad3 (diff)
Introduction de "S with module ... = ..."
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@306 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/map.mli2
-rw-r--r--stdlib/set.ml2
-rw-r--r--stdlib/set.mli2
3 files changed, 3 insertions, 3 deletions
diff --git a/stdlib/map.mli b/stdlib/map.mli
index 99b2dd2db..eb624c8cd 100644
--- a/stdlib/map.mli
+++ b/stdlib/map.mli
@@ -66,6 +66,6 @@ module type S =
not specified. *)
end
-module Make(Ord: OrderedType): (S with key = Ord.t)
+module Make(Ord: OrderedType): (S with type key = Ord.t)
(* Functor building an implementation of the map structure
given a totally ordered type. *)
diff --git a/stdlib/set.ml b/stdlib/set.ml
index e7aa9d643..140b7ff47 100644
--- a/stdlib/set.ml
+++ b/stdlib/set.ml
@@ -40,7 +40,7 @@ module type S =
val choose: t -> elt
end
-module Make(Ord: OrderedType): (S with elt = Ord.t) =
+module Make(Ord: OrderedType) =
struct
type elt = Ord.t
type t = Empty | Node of t * elt * t * int
diff --git a/stdlib/set.mli b/stdlib/set.mli
index 899226127..fbb62446d 100644
--- a/stdlib/set.mli
+++ b/stdlib/set.mli
@@ -84,6 +84,6 @@ module type S =
but equal elements will be chosen for equal sets. *)
end
-module Make(Ord: OrderedType): (S with elt = Ord.t)
+module Make(Ord: OrderedType): (S with type elt = Ord.t)
(* Functor building an implementation of the set structure
given a totally ordered type. *)