Errortrace
val print_pos : Format.formatter -> position -> unit
val trivial_expansion : Types.type_expr -> expanded_type
type !'a escape_kind =
| Constructor of Path.t
| Univ of Types.type_expr
| Self
| Module_type of Path.t
| Equation of 'a
| Constraint
type !'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 variant
type (!'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) elt
type (!'a, !'variety) t = ('a, 'variety) elt list
type !'variety trace = (Types.type_expr, 'variety) t
type !'variety error = (expanded_type, 'variety) t
val incompatible_fields :
name:string ->
got:Types.type_expr ->
expected:Types.type_expr ->
(Types.type_expr, 'a) elt
type equality_error = private {
trace : comparison error;
subst : (Types.type_expr * Types.type_expr) list;
}
val unification_error : trace:unification error -> unification_error
val equality_error :
trace:comparison error ->
subst:(Types.type_expr * Types.type_expr) list ->
equality_error
val moregen_error : trace:comparison error -> moregen_error
val swap_unification_error : unification_error -> unification_error
module Subtype : sig ... end