Module Env
type summary=|Env_empty|Env_value of summary * Ident.t * Types.value_description|Env_type of summary * Ident.t * Types.type_declaration|Env_extension of summary * Ident.t * Types.extension_constructor|Env_module of summary * Ident.t * Types.module_presence * Types.module_declaration|Env_modtype of summary * Ident.t * Types.modtype_declaration|Env_class of summary * Ident.t * Types.class_declaration|Env_cltype of summary * Ident.t * Types.class_type_declaration|Env_open of summary * Path.tThe string set argument of
Env_openrepresents a list of module names to skip, i.e. that won't be imported in the toplevel namespace.|Env_functor_arg of summary * Ident.t|Env_constraints of summary * Types.type_declaration Path.Map.t|Env_copy_types of summary * string list|Env_persistent of summary * Ident.ttype address=|Aident of Ident.t|Adot of address * inttype t
val empty : tval initial_safe_string : tval initial_unsafe_string : tval diff : t -> t -> Ident.t listval copy_local : from:t -> t -> t
type type_descriptions= Types.constructor_description list * Types.label_description listtype iter_cont
val iter_types : (Path.t -> (Path.t * (Types.type_declaration * type_descriptions)) -> unit) -> t -> iter_contval run_iter_cont : iter_cont list -> (Path.t * iter_cont) listval same_types : t -> t -> boolval used_persistent : unit -> Types.Concr.tval find_shadowed_types : Path.t -> t -> Path.t listval without_cmis : ('a -> 'b) -> 'a -> 'bval find_value : Path.t -> t -> Types.value_descriptionval find_type : Path.t -> t -> Types.type_declarationval find_type_descrs : Path.t -> t -> type_descriptionsval find_module : Path.t -> t -> Types.module_declarationval find_modtype : Path.t -> t -> Types.modtype_declarationval find_class : Path.t -> t -> Types.class_declarationval find_cltype : Path.t -> t -> Types.class_type_declarationval find_type_expansion : Path.t -> t -> Types.type_expr list * Types.type_expr * intval find_type_expansion_opt : Path.t -> t -> Types.type_expr list * Types.type_expr * intval find_modtype_expansion : Path.t -> t -> Types.module_typeval find_value_address : Path.t -> t -> addressval find_module_address : Path.t -> t -> addressval find_class_address : Path.t -> t -> addressval find_constructor_address : Path.t -> t -> addressval add_functor_arg : Ident.t -> t -> tval is_functor_arg : Path.t -> t -> boolval normalize_module_path : Location.t option -> t -> Path.t -> Path.tval normalize_type_path : Location.t option -> t -> Path.t -> Path.tval normalize_path_prefix : Location.t option -> t -> Path.t -> Path.tval reset_required_globals : unit -> unitval get_required_globals : unit -> Ident.t listval add_required_global : Ident.t -> unitval has_local_constraints : t -> boolval lookup_value : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.t * Types.value_descriptionval lookup_constructor : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Types.constructor_descriptionval lookup_all_constructors : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> (Types.constructor_description * (unit -> unit)) listval lookup_label : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Types.label_descriptionval lookup_all_labels : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> (Types.label_description * (unit -> unit)) listval lookup_type : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.tval lookup_module : load:bool -> ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.tval lookup_modtype : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.t * Types.modtype_declarationval lookup_class : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.t * Types.class_declarationval lookup_cltype : ?loc:Location.t -> ?mark:bool -> Longident.t -> t -> Path.t * Types.class_type_declaration
val make_copy_of_types : string list -> t -> copy_of_typesval do_copy_types : copy_of_types -> t -> tdo_copy_types copy envwill raise a fatal error if the values inenvare different from the env passed tomake_copy_of_types.
val add_value : ?check:(string -> Warnings.t) -> Ident.t -> Types.value_description -> t -> tval add_type : check:bool -> Ident.t -> Types.type_declaration -> t -> tval add_extension : check:bool -> Ident.t -> Types.extension_constructor -> t -> tval add_module : ?arg:bool -> Ident.t -> Types.module_presence -> Types.module_type -> t -> tval add_module_declaration : ?arg:bool -> check:bool -> Ident.t -> Types.module_presence -> Types.module_declaration -> t -> tval add_modtype : Ident.t -> Types.modtype_declaration -> t -> tval add_class : Ident.t -> Types.class_declaration -> t -> tval add_cltype : Ident.t -> Types.class_type_declaration -> t -> tval add_local_type : Path.t -> Types.type_declaration -> t -> tval add_persistent_structure : Ident.t -> t -> tval persistent_structures_of_dir : Load_path.Dir.t -> Misc.Stdlib.String.Set.tval filter_non_loaded_persistent : (Ident.t -> bool) -> t -> tval add_item : Types.signature_item -> t -> tval add_signature : Types.signature -> t -> tval open_signature : ?used_slot:bool Stdlib.ref -> ?loc:Location.t -> ?toplevel:bool -> Asttypes.override_flag -> Path.t -> t -> t optionval open_pers_signature : string -> t -> tval enter_value : ?check:(string -> Warnings.t) -> string -> Types.value_description -> t -> Ident.t * tval enter_type : scope:int -> string -> Types.type_declaration -> t -> Ident.t * tval enter_extension : scope:int -> string -> Types.extension_constructor -> t -> Ident.t * tval enter_module : scope:int -> ?arg:bool -> string -> Types.module_presence -> Types.module_type -> t -> Ident.t * tval enter_module_declaration : ?arg:bool -> Ident.t -> Types.module_presence -> Types.module_declaration -> t -> tval enter_modtype : scope:int -> string -> Types.modtype_declaration -> t -> Ident.t * tval enter_class : scope:int -> string -> Types.class_declaration -> t -> Ident.t * tval enter_cltype : scope:int -> string -> Types.class_type_declaration -> t -> Ident.t * tval enter_signature : scope:int -> Types.signature -> t -> Types.signature * tval reset_cache : unit -> unitval reset_cache_toplevel : unit -> unitval set_unit_name : string -> unitval get_unit_name : unit -> stringval read_signature : string -> string -> Types.signatureval save_signature : alerts:string Misc.Stdlib.String.Map.t -> Types.signature -> string -> string -> Cmi_format.cmi_infosval save_signature_with_imports : alerts:string Misc.Stdlib.String.Map.t -> Types.signature -> string -> string -> (string * Stdlib.Digest.t option) list -> Cmi_format.cmi_infosval crc_of_unit : string -> Stdlib.Digest.tval imports : unit -> (string * Stdlib.Digest.t option) listval is_imported_opaque : string -> boolval crc_units : Consistbl.tval add_import : string -> unitval summary : t -> summaryval keep_only_summary : t -> tval env_of_only_summary : (summary -> Subst.t -> t) -> t -> t
type error=|Illegal_renaming of string * string * string|Inconsistent_import of string * string * string|Need_recursive_types of string * string|Depend_on_unsafe_string_unit of string * string|Missing_module of Location.t * Path.t * Path.t|Illegal_value_name of Location.t * string
exceptionError of error
val report_error : Stdlib.Format.formatter -> error -> unitval mark_value_used : string -> Types.value_description -> unitval mark_module_used : string -> Location.t -> unitval mark_type_used : string -> Types.type_declaration -> unit
val mark_constructor_used : constructor_usage -> string -> Types.type_declaration -> string -> unitval mark_constructor : constructor_usage -> t -> string -> Types.constructor_description -> unitval mark_extension_used : constructor_usage -> Types.extension_constructor -> string -> unitval in_signature : bool -> t -> tval is_in_signature : t -> boolval set_value_used_callback : string -> Types.value_description -> (unit -> unit) -> unitval set_type_used_callback : string -> Types.type_declaration -> ((unit -> unit) -> unit) -> unitval check_modtype_inclusion : (loc:Location.t -> t -> Types.module_type -> Path.t -> Types.module_type -> unit) Stdlib.refval check_well_formed_module : (t -> Location.t -> string -> Types.module_type -> unit) Stdlib.refval add_delayed_check_forward : ((unit -> unit) -> unit) Stdlib.refval strengthen : (aliasable:bool -> t -> Types.module_type -> Path.t -> Types.module_type) Stdlib.refval same_constr : (t -> Types.type_expr -> Types.type_expr -> bool) Stdlib.ref
val fold_values : (string -> Path.t -> Types.value_description -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_types : (string -> Path.t -> (Types.type_declaration * type_descriptions) -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_constructors : (Types.constructor_description -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_labels : (Types.label_description -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_modules : (string -> Path.t -> Types.module_declaration -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aPersistent structures are only traversed if they are already loaded.
val fold_modtypes : (string -> Path.t -> Types.modtype_declaration -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_classes : (string -> Path.t -> Types.class_declaration -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval fold_cltypes : (string -> Path.t -> Types.class_type_declaration -> 'a -> 'a) -> Longident.t option -> t -> 'a -> 'aval scrape_alias : t -> Types.module_type -> Types.module_typeUtilities
val check_value_name : string -> Location.t -> unitval print_address : Stdlib.Format.formatter -> address -> unit
module Persistent_signature : sig ... end