Module Ctype.Unification_trace

Unification traces are used to explain unification errors when printing error messages

type position =
| First
| Second
type desc = {
t : Types.type_expr;
expanded : Types.type_expr option;
}
type 'a diff = {
got : 'a;
expected : 'a;
}
type 'a escape =
| Constructor of Path.t
| Univ of Types.type_expr(*

The type_expr argument of Univ is always a Tunivar _, we keep a type_expr to track renaming in Printtyp

*)
| Self
| Module_type of Path.t
| Equation of 'a

Scope escape related errors

Errors for polymorphic variants

type fixed_row_case =
| Cannot_be_closed
| Cannot_add_tags of string list
type variant =
| No_intersection
| No_tags of position * (Asttypes.label * Types.row_field) list
| Incompatible_types_for of string
| Fixed_row of position * fixed_row_case * Types.fixed_explanation(*

Fixed row types, e.g. 'a. [> `X] as 'a

*)
type obj =
| Missing_field of position * string
| Abstract_row of position
| Self_cannot_be_closed
type 'a elt =
| Diff of 'a diff
| Variant of variant
| Obj of obj
| Escape of {
context : Types.type_expr option;
kind : 'a escape;
}
| Incompatible_fields of {
name : string;
diff : Types.type_expr diff;
}
| Rec_occur of Types.type_expr * Types.type_expr
type t = desc elt list
val map_diff : ('a -> 'b) -> 'a diff -> 'b diff

map_diff f {expected;got} is {expected=f expected; got=f got}

val flatten : (Types.type_expr -> Types.type_expr -> 'a) -> t -> 'a elt list

flatten f trace flattens all elements of type desc in trace to either f x.t expanded if x.expanded=Some expanded or f x.t x.t otherwise

val swap : t -> t

Switch expected and got

val explain : 'a elt list -> (prev:'a elt option -> 'a elt -> 'b option) -> 'b option

explain trace f calls f on trace elements starting from the end until f ~prev elt is Some _, returns that or None if the end of the trace is reached.