printing of anonymous type parameters after strengthening

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13603 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2013-04-24 11:02:49 +00:00
parent 1d1d751326
commit b20679022a
4 changed files with 23 additions and 0 deletions

View File

@ -512,3 +512,9 @@ let f : type a. a ty -> a =
let g : type a. a ty -> a =
let () = () in
fun x -> match x with Int y -> y;;
(* Printing of anonymous variables *)
module M = struct type _ t = int end;;
module M = struct type _ t = T : int t end;;
module N = M;;

View File

@ -309,4 +309,7 @@ Error: This expression has type < bar : int; foo : int; .. > as 'a
# type 'a ty = Int : int -> int ty
# val f : 'a ty -> 'a = <fun>
# val g : 'a ty -> 'a = <fun>
# module M : sig type _ t = int end
# module M : sig type _ t = T : int t end
# module N : sig type 'a t = 'a M.t = T : int t end
#

View File

@ -295,4 +295,7 @@ Error: This expression has type < bar : int; foo : int; .. > as 'a
# type 'a ty = Int : int -> int ty
# val f : 'a ty -> 'a = <fun>
# val g : 'a ty -> 'a = <fun>
# module M : sig type _ t = int end
# module M : sig type _ t = T : int t end
# module N : sig type 'a t = 'a M.t = T : int t end
#

View File

@ -683,6 +683,17 @@ let rec tree_of_type_decl id decl =
let params = filter_params decl.type_params in
begin match decl.type_manifest with
| Some ty ->
let vars = free_variables ty in
List.iter
(function {desc = Tvar (Some "_")} as ty ->
if List.memq ty vars then ty.desc <- Tvar None
| _ -> ())
params
| None -> ()
end;
List.iter add_alias params;
List.iter mark_loops params;
List.iter check_name_of_type (List.map proxy params);