Errortraceval print_pos : Format.formatter -> position -> unitval trivial_expansion : Types.type_expr -> expanded_typetype !'a escape_kind = | Constructor of Path.t| Univ of Types.type_expr| Self| Module_type of Path.t| Equation of 'a| Constrainttype !'variety variant = | Incompatible_types_for : string -> 'a variant| No_intersection : unification variant| Fixed_row : position
* fixed_row_case
* Types.fixed_explanation -> unification variant| Presence_not_guaranteed_for : position * string -> comparison variant| Openness : position -> comparison varianttype (!'a5, !'variety1) elt = | Diff : 'a diff -> ('a, 'b) elt| Variant : 'variety variant -> ('a0, 'variety) elt| Obj : 'variety0 obj -> ('a1, 'variety0) elt| Escape : 'a2 escape -> ('a2, 'c) elt| Incompatible_fields : {name : string;diff : Types.type_expr diff;} -> ('a3, 'd) elt| Rec_occur : Types.type_expr * Types.type_expr -> ('a4, 'e) elttype (!'a, !'variety) t = ('a, 'variety) elt listtype !'variety trace = (Types.type_expr, 'variety) ttype !'variety error = (expanded_type, 'variety) tval incompatible_fields :
name:string ->
got:Types.type_expr ->
expected:Types.type_expr ->
(Types.type_expr, 'a) elttype equality_error = private {trace : comparison error;subst : (Types.type_expr * Types.type_expr) list;}val unification_error : trace:unification error -> unification_errorval equality_error :
trace:comparison error ->
subst:(Types.type_expr * Types.type_expr) list ->
equality_errorval moregen_error : trace:comparison error -> moregen_errorval swap_unification_error : unification_error -> unification_errormodule Subtype : sig ... end