Ctypeexception Unify of Errortrace.unification_errorexception Equality of Errortrace.equality_errorexception Moregen of Errortrace.moregen_errorexception Subtype of Errortrace.Subtype.errorexception Escape of Types.type_expr Errortrace.escapeexception Tags of Asttypes.label * Asttypes.labelexception Matches_failure of Env.t * Errortrace.unification_errorval newty : Types.type_desc -> Types.type_exprval new_scoped_ty : int -> Types.type_desc -> Types.type_exprval newvar : ?name:string -> unit -> Types.type_exprval newvar2 : ?name:string -> int -> Types.type_exprval new_global_var : ?name:string -> unit -> Types.type_exprval newobj : Types.type_expr -> Types.type_exprval newconstr : Path.t -> Types.type_expr list -> Types.type_exprval none : Types.type_exprval object_fields : Types.type_expr -> Types.type_exprval flatten_fields : 
  Types.type_expr ->
  (string * Types.field_kind * Types.type_expr) list * Types.type_exprTransform a field type into a list of pairs label-type. The fields are sorted.
Beware of the interaction with GADTs:
Due to the introduction of object indexes for GADTs, the row variable of an object may now be an expansible type abbreviation. A first consequence is that flatten_fields will not completely flatten the object, since the type abbreviation will not be expanded (flatten_fields does not receive the current environment). Another consequence is that various functions may be called with the expansion of this type abbreviation, which is a Tfield, e.g. during printing.
Concrete problems have been fixed, but new bugs may appear in the future. (Test cases were added to typing-gadts/test.ml)
val associate_fields : 
  (string * Types.field_kind * Types.type_expr) list ->
  (string * Types.field_kind * Types.type_expr) list ->
  (string
   * Types.field_kind
   * Types.type_expr
   * Types.field_kind
   * Types.type_expr)
    list
  * (string * Types.field_kind * Types.type_expr) list
  * (string * Types.field_kind * Types.type_expr) listval opened_object : Types.type_expr -> boolval set_object_name : 
  Ident.t ->
  Types.type_expr list ->
  Types.type_expr ->
  unitval remove_object_name : Types.type_expr -> unitval find_cltype_for_path : 
  Env.t ->
  Path.t ->
  Types.type_declaration * Types.type_exprval sort_row_fields : 
  (Asttypes.label * Types.row_field) list ->
  (Asttypes.label * Types.row_field) listval merge_row_fields : 
  (Asttypes.label * Types.row_field) list ->
  (Asttypes.label * Types.row_field) list ->
  (Asttypes.label * Types.row_field) list
  * (Asttypes.label * Types.row_field) list
  * (Asttypes.label * Types.row_field * Types.row_field) listval filter_row_fields : 
  bool ->
  (Asttypes.label * Types.row_field) list ->
  (Asttypes.label * Types.row_field) listval lower_contravariant : Env.t -> Types.type_expr -> unitval lower_variables_only : Env.t -> int -> Types.type_expr -> unitval enforce_current_level : Env.t -> Types.type_expr -> unitval generalize_class_signature_spine : Types.class_signature -> unitval limited_generalize : Types.type_expr -> inside:Types.type_expr -> unitval limited_generalize_class_type : 
  Types.type_expr ->
  inside:Types.class_type ->
  unitval duplicate_type : Types.type_expr -> Types.type_exprval fully_generic : Types.type_expr -> boolval check_scope_escape : Env.t -> int -> Types.type_expr -> unitval instance : ?partial:bool -> Types.type_expr -> Types.type_exprval generic_instance : Types.type_expr -> Types.type_exprval instance_list : Types.type_expr list -> Types.type_expr listval new_local_type : 
  ?loc:Location.t ->
  ?manifest_and_scope:(Types.type_expr * int) ->
  Types.type_origin ->
  Types.type_declarationmodule Pattern_env : sig ... endtype existential_treatment = | Keep_existentials_flexible| Make_existentials_abstract of Pattern_env.tval instance_constructor : 
  existential_treatment ->
  Types.constructor_description ->
  Types.type_expr list * Types.type_expr * Types.type_expr listval instance_parameterized_type : 
  ?keep_names:bool ->
  Types.type_expr list ->
  Types.type_expr ->
  Types.type_expr list * Types.type_exprval instance_declaration : Types.type_declaration -> Types.type_declarationval generic_instance_declaration : 
  Types.type_declaration ->
  Types.type_declarationval instance_class : 
  Types.type_expr list ->
  Types.class_type ->
  Types.type_expr list * Types.class_typeval instance_poly : 
  ?keep_names:bool ->
  fixed:bool ->
  Types.type_expr list ->
  Types.type_expr ->
  Types.type_expr list * Types.type_exprval polyfy : 
  Env.t ->
  Types.type_expr ->
  Types.type_expr list ->
  Types.type_expr * boolval instance_label : 
  fixed:bool ->
  Types.label_description ->
  Types.type_expr list * Types.type_expr * Types.type_exprval apply : 
  ?use_current_level:bool ->
  Env.t ->
  Types.type_expr list ->
  Types.type_expr ->
  Types.type_expr list ->
  Types.type_exprval try_expand_once_opt : Env.t -> Types.type_expr -> Types.type_exprval try_expand_safe_opt : Env.t -> Types.type_expr -> Types.type_exprval expand_head_once : Env.t -> Types.type_expr -> Types.type_exprval expand_head : Env.t -> Types.type_expr -> Types.type_exprval expand_head_opt : Env.t -> Types.type_expr -> Types.type_exprThe compiler's own version of expand_head necessary for type-based optimisations.
Expansion of types for error traces; lives here instead of in Errortrace because the expansion machinery lives here.
val expanded_diff : 
  Env.t ->
  got:Types.type_expr ->
  expected:Types.type_expr ->
  (Errortrace.expanded_type, 'variant) Errortrace.eltCreate an Errortrace.Diff by expanding the two types
val unexpanded_diff : 
  got:Types.type_expr ->
  expected:Types.type_expr ->
  (Errortrace.expanded_type, 'variant) Errortrace.eltCreate an Errortrace.Diff by *duplicating* the two types, so that each one's expansion is identical to itself. Despite the name, does create Errortrace.expanded_types.
val full_expand : 
  may_forget_scope:bool ->
  Env.t ->
  Types.type_expr ->
  Types.type_exprtype typedecl_extraction_result = | Typedecl of Path.t * Path.t * Types.type_declaration| Has_no_typedecl| May_have_typedeclval extract_concrete_typedecl : 
  Env.t ->
  Types.type_expr ->
  typedecl_extraction_resultval get_new_abstract_name : Env.t -> string -> stringval unify : Env.t -> Types.type_expr -> Types.type_expr -> unitval unify_gadt : 
  Pattern_env.t ->
  Types.type_expr ->
  Types.type_expr ->
  Btype.TypePairs.tval unify_var : Env.t -> Types.type_expr -> Types.type_expr -> unitval filter_arrow : 
  Env.t ->
  Types.type_expr ->
  Asttypes.arg_label ->
  Types.type_expr * Types.type_exprval filter_method : Env.t -> string -> Types.type_expr -> Types.type_exprval occur_in : Env.t -> Types.type_expr -> Types.type_expr -> boolval deep_occur : Types.type_expr -> Types.type_expr -> boolval moregeneral : Env.t -> bool -> Types.type_expr -> Types.type_expr -> unitval is_moregeneral : 
  Env.t ->
  bool ->
  Types.type_expr ->
  Types.type_expr ->
  boolval rigidify : Types.type_expr -> Types.type_expr listval all_distinct_vars : Env.t -> Types.type_expr list -> boolval matches : 
  expand_error_trace:bool ->
  Env.t ->
  Types.type_expr ->
  Types.type_expr ->
  unitval does_match : Env.t -> Types.type_expr -> Types.type_expr -> boolval reify_univars : Env.t -> Types.type_expr -> Types.type_exprtype filter_arrow_failure = | Unification_error of Errortrace.unification_error| Label_mismatch of {got : Asttypes.arg_label;expected : Asttypes.arg_label;expected_type : Types.type_expr;}| Not_a_functionexception Filter_arrow_failed of filter_arrow_failuretype filter_method_failure = | Unification_error of Errortrace.unification_error| Not_a_method| Not_an_object of Types.type_exprexception Filter_method_failed of filter_method_failuretype class_match_failure = | CM_Virtual_class| CM_Parameter_arity_mismatch of int * int| CM_Type_parameter_mismatch of int * Env.t * Errortrace.equality_error| CM_Class_type_mismatch of Env.t * Types.class_type * Types.class_type| CM_Parameter_mismatch of int * Env.t * Errortrace.moregen_error| CM_Val_type_mismatch of string * Env.t * Errortrace.comparison_error| CM_Meth_type_mismatch of string * Env.t * Errortrace.comparison_error| CM_Non_mutable_value of string| CM_Non_concrete_value of string| CM_Missing_value of string| CM_Missing_method of string| CM_Hide_public of string| CM_Hide_virtual of string * string| CM_Public_method of string| CM_Private_method of string| CM_Virtual_method of stringval match_class_types : 
  ?trace:bool ->
  Env.t ->
  Types.class_type ->
  Types.class_type ->
  class_match_failure listval equal : 
  Env.t ->
  bool ->
  Types.type_expr list ->
  Types.type_expr list ->
  unitval is_equal : 
  Env.t ->
  bool ->
  Types.type_expr list ->
  Types.type_expr list ->
  boolval equal_private : 
  Env.t ->
  Types.type_expr list ->
  Types.type_expr ->
  Types.type_expr list ->
  Types.type_expr ->
  unitval match_class_declarations : 
  Env.t ->
  Types.type_expr list ->
  Types.class_type ->
  Types.type_expr list ->
  Types.class_type ->
  class_match_failure listval enlarge_type : Env.t -> Types.type_expr -> Types.type_expr * boolval subtype : Env.t -> Types.type_expr -> Types.type_expr -> unit -> unitval new_class_signature : unit -> Types.class_signatureval add_dummy_method : Env.t -> scope:int -> Types.class_signature -> unitexception Add_method_failed of add_method_failureval add_method : 
  Env.t ->
  Asttypes.label ->
  Asttypes.private_flag ->
  Asttypes.virtual_flag ->
  Types.type_expr ->
  Types.class_signature ->
  unittype add_instance_variable_failure = | Mutability_mismatch of Asttypes.mutable_flag| Type_mismatch of Errortrace.unification_errorexception Add_instance_variable_failed of add_instance_variable_failureval add_instance_variable : 
  strict:bool ->
  Env.t ->
  Asttypes.label ->
  Asttypes.mutable_flag ->
  Asttypes.virtual_flag ->
  Types.type_expr ->
  Types.class_signature ->
  unittype inherit_class_signature_failure = | Self_type_mismatch of Errortrace.unification_error| Method of Asttypes.label * add_method_failure| Instance_variable of Asttypes.label * add_instance_variable_failureexception Inherit_class_signature_failed of inherit_class_signature_failureval inherit_class_signature : 
  strict:bool ->
  Env.t ->
  Types.class_signature ->
  Types.class_signature ->
  unitval update_class_signature : 
  Env.t ->
  Types.class_signature ->
  Asttypes.label list * Asttypes.label listval hide_private_methods : Env.t -> Types.class_signature -> unitval close_class_signature : Env.t -> Types.class_signature -> boolexception Nondep_cannot_erase of Ident.tval nondep_type : Env.t -> Ident.t list -> Types.type_expr -> Types.type_exprval nondep_type_decl : 
  Env.t ->
  Ident.t list ->
  bool ->
  Types.type_declaration ->
  Types.type_declarationval nondep_extension_constructor : 
  Env.t ->
  Ident.t list ->
  Types.extension_constructor ->
  Types.extension_constructorval nondep_class_declaration : 
  Env.t ->
  Ident.t list ->
  Types.class_declaration ->
  Types.class_declarationval nondep_cltype_declaration : 
  Env.t ->
  Ident.t list ->
  Types.class_type_declaration ->
  Types.class_type_declarationval normalize_type : Types.type_expr -> unitval nongen_vars_in_schema : Env.t -> Types.type_expr -> Btype.TypeSet.t optionval nongen_vars_in_class_declaration : 
  Types.class_declaration ->
  Btype.TypeSet.t optiontype closed_class_failure = {free_variable : Types.type_expr * variable_kind;meth : string;meth_ty : Types.type_expr;}val free_variables : ?env:Env.t -> Types.type_expr -> Types.type_expr listval closed_type_expr : ?env:Env.t -> Types.type_expr -> boolval closed_type_decl : Types.type_declaration -> Types.type_expr optionval closed_extension_constructor : 
  Types.extension_constructor ->
  Types.type_expr optionval closed_class : 
  Types.type_expr list ->
  Types.class_signature ->
  closed_class_failure optionval unalias : Types.type_expr -> Types.type_exprval arity : Types.type_expr -> intval collapse_conj_params : Env.t -> Types.type_expr list -> unitval wrap_trace_gadt_instances : ?force:bool -> Env.t -> ('a -> 'b) -> 'a -> 'bval immediacy : Env.t -> Types.type_expr -> Type_immediacy.tval package_subtype : 
  (Env.t ->
    Path.t ->
    (Longident.t * Types.type_expr) list ->
    Path.t ->
    (Longident.t * Types.type_expr) list ->
    (unit, Errortrace.first_class_module) Stdlib.Result.t)
    refval mcomp : Env.t -> Types.type_expr -> Types.type_expr -> unit