Printtypval longident : Format.formatter -> Longident.t -> unitval ident : Format.formatter -> Ident.t -> unitval tree_of_path : Path.t -> Outcometree.out_identval path : Format.formatter -> Path.t -> unitval string_of_path : Path.t -> stringval type_path : Format.formatter -> Path.t -> unitmodule Out_name : sig ... endval raw_type_expr : Format.formatter -> Types.type_expr -> unitval string_of_label : Asttypes.arg_label -> stringval wrap_printing_env : error:bool -> Env.t -> (unit -> 'a) -> 'amodule Naming_context : sig ... endmodule Conflicts : sig ... endval type_expr : Format.formatter -> Types.type_expr -> unitval prepare_for_printing : Types.type_expr list -> unitval add_type_to_preparation : Types.type_expr -> unitval prepared_type_expr : Format.formatter -> Types.type_expr -> unitval constructor_arguments :
Format.formatter ->
Types.constructor_arguments ->
unitval tree_of_type_scheme : Types.type_expr -> Outcometree.out_typeval type_scheme : Format.formatter -> Types.type_expr -> unitval tree_of_value_description :
Ident.t ->
Types.value_description ->
Outcometree.out_sig_itemval value_description :
Ident.t ->
Format.formatter ->
Types.value_description ->
unitval label : Format.formatter -> Types.label_declaration -> unitval constructor : Format.formatter -> Types.constructor_declaration -> unitval tree_of_type_declaration :
Ident.t ->
Types.type_declaration ->
Types.rec_status ->
Outcometree.out_sig_itemval type_declaration :
Ident.t ->
Format.formatter ->
Types.type_declaration ->
unitval tree_of_extension_constructor :
Ident.t ->
Types.extension_constructor ->
Types.ext_status ->
Outcometree.out_sig_itemval extension_constructor :
Ident.t ->
Format.formatter ->
Types.extension_constructor ->
unitval extension_only_constructor :
Ident.t ->
Format.formatter ->
Types.extension_constructor ->
unitval tree_of_module :
Ident.t ->
?ellipsis:bool ->
Types.module_type ->
Types.rec_status ->
Outcometree.out_sig_itemval modtype : Format.formatter -> Types.module_type -> unitval signature : Format.formatter -> Types.signature -> unitval tree_of_modtype : Types.module_type -> Outcometree.out_module_typeval tree_of_modtype_declaration :
Ident.t ->
Types.modtype_declaration ->
Outcometree.out_sig_itemval functor_parameters :
sep:(Format.formatter -> unit -> unit) ->
('b -> Format.formatter -> unit) ->
(Ident.t option * 'b) list ->
Format.formatter ->
unitval tree_of_signature : Types.signature -> Outcometree.out_sig_item listval tree_of_typexp : type_or_scheme -> Types.type_expr -> Outcometree.out_typeval modtype_declaration :
Ident.t ->
Format.formatter ->
Types.modtype_declaration ->
unitval class_type : Format.formatter -> Types.class_type -> unitval tree_of_class_declaration :
Ident.t ->
Types.class_declaration ->
Types.rec_status ->
Outcometree.out_sig_itemval class_declaration :
Ident.t ->
Format.formatter ->
Types.class_declaration ->
unitval tree_of_cltype_declaration :
Ident.t ->
Types.class_type_declaration ->
Types.rec_status ->
Outcometree.out_sig_itemval cltype_declaration :
Ident.t ->
Format.formatter ->
Types.class_type_declaration ->
unitval type_expansion :
type_or_scheme ->
Format.formatter ->
Errortrace.expanded_type ->
unitval prepare_expansion : Errortrace.expanded_type -> Errortrace.expanded_typeval report_ambiguous_type_error :
Format.formatter ->
Env.t ->
(Path.t * Path.t) ->
(Path.t * Path.t) list ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
unitval report_unification_error :
Format.formatter ->
Env.t ->
Errortrace.unification_error ->
?type_expected_explanation:(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
unitval report_equality_error :
Format.formatter ->
type_or_scheme ->
Env.t ->
Errortrace.equality_error ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
unitval report_moregen_error :
Format.formatter ->
type_or_scheme ->
Env.t ->
Errortrace.moregen_error ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
unitval report_comparison_error :
Format.formatter ->
type_or_scheme ->
Env.t ->
Errortrace.comparison_error ->
(Format.formatter -> unit) ->
(Format.formatter -> unit) ->
unitmodule Subtype : sig ... endval print_items :
(Env.t -> Types.signature_item -> 'a option) ->
Env.t ->
Types.signature_item list ->
(Outcometree.out_sig_item * 'a option) listval printed_signature : string -> Format.formatter -> Types.signature -> unit