Typestype type_desc = | Tvar of string option| Tarrow of Asttypes.arg_label * type_expr * type_expr * commutable| Ttuple of type_expr list| Tconstr of Path.t * type_expr list * abbrev_memo ref| Tobject of type_expr * (Path.t * type_expr list) option ref| Tfield of string * field_kind * type_expr * type_expr| Tnil| Tlink of type_expr| Tsubst of type_expr * type_expr option| Tvariant of row_desc| Tunivar of string option| Tpoly of type_expr * type_expr list| Tpackage of Path.t * (Longident.t * type_expr) listand abbrev_memo = | Mnil| Mcons of Asttypes.private_flag * Path.t * type_expr * type_expr * abbrev_memo| Mlink of abbrev_memo refval is_commu_ok : commutable -> boolval commu_ok : commutableval commu_var : unit -> commutableval field_kind_repr : field_kind -> field_kind_viewval field_public : field_kindval field_absent : field_kindval field_private : unit -> field_kindval field_kind_internal_repr : field_kind -> field_kindval get_level : type_expr -> intval get_scope : type_expr -> intval get_id : type_expr -> inttype transient_expr = private {mutable desc : type_desc;mutable level : int;mutable scope : int;id : int;}module Transient_expr : sig ... endmodule TransientTypeOps : sig ... endval create_row :
fields:(Asttypes.label * row_field) list ->
more:type_expr ->
closed:bool ->
fixed:fixed_explanation option ->
name:(Path.t * type_expr list) option ->
row_descval row_fields : row_desc -> (Asttypes.label * row_field) listval row_closed : row_desc -> boolval row_fixed : row_desc -> fixed_explanation optionval get_row_field : Asttypes.label -> row_desc -> row_fieldtype row_desc_repr = | Row of {fields : (Asttypes.label * row_field) list;more : type_expr;closed : bool;fixed : fixed_explanation option;name : (Path.t * type_expr list) option;}val row_repr : row_desc -> row_desc_reprval row_field_repr : row_field -> row_field_viewval rf_absent : row_fieldval changed_row_field_exts : row_field list -> (unit -> unit) -> boolmodule Uid = Shape.Uidmodule MethSet : sig ... endmodule VarSet : sig ... endmodule Meths : sig ... endmodule Vars : sig ... endtype value_description = {val_type : type_expr;val_kind : value_kind;val_loc : Location.t;val_attributes : Parsetree.attributes;val_uid : Uid.t;}and value_kind = | Val_reg| Val_prim of Primitive.description| Val_ivar of Asttypes.mutable_flag * string| Val_self of class_signature * self_meths * Ident.t Vars.t * string| Val_anc of class_signature * Ident.t Meths.t * stringand class_signature = {csig_self : type_expr;mutable csig_self_row : type_expr;mutable csig_vars : (Asttypes.mutable_flag * Asttypes.virtual_flag * type_expr)
Vars.t;mutable csig_meths : (method_privacy * Asttypes.virtual_flag * type_expr)
Meths.t;}module Variance : sig ... endmodule Separability : sig ... endtype type_declaration = {type_params : type_expr list;type_arity : int;type_kind : type_decl_kind;type_private : Asttypes.private_flag;type_manifest : type_expr option;type_variance : Variance.t list;type_separability : Separability.t list;type_is_newtype : bool;type_expansion_scope : int;type_loc : Location.t;type_attributes : Parsetree.attributes;type_immediate : Type_immediacy.t;type_unboxed_default : bool;type_uid : Uid.t;}and type_decl_kind = (label_declaration, constructor_declaration) type_kindand (!'lbl, !'cstr) type_kind = | Type_abstract| Type_record of 'lbl list * record_representation| Type_variant of 'cstr list * variant_representation| Type_openand record_representation = | Record_regular| Record_float| Record_unboxed of bool| Record_inlined of int| Record_extension of Path.tand label_declaration = {ld_id : Ident.t;ld_mutable : Asttypes.mutable_flag;ld_type : type_expr;ld_loc : Location.t;ld_attributes : Parsetree.attributes;ld_uid : Uid.t;}and constructor_declaration = {cd_id : Ident.t;cd_args : constructor_arguments;cd_res : type_expr option;cd_loc : Location.t;cd_attributes : Parsetree.attributes;cd_uid : Uid.t;}type extension_constructor = {ext_type_path : Path.t;ext_type_params : type_expr list;ext_args : constructor_arguments;ext_ret_type : type_expr option;ext_private : Asttypes.private_flag;ext_loc : Location.t;ext_attributes : Parsetree.attributes;ext_uid : Uid.t;}type class_type = | Cty_constr of Path.t * type_expr list * class_type| Cty_signature of class_signature| Cty_arrow of Asttypes.arg_label * type_expr * class_typetype class_declaration = {cty_params : type_expr list;mutable cty_type : class_type;cty_path : Path.t;cty_new : type_expr option;cty_variance : Variance.t list;cty_loc : Location.t;cty_attributes : Parsetree.attributes;cty_uid : Uid.t;}type class_type_declaration = {clty_params : type_expr list;clty_type : class_type;clty_path : Path.t;clty_variance : Variance.t list;clty_loc : Location.t;clty_attributes : Parsetree.attributes;clty_uid : Uid.t;}type module_type = | Mty_ident of Path.t| Mty_signature of signature| Mty_functor of functor_parameter * module_type| Mty_alias of Path.tand signature = signature_item listand signature_item = | Sig_value of Ident.t * value_description * visibility| Sig_type of Ident.t * type_declaration * rec_status * visibility| Sig_typext of Ident.t * extension_constructor * ext_status * visibility| Sig_module of Ident.t
* module_presence
* module_declaration
* rec_status
* visibility| Sig_modtype of Ident.t * modtype_declaration * visibility| Sig_class of Ident.t * class_declaration * rec_status * visibility| Sig_class_type of Ident.t * class_type_declaration * rec_status * visibilityand module_declaration = {md_type : module_type;md_attributes : Parsetree.attributes;md_loc : Location.t;md_uid : Uid.t;}and modtype_declaration = {mtd_type : module_type option;mtd_attributes : Parsetree.attributes;mtd_loc : Location.t;mtd_uid : Uid.t;}val item_visibility : signature_item -> visibilitytype constructor_description = {cstr_name : string;cstr_res : type_expr;cstr_existentials : type_expr list;cstr_args : type_expr list;cstr_arity : int;cstr_tag : constructor_tag;cstr_consts : int;cstr_nonconsts : int;cstr_generalized : bool;cstr_private : Asttypes.private_flag;cstr_loc : Location.t;cstr_attributes : Parsetree.attributes;cstr_inlined : type_declaration option;cstr_uid : Uid.t;}and constructor_tag = | Cstr_constant of int| Cstr_block of int| Cstr_unboxed| Cstr_extension of Path.t * boolval equal_tag : constructor_tag -> constructor_tag -> boolval may_equal_constr :
constructor_description ->
constructor_description ->
booltype label_description = {lbl_name : string;lbl_res : type_expr;lbl_arg : type_expr;lbl_mut : Asttypes.mutable_flag;lbl_pos : int;lbl_all : label_description array;lbl_repres : record_representation;lbl_private : Asttypes.private_flag;lbl_loc : Location.t;lbl_attributes : Parsetree.attributes;lbl_uid : Uid.t;}val signature_item_id : signature_item -> Ident.tval snapshot : unit -> snapshotval backtrack : cleanup_abbrev:(unit -> unit) -> snapshot -> unitval undo_first_change_after : snapshot -> unitval undo_compress : snapshot -> unitval set_level : type_expr -> int -> unitval set_scope : type_expr -> int -> unitval link_kind : inside:field_kind -> field_kind -> unitval link_commu : inside:commutable -> commutable -> unitval set_commu_ok : commutable -> unit