package melange-compiler-libs

  1. Overview
  2. Docs
type position =
  1. | First
  2. | Second
val swap_position : position -> position
val print_pos : Format.formatter -> position -> unit
type expanded_type = {
  1. ty : Types.type_expr;
  2. expanded : Types.type_expr;
}
val trivial_expansion : Types.type_expr -> expanded_type

trivial_expansion ty creates an expanded_type whose expansion is also ty. Usually, you want Ctype.expand_type instead, since the expansion carries useful information; however, in certain circumstances, the error is about the expansion of the type, meaning that actually performing the expansion produces more confusing or inaccurate output.

type 'a diff = {
  1. got : 'a;
  2. expected : 'a;
}
val map_diff : ('a -> 'b) -> 'a diff -> 'b diff

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

type 'a escape_kind =
  1. | Constructor of Path.t
  2. | Univ of Types.type_expr
  3. | Self
  4. | Module_type of Path.t
  5. | Equation of 'a
  6. | Constraint

Scope escape related errors

type 'a escape = {
  1. kind : 'a escape_kind;
  2. context : Types.type_expr option;
}
val map_escape : ('a -> 'b) -> 'a escape -> 'b escape
val explain : 'a list -> (prev:'a option -> 'a -> 'b option) -> 'b option
type unification = private
  1. | Unification

Type indices

type comparison = private
  1. | Comparison
type fixed_row_case =
  1. | Cannot_be_closed
  2. | Cannot_add_tags of string list
type 'variety variant =
  1. | Incompatible_types_for : string -> _ variant
  2. | No_tags : position * (Asttypes.label * Types.row_field) list -> _ variant
  3. | No_intersection : unification variant
  4. | Fixed_row : position * fixed_row_case * Types.fixed_explanation -> unification variant
  5. | Presence_not_guaranteed_for : position * string -> comparison variant
  6. | Openness : position -> comparison variant
type 'variety obj =
  1. | Missing_field : position * string -> _ obj
  2. | Abstract_row : position -> _ obj
  3. | Self_cannot_be_closed : unification obj
type ('a, 'variety) elt =
  1. | Diff : 'a diff -> ('a, _) elt
  2. | Variant : 'variety variant -> ('a, 'variety) elt
  3. | Obj : 'variety obj -> ('a, 'variety) elt
  4. | Escape : 'a escape -> ('a, _) elt
  5. | Incompatible_fields : {
    1. name : string;
    2. diff : Types.type_expr diff;
    } -> ('a, _) elt
  6. | Rec_occur : Types.type_expr * Types.type_expr -> ('a, _) 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 map : ('a -> 'b) -> ('a, 'variety) t -> ('b, 'variety) t
val incompatible_fields : name:string -> got:Types.type_expr -> expected:Types.type_expr -> (Types.type_expr, _) elt
val swap_trace : ('a, 'variety) t -> ('a, 'variety) t

The traces ('variety t) are the core error types. However, we bundle them up into three "top-level" error types, which are used elsewhere: unification_error, equality_error, and moregen_error. In the case of equality_error, this has to bundle in extra information; in general, it distinguishes the three types of errors and allows us to distinguish traces that are being built (or processed) from those that are complete and have become the final error. These error types have the invariants that their traces are nonempty; we ensure that through three smart constructors with matching names.

type unification_error = private {
  1. trace : unification error;
}
type equality_error = private {
  1. trace : comparison error;
  2. subst : (Types.type_expr * Types.type_expr) list;
}
type moregen_error = private {
  1. trace : comparison error;
}
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
type comparison_error =
  1. | Equality_error of equality_error
  2. | Moregen_error of moregen_error

Wraps up the two different kinds of comparison errors in one type

val swap_unification_error : unification_error -> unification_error

Lift swap_trace to unification_error

module Subtype : sig ... end