Module Printtyp

val longident : Format.formatter -> Longident.t -> unit
val ident : Format.formatter -> Ident.t -> unit
val tree_of_path : Path.t -> Outcometree.out_ident
val path : Format.formatter -> Path.t -> unit
val string_of_path : Path.t -> string
val type_path : Format.formatter -> Path.t -> unit
module Out_name : sig ... end
type namespace =
  1. | Type
  2. | Module
  3. | Module_type
  4. | Class
  5. | Class_type
  6. | Other
val strings_of_paths : namespace -> Path.t list -> string list
val raw_type_expr : Format.formatter -> Types.type_expr -> unit
val string_of_label : Asttypes.arg_label -> string
val wrap_printing_env : error:bool -> Env.t -> (unit -> 'a) -> 'a
module Naming_context : sig ... end
module Conflicts : sig ... end
val reset : unit -> unit
val type_expr : Format.formatter -> Types.type_expr -> unit
val prepare_for_printing : Types.type_expr list -> unit
val add_type_to_preparation : Types.type_expr -> unit
val prepared_type_expr : Format.formatter -> Types.type_expr -> unit
val constructor_arguments : Format.formatter -> Types.constructor_arguments -> unit
val tree_of_type_scheme : Types.type_expr -> Outcometree.out_type
val type_scheme : Format.formatter -> Types.type_expr -> unit
val shared_type_scheme : Format.formatter -> Types.type_expr -> unit
val tree_of_value_description : Ident.t -> Types.value_description -> Outcometree.out_sig_item
val value_description : Ident.t -> Format.formatter -> Types.value_description -> unit
val constructor : Format.formatter -> Types.constructor_declaration -> unit
val type_declaration : Ident.t -> Format.formatter -> Types.type_declaration -> unit
val extension_constructor : Ident.t -> Format.formatter -> Types.extension_constructor -> unit
val extension_only_constructor : Ident.t -> Format.formatter -> Types.extension_constructor -> unit
val tree_of_module : Ident.t -> ?ellipsis:bool -> Types.module_type -> Types.rec_status -> Outcometree.out_sig_item
val modtype : Format.formatter -> Types.module_type -> unit
val signature : Format.formatter -> Types.signature -> unit
val tree_of_modtype_declaration : Ident.t -> Types.modtype_declaration -> Outcometree.out_sig_item
val functor_parameters : sep:(Format.formatter -> unit -> unit) -> ('b -> Format.formatter -> unit) -> (Ident.t option * 'b) list -> Format.formatter -> unit
type type_or_scheme =
  1. | Type
  2. | Type_scheme
val tree_of_signature : Types.signature -> Outcometree.out_sig_item list
val modtype_declaration : Ident.t -> Format.formatter -> Types.modtype_declaration -> unit
val class_type : Format.formatter -> Types.class_type -> unit
val class_declaration : Ident.t -> Format.formatter -> Types.class_declaration -> unit
val cltype_declaration : Ident.t -> Format.formatter -> Types.class_type_declaration -> unit
val type_expansion : type_or_scheme -> Format.formatter -> Errortrace.expanded_type -> unit
val 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) -> unit
val report_unification_error : Format.formatter -> Env.t -> Errortrace.unification_error -> ?type_expected_explanation:(Format.formatter -> unit) -> (Format.formatter -> unit) -> (Format.formatter -> unit) -> unit
val report_equality_error : Format.formatter -> type_or_scheme -> Env.t -> Errortrace.equality_error -> (Format.formatter -> unit) -> (Format.formatter -> unit) -> unit
val report_moregen_error : Format.formatter -> type_or_scheme -> Env.t -> Errortrace.moregen_error -> (Format.formatter -> unit) -> (Format.formatter -> unit) -> unit
val report_comparison_error : Format.formatter -> type_or_scheme -> Env.t -> Errortrace.comparison_error -> (Format.formatter -> unit) -> (Format.formatter -> unit) -> unit
module Subtype : sig ... end
val print_items : (Env.t -> Types.signature_item -> 'a option) -> Env.t -> Types.signature_item list -> (Outcometree.out_sig_item * 'a option) list
val rewrite_double_underscore_paths : Env.t -> Path.t -> Path.t
val printed_signature : string -> Format.formatter -> Types.signature -> unit