Integrate simple change from constructors_with_record4.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15423 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2014-10-03 08:58:06 +00:00
parent 5be2d7d52c
commit c0d246224a
3 changed files with 9 additions and 10 deletions

View File

@ -39,7 +39,10 @@ let free_vars ty =
unmark_type ty;
!ret
let constructor_descrs ty_res cstrs priv =
let newgenconstr path tyl = newgenty (Tconstr (path, tyl, ref Mnil))
let constructor_descrs ty_path decl cstrs =
let ty_res = newgenconstr ty_path decl.type_params in
let num_consts = ref 0 and num_nonconsts = ref 0 and num_normal = ref 0 in
List.iter
(fun {cd_args; cd_res; _} ->
@ -78,7 +81,7 @@ let constructor_descrs ty_res cstrs priv =
cstr_consts = !num_consts;
cstr_nonconsts = !num_nonconsts;
cstr_normal = !num_normal;
cstr_private = priv;
cstr_private = decl.type_private;
cstr_generalized = cd_res <> None;
cstr_loc = cd_loc;
cstr_attributes = cd_attributes;

View File

@ -17,8 +17,9 @@ open Asttypes
open Types
val constructor_descrs:
type_expr -> constructor_declaration list ->
private_flag -> (Ident.t * constructor_description) list
Path.t -> type_declaration ->
constructor_declaration list ->
(Ident.t * constructor_description) list
val extension_descr:
Path.t -> extension_constructor -> constructor_description
val label_descrs:

View File

@ -1072,13 +1072,8 @@ let scrape_alias env mty = scrape_alias env mty
(* Compute constructor descriptions *)
let constructors_of_type ty_path decl =
let handle_variants cstrs =
Datarepr.constructor_descrs
(newgenty (Tconstr(ty_path, decl.type_params, ref Mnil)))
cstrs decl.type_private
in
match decl.type_kind with
| Type_variant cstrs -> handle_variants cstrs
| Type_variant cstrs -> Datarepr.constructor_descrs ty_path decl cstrs
| Type_record _ | Type_abstract | Type_open -> []
(* Compute label descriptions *)