summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Clerc <xavier.clerc@inria.fr>2011-07-21 07:43:44 +0000
committerXavier Clerc <xavier.clerc@inria.fr>2011-07-21 07:43:44 +0000
commitd5e1e67d6451de72b4e1e4cb11157deda19b5abb (patch)
treea767ef709f3a4350ff0d01237a3cb21a44df2e9a
parent22a753340d9bbccb31112963db3a89ff3d0603d5 (diff)
test suite: 'sigsubst' moved from 'testlabl'.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11138 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--testsuite/tests/typing-sigsubst/Makefile4
-rw-r--r--testsuite/tests/typing-sigsubst/sigsubst.ml (renamed from testlabl/sigsubst.ml)29
-rw-r--r--testsuite/tests/typing-sigsubst/sigsubst.ml.reference36
3 files changed, 54 insertions, 15 deletions
diff --git a/testsuite/tests/typing-sigsubst/Makefile b/testsuite/tests/typing-sigsubst/Makefile
new file mode 100644
index 000000000..5f42b7057
--- /dev/null
+++ b/testsuite/tests/typing-sigsubst/Makefile
@@ -0,0 +1,4 @@
+BASEDIR=../..
+include $(BASEDIR)/makefiles/Makefile.toplevel
+include $(BASEDIR)/makefiles/Makefile.common
+
diff --git a/testlabl/sigsubst.ml b/testsuite/tests/typing-sigsubst/sigsubst.ml
index 9b6c957b2..4cb22fa2d 100644
--- a/testlabl/sigsubst.ml
+++ b/testsuite/tests/typing-sigsubst/sigsubst.ml
@@ -1,38 +1,37 @@
module type Printable = sig
type t
val print : Format.formatter -> t -> unit
-end
+end;;
module type Comparable = sig
type t
val compare : t -> t -> int
-end
+end;;
module type PrintableComparable = sig
include Printable
include Comparable with type t = t
-end
+end;;
module type PrintableComparable = sig
type t
include Printable with type t := t
include Comparable with type t := t
-end
+end;;
module type PrintableComparable = sig
include Printable
include Comparable with type t := t
-end
-module type ComparableInt = Comparable with type t := int
+end;;
+module type ComparableInt = Comparable with type t := int;;
+module type S = sig type t val f : t -> t end;;
+module type S' = S with type t := int;;
-module type S = sig type t val f : t -> t end
-module type S' = S with type t := int
-
-module type S = sig type 'a t val map : ('a -> 'b) -> 'a t -> 'b t end
-module type S1 = S with type 'a t := 'a list
+module type S = sig type 'a t val map : ('a -> 'b) -> 'a t -> 'b t end;;
+module type S1 = S with type 'a t := 'a list;;
module type S2 = sig
type 'a dict = (string * 'a) list
include S with type 'a t := 'a dict
-end
+end;;
module type S =
- sig module T : sig type exp type arg end val f : T.exp -> T.arg end
-module M = struct type exp = string type arg = int end
-module type S' = S with module T := M
+ sig module T : sig type exp type arg end val f : T.exp -> T.arg end;;
+module M = struct type exp = string type arg = int end;;
+module type S' = S with module T := M;;
diff --git a/testsuite/tests/typing-sigsubst/sigsubst.ml.reference b/testsuite/tests/typing-sigsubst/sigsubst.ml.reference
new file mode 100644
index 000000000..3adcb82a9
--- /dev/null
+++ b/testsuite/tests/typing-sigsubst/sigsubst.ml.reference
@@ -0,0 +1,36 @@
+
+# module type Printable =
+ sig type t val print : Format.formatter -> t -> unit end
+# module type Comparable = sig type t val compare : t -> t -> int end
+# Characters 60-94:
+ include Comparable with type t = t
+ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+Error: Multiple definition of the type name t.
+ Names must be unique in a given structure or signature.
+# module type PrintableComparable =
+ sig
+ type t
+ val print : Format.formatter -> t -> unit
+ val compare : t -> t -> int
+ end
+# module type PrintableComparable =
+ sig
+ type t
+ val print : Format.formatter -> t -> unit
+ val compare : t -> t -> int
+ end
+# module type ComparableInt = sig val compare : int -> int -> int end
+# module type S = sig type t val f : t -> t end
+# module type S' = sig val f : int -> int end
+# module type S = sig type 'a t val map : ('a -> 'b) -> 'a t -> 'b t end
+# module type S1 = sig val map : ('a -> 'b) -> 'a list -> 'b list end
+# module type S2 =
+ sig
+ type 'a dict = (string * 'a) list
+ val map : ('a -> 'b) -> 'a dict -> 'b dict
+ end
+# module type S =
+ sig module T : sig type exp type arg end val f : T.exp -> T.arg end
+# module M : sig type exp = string type arg = int end
+# module type S' = sig val f : M.exp -> M.arg end
+#