Includecoretype primitive_mismatch = | Name| Arity| No_alloc of position| Native_name| Result_repr| Argument_repr of inttype value_mismatch = | Primitive_mismatch of primitive_mismatch| Not_a_primitive| Type of Errortrace.moregen_errorexception Dont_match of value_mismatchtype record_change =
  (Types.label_declaration as 'ld, 'ld, label_mismatch)
    Diffing_with_keys.changetype record_mismatch = | Label_mismatch of record_change list| Unboxed_float_representation of positiontype constructor_mismatch = | Type of Errortrace.equality_error| Arity| Inline_record of record_change list| Kind of position| Explicit_return_type of positiontype extension_constructor_mismatch = | Constructor_privacy| Constructor_mismatch of Ident.t
  * Types.extension_constructor
  * Types.extension_constructor
  * constructor_mismatchtype variant_change =
  (Types.constructor_declaration as 'cd, 'cd, constructor_mismatch)
    Diffing_with_keys.changetype private_variant_mismatch = | Only_outer_closed| Missing of position * string| Presence of string| Incompatible_types_for of string| Types of Errortrace.equality_errortype type_mismatch = | Arity| Privacy of privacy_mismatch| Kind of kind_mismatch| Constraint of Errortrace.equality_error| Manifest of Errortrace.equality_error| Private_variant of Types.type_expr * Types.type_expr * private_variant_mismatch| Private_object of Types.type_expr * Types.type_expr * private_object_mismatch| Variance| Record_mismatch of record_mismatch| Variant_mismatch of variant_change list| Unboxed_representation of position| Immediate of Type_immediacy.Violation.tval value_descriptions : 
  loc:Location.t ->
  Env.t ->
  string ->
  Types.value_description ->
  Types.value_description ->
  Typedtree.module_coercionval type_declarations : 
  ?equality:bool ->
  loc:Location.t ->
  Env.t ->
  mark:bool ->
  string ->
  Types.type_declaration ->
  Path.t ->
  Types.type_declaration ->
  type_mismatch optionval extension_constructors : 
  loc:Location.t ->
  Env.t ->
  mark:bool ->
  Ident.t ->
  Types.extension_constructor ->
  Types.extension_constructor ->
  extension_constructor_mismatch optionval value_descriptions_consistency : 
  Env.t ->
  Types.value_description ->
  Types.value_description ->
  Typedtree.module_coercionThe functions value_descriptions_consistency and type_declarations_consistency check if two declaration are consistent. Declarations are consistent when there exists an environment such that the first declaration is a subtype of the second one.
Notably, if a type declaration td1 is consistent with td2 then a type expression te which is well-formed with the td2 declaration in scope is still well-formed with the td1 declaration: E, td2 |- te => E, td1 |- te.
val type_declarations_consistency : 
  Env.t ->
  Types.type_declaration ->
  Types.type_declaration ->
  type_mismatch optionval report_value_mismatch : 
  string ->
  string ->
  Env.t ->
  value_mismatch Format_doc.printerval report_type_mismatch : 
  string ->
  string ->
  string ->
  Env.t ->
  type_mismatch Format_doc.printerval report_extension_constructor_mismatch : 
  string ->
  string ->
  string ->
  Env.t ->
  extension_constructor_mismatch Format_doc.printer