Module Btype
module TypeSet : Stdlib.Set.S with type elt = Types.type_exprmodule TypeMap : Stdlib.Map.S with type key = Types.type_exprmodule TypeHash : Stdlib.Hashtbl.S with type key = Types.type_exprval generic_level : intval newty2 : int -> Types.type_desc -> Types.type_exprval newgenty : Types.type_desc -> Types.type_exprval newgenvar : ?name:string -> unit -> Types.type_exprval is_Tvar : Types.type_expr -> boolval is_Tunivar : Types.type_expr -> boolval is_Tconstr : Types.type_expr -> boolval dummy_method : Asttypes.labelval default_mty : Types.module_type option -> Types.module_typeval repr : Types.type_expr -> Types.type_exprval field_kind_repr : Types.field_kind -> Types.field_kindval commu_repr : Types.commutable -> Types.commutableval row_repr : Types.row_desc -> Types.row_descval row_field_repr : Types.row_field -> Types.row_fieldval row_field : Asttypes.label -> Types.row_desc -> Types.row_fieldval row_more : Types.row_desc -> Types.type_exprval row_fixed : Types.row_desc -> boolval static_row : Types.row_desc -> boolval hash_variant : Asttypes.label -> intval proxy : Types.type_expr -> Types.type_exprval row_of_type : Types.type_expr -> Types.type_exprval has_constr_row : Types.type_expr -> boolval is_row_name : string -> boolval is_constr_row : allow_ident:bool -> Types.type_expr -> boolval iter_type_expr : (Types.type_expr -> unit) -> Types.type_expr -> unitval fold_type_expr : ('a -> Types.type_expr -> 'a) -> 'a -> Types.type_expr -> 'aval iter_row : (Types.type_expr -> unit) -> Types.row_desc -> unitval fold_row : ('a -> Types.type_expr -> 'a) -> 'a -> Types.row_desc -> 'aval iter_abbrev : (Types.type_expr -> unit) -> Types.abbrev_memo -> unit
type type_iterators={it_signature : type_iterators -> Types.signature -> unit;it_signature_item : type_iterators -> Types.signature_item -> unit;it_value_description : type_iterators -> Types.value_description -> unit;it_type_declaration : type_iterators -> Types.type_declaration -> unit;it_extension_constructor : type_iterators -> Types.extension_constructor -> unit;it_module_declaration : type_iterators -> Types.module_declaration -> unit;it_modtype_declaration : type_iterators -> Types.modtype_declaration -> unit;it_class_declaration : type_iterators -> Types.class_declaration -> unit;it_class_type_declaration : type_iterators -> Types.class_type_declaration -> unit;it_module_type : type_iterators -> Types.module_type -> unit;it_class_type : type_iterators -> Types.class_type -> unit;it_type_kind : type_iterators -> Types.type_kind -> unit;it_do_type_expr : type_iterators -> Types.type_expr -> unit;it_type_expr : type_iterators -> Types.type_expr -> unit;it_path : Path.t -> unit;}
val type_iterators : type_iteratorsval unmark_iterators : type_iteratorsval copy_type_desc : ?keep_names:bool -> (Types.type_expr -> Types.type_expr) -> Types.type_desc -> Types.type_descval copy_row : (Types.type_expr -> Types.type_expr) -> bool -> Types.row_desc -> bool -> Types.type_expr -> Types.row_descval copy_kind : Types.field_kind -> Types.field_kind
module For_copy : sig ... endval lowest_level : intval pivot_level : intval mark_type : Types.type_expr -> unitval mark_type_node : Types.type_expr -> unitval mark_type_params : Types.type_expr -> unitval unmark_type : Types.type_expr -> unitval unmark_type_decl : Types.type_declaration -> unitval unmark_extension_constructor : Types.extension_constructor -> unitval unmark_class_type : Types.class_type -> unitval unmark_class_signature : Types.class_signature -> unitval find_expans : Asttypes.private_flag -> Path.t -> Types.abbrev_memo -> Types.type_expr optionval cleanup_abbrev : unit -> unitval memorize_abbrev : Types.abbrev_memo Stdlib.ref -> Asttypes.private_flag -> Path.t -> Types.type_expr -> Types.type_expr -> unitval forget_abbrev : Types.abbrev_memo Stdlib.ref -> Path.t -> unitval is_optional : Asttypes.arg_label -> boolval label_name : Asttypes.arg_label -> Asttypes.labelval prefixed_label_name : Asttypes.arg_label -> Asttypes.labelval extract_label : Asttypes.label -> (Asttypes.arg_label * 'a) list -> Asttypes.arg_label * 'a * (Asttypes.arg_label * 'a) list * (Asttypes.arg_label * 'a) list
val snapshot : unit -> snapshotval backtrack : snapshot -> unitval undo_compress : snapshot -> unitval link_type : Types.type_expr -> Types.type_expr -> unitval set_level : Types.type_expr -> int -> unitval set_scope : Types.type_expr -> int -> unitval set_name : (Path.t * Types.type_expr list) option Stdlib.ref -> (Path.t * Types.type_expr list) option -> unitval set_row_field : Types.row_field option Stdlib.ref -> Types.row_field -> unitval set_univar : Types.type_expr option Stdlib.ref -> Types.type_expr -> unitval set_kind : Types.field_kind option Stdlib.ref -> Types.field_kind -> unitval set_commu : Types.commutable Stdlib.ref -> Types.commutable -> unitval set_typeset : TypeSet.t Stdlib.ref -> TypeSet.t -> unitval log_type : Types.type_expr -> unitval print_raw : (Stdlib.Format.formatter -> Types.type_expr -> unit) Stdlib.refval iter_type_expr_kind : (Types.type_expr -> unit) -> Types.type_kind -> unitval iter_type_expr_cstr_args : (Types.type_expr -> unit) -> Types.constructor_arguments -> unitval map_type_expr_cstr_args : (Types.type_expr -> Types.type_expr) -> Types.constructor_arguments -> Types.constructor_arguments