summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2012-07-21 01:12:51 +0000
committerJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2012-07-21 01:12:51 +0000
commitd94c59240fca7e5b0d7385008e29c3256ca96bca (patch)
tree01edc5e886609deaec60b0eba51ac6edee7adc0b
parenta2ad11e98c176e0b63cdd596f54ca05fbe8e95f8 (diff)
Fix PR#5694 by checking that the number of parameters is identical
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12753 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--testsuite/tests/typing-sigsubst/sigsubst.ml5
-rw-r--r--typing/typemod.ml3
2 files changed, 6 insertions, 2 deletions
diff --git a/testsuite/tests/typing-sigsubst/sigsubst.ml b/testsuite/tests/typing-sigsubst/sigsubst.ml
index 4cb22fa2d..6759f63ab 100644
--- a/testsuite/tests/typing-sigsubst/sigsubst.ml
+++ b/testsuite/tests/typing-sigsubst/sigsubst.ml
@@ -9,7 +9,7 @@ end;;
module type PrintableComparable = sig
include Printable
include Comparable with type t = t
-end;;
+end;; (* Fails *)
module type PrintableComparable = sig
type t
include Printable with type t := t
@@ -35,3 +35,6 @@ 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;;
+
+
+module type S = sig type 'a t end with type 'a t := unit;; (* Fails *)
diff --git a/typing/typemod.ml b/typing/typemod.ml
index 612cd165c..406c31865 100644
--- a/typing/typemod.ml
+++ b/typing/typemod.ml
@@ -203,7 +203,8 @@ let merge_constraint initial_env loc sg lid constr =
match !real_id with None -> assert false | Some id -> id in
let lid =
try match sdecl.ptype_manifest with
- | Some {ptyp_desc = Ptyp_constr (lid, stl)} ->
+ | Some {ptyp_desc = Ptyp_constr (lid, stl)}
+ when List.length stl = List.length sdecl.ptype_params ->
let params =
List.map
(function {ptyp_desc=Ptyp_var s} -> s | _ -> raise Exit)