Module Cmt_format

type binary_annots =
  1. | Packed of Types.signature * string list
  2. | Implementation of Typedtree.structure
  3. | Interface of Typedtree.signature
  4. | Partial_implementation of binary_part array
  5. | Partial_interface of binary_part array
and binary_part =
  1. | Partial_structure of Typedtree.structure
  2. | Partial_structure_item of Typedtree.structure_item
  3. | Partial_expression of Typedtree.expression
  4. | Partial_pattern : 'k Typedtree.pattern_category * 'k Typedtree.general_pattern -> binary_part
  5. | Partial_class_expr of Typedtree.class_expr
  6. | Partial_signature of Typedtree.signature
  7. | Partial_signature_item of Typedtree.signature_item
  8. | Partial_module_type of Typedtree.module_type
type cmt_infos = {
  1. cmt_modname : Misc.modname;
  2. cmt_annots : binary_annots;
  3. cmt_value_dependencies : (Types.value_description * Types.value_description) list;
  4. cmt_comments : (string * Location.t) list;
  5. cmt_args : string array;
  6. cmt_sourcefile : string option;
  7. cmt_builddir : string;
  8. cmt_loadpath : string list;
  9. cmt_source_digest : string option;
  10. cmt_initial_env : Env.t;
  11. cmt_imports : Misc.crcs;
  12. cmt_interface_digest : Digest.t option;
  13. cmt_use_summaries : bool;
  14. cmt_uid_to_loc : Location.t Shape.Uid.Tbl.t;
  15. cmt_impl_shape : Shape.t option;
}
type error =
  1. | Not_a_typedtree of string
exception Error of error
val read : string -> Cmi_format.cmi_infos option * cmt_infos option
val read_cmt : string -> cmt_infos
val read_cmi : string -> Cmi_format.cmi_infos
val save_cmt : string -> string -> binary_annots -> string option -> Env.t -> Cmi_format.cmi_infos option -> Shape.t option -> unit
val read_magic_number : in_channel -> string
val clear : unit -> unit
val add_saved_type : binary_part -> unit
val get_saved_types : unit -> binary_part list
val set_saved_types : binary_part list -> unit
val record_value_dependency : Types.value_description -> Types.value_description -> unit