Ctypemodule TypePairs : Hashtbl.S with type key = Types.type_expr * Types.type_exprmodule Unification_trace : sig ... endUnification traces are used to explain unification errors when printing error messages
exception Unify of Unification_trace.texception Tags of Asttypes.label * Asttypes.labelexception Subtype of Unification_trace.t * Unification_trace.tval save_levels : unit -> levelsval set_levels : levels -> unitval newty : 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 repr : Types.type_expr -> 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 close_object : Types.type_expr -> boolval row_variable : Types.type_expr -> Types.type_exprval set_object_name : Ident.t -> Types.type_expr -> Types.type_expr list -> Types.type_expr -> unitval remove_object_name : Types.type_expr -> unitval hide_private_methods : 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 generalize : Types.type_expr -> unitval lower_contravariant : Env.t -> Types.type_expr -> unitval generalize_structure : Types.type_expr -> unitval generalize_spine : Types.type_expr -> unitval correct_levels : Types.type_expr -> Types.type_exprval limited_generalize : Types.type_expr -> Types.type_expr -> unitval 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 existential_name : Types.constructor_description -> Types.type_expr -> stringval instance_constructor : ?in_pattern:(Env.t ref * int) -> Types.constructor_description -> Types.type_expr list * Types.type_exprval instance_parameterized_type : ?keep_names:bool -> Types.type_expr list -> Types.type_expr -> Types.type_expr list * Types.type_exprval instance_parameterized_type_2 : Types.type_expr list -> Types.type_expr list -> Types.type_expr -> Types.type_expr list * 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 -> 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 : bool -> Types.label_description -> Types.type_expr list * Types.type_expr * Types.type_exprval apply : Env.t -> Types.type_expr list -> Types.type_expr -> Types.type_expr list -> Types.type_exprval expand_head_once : Env.t -> Types.type_expr -> Types.type_exprval expand_head : Env.t -> Types.type_expr -> Types.type_exprval try_expand_once_opt : 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.
val full_expand : Env.t -> Types.type_expr -> Types.type_exprval extract_concrete_typedecl : Env.t -> Types.type_expr -> Path.t * Path.t * Types.type_declarationval enforce_constraints : Env.t -> Types.type_expr -> unitval unify : Env.t -> Types.type_expr -> Types.type_expr -> unitval unify_gadt : equations_level:int -> allow_recursive:bool -> Env.t ref -> Types.type_expr -> Types.type_expr -> unit 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 -> Asttypes.private_flag -> Types.type_expr -> Types.type_exprval check_filter_method : Env.t -> string -> Asttypes.private_flag -> Types.type_expr -> unitval occur_in : Env.t -> Types.type_expr -> Types.type_expr -> boolval deep_occur : Types.type_expr -> Types.type_expr -> boolval filter_self_method : Env.t -> string -> Asttypes.private_flag -> (Ident.t * Types.type_expr) Types.Meths.t ref -> Types.type_expr -> Ident.t * Types.type_exprval 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 : Env.t -> Types.type_expr -> Types.type_expr -> boolval reify_univars : Env.t -> Types.type_expr -> Types.type_exprtype class_match_failure = | CM_Virtual_class |
| CM_Parameter_arity_mismatch of int * int |
| CM_Type_parameter_mismatch of Env.t * Unification_trace.t |
| CM_Class_type_mismatch of Env.t * Types.class_type * Types.class_type |
| CM_Parameter_mismatch of Env.t * Unification_trace.t |
| CM_Val_type_mismatch of string * Env.t * Unification_trace.t |
| CM_Meth_type_mismatch of string * Env.t * Unification_trace.t |
| 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 string |
val 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 -> boolval 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 -> unitexception 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 cyclic_abbrev : Env.t -> Ident.t -> Types.type_expr -> boolval normalize_type : Types.type_expr -> unitval closed_schema : Env.t -> Types.type_expr -> boolval free_variables : ?env:Env.t -> Types.type_expr -> Types.type_expr listval closed_type_decl : Types.type_declaration -> Types.type_expr optionval closed_extension_constructor : Types.extension_constructor -> Types.type_expr optiontype closed_class_failure = | CC_Method of Types.type_expr * bool * string * Types.type_expr |
| CC_Value of Types.type_expr * bool * string * Types.type_expr |
val closed_class : Types.type_expr list -> Types.class_signature -> closed_class_failure optionval unalias : Types.type_expr -> Types.type_exprval signature_of_class_type : Types.class_type -> Types.class_signatureval self_type : Types.class_type -> Types.type_exprval class_type_arity : Types.class_type -> intval arity : Types.type_expr -> intval collapse_conj_params : Env.t -> Types.type_expr list -> unitval wrap_trace_gadt_instances : Env.t -> ('a -> 'b) -> 'a -> 'bval immediacy : Env.t -> Types.type_expr -> Type_immediacy.tval maybe_pointer_type : Env.t -> Types.type_expr -> boolval package_subtype : (Env.t -> Path.t -> Longident.t list -> Types.type_expr list -> Path.t -> Longident.t list -> Types.type_expr list -> bool) refval mcomp : Env.t -> Types.type_expr -> Types.type_expr -> unit