Envtype value_unbound_reason = | Val_unbound_instance_variable |
| Val_unbound_self |
| Val_unbound_ancestor |
| Val_unbound_ghost_recursive of Location.t |
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.t | (* The string set argument of |
| Env_functor_arg of summary * Ident.t | |
| Env_constraints of summary * Types.type_declaration Path.Map.t | |
| Env_copy_types of summary | |
| Env_persistent of summary * Ident.t | |
| Env_value_unbound of summary * string * value_unbound_reason | |
| Env_module_unbound of summary * string * module_unbound_reason |
val empty : tval initial_safe_string : tval initial_unsafe_string : ttype type_descriptions = Types.constructor_description list * Types.label_description listval iter_types : (Path.t -> (Path.t * Types.type_declaration) -> unit) -> t -> iter_contval used_persistent : unit -> Types.Concr.tval 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_ident_constructor : Ident.t -> t -> Types.constructor_descriptionval find_ident_label : Ident.t -> t -> Types.label_descriptionval 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_hash_type : Path.t -> t -> Types.type_declarationval 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 get_required_globals : unit -> Ident.t listval add_required_global : Ident.t -> unitval has_local_constraints : t -> boolval mark_value_used : Types.Uid.t -> unitval mark_module_used : Types.Uid.t -> unitval mark_type_used : Types.Uid.t -> unitval mark_constructor_used : constructor_usage -> Types.constructor_declaration -> unitval mark_extension_used : constructor_usage -> Types.extension_constructor -> unittype lookup_error = | Unbound_value of Longident.t * unbound_value_hint |
| Unbound_type of Longident.t |
| Unbound_constructor of Longident.t |
| Unbound_label of Longident.t |
| Unbound_module of Longident.t |
| Unbound_class of Longident.t |
| Unbound_modtype of Longident.t |
| Unbound_cltype of Longident.t |
| Unbound_instance_variable of string |
| Not_an_instance_variable of string |
| Masked_instance_variable of Longident.t |
| Masked_self_variable of Longident.t |
| Masked_ancestor_variable of Longident.t |
| Structure_used_as_functor of Longident.t |
| Abstract_used_as_functor of Longident.t |
| Functor_used_as_structure of Longident.t |
| Abstract_used_as_structure of Longident.t |
| Generative_used_as_applicative of Longident.t |
| Illegal_reference_to_recursive_module |
| Cannot_scrape_alias of Longident.t * Path.t |
val lookup_error : Location.t -> t -> lookup_error -> 'aval lookup_value : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.value_descriptionval lookup_type : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.type_declarationval lookup_module : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.module_declarationval lookup_modtype : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.modtype_declarationval lookup_class : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.class_declarationval lookup_cltype : ?use:bool -> loc:Location.t -> Longident.t -> t -> Path.t * Types.class_type_declarationval lookup_module_path : ?use:bool -> loc:Location.t -> load:bool -> Longident.t -> t -> Path.tval lookup_constructor : ?use:bool -> loc:Location.t -> constructor_usage -> Longident.t -> t -> Types.constructor_descriptionval lookup_all_constructors : ?use:bool -> loc:Location.t ->
constructor_usage -> Longident.t -> t -> ((Types.constructor_description * (unit -> unit)) list, Location.t * t * lookup_error) resultval lookup_all_constructors_from_type : ?use:bool -> loc:Location.t ->
constructor_usage -> Path.t -> t -> (Types.constructor_description * (unit -> unit)) listval lookup_label : ?use:bool -> loc:Location.t -> Longident.t -> t -> Types.label_descriptionval lookup_all_labels : ?use:bool -> loc:Location.t ->
Longident.t -> t -> ((Types.label_description * (unit -> unit)) list, Location.t * t * lookup_error) resultval lookup_all_labels_from_type : ?use:bool -> loc:Location.t -> Path.t -> t -> (Types.label_description * (unit -> unit)) listval lookup_instance_variable : ?use:bool -> loc:Location.t -> string -> t -> Path.t * Asttypes.mutable_flag * string * Types.type_exprval find_value_by_name : Longident.t -> t -> Path.t * Types.value_descriptionval find_type_by_name : Longident.t -> t -> Path.t * Types.type_declarationval find_module_by_name : Longident.t -> t -> Path.t * Types.module_declarationval find_modtype_by_name : Longident.t -> t -> Path.t * Types.modtype_declarationval find_class_by_name : Longident.t -> t -> Path.t * Types.class_declarationval find_cltype_by_name : Longident.t -> t -> Path.t * Types.class_type_declarationval find_constructor_by_name : Longident.t -> t -> Types.constructor_descriptionval find_label_by_name : Longident.t -> t -> Types.label_descriptionval bound_value : string -> t -> boolval bound_module : string -> t -> boolval bound_type : string -> t -> boolval bound_modtype : string -> t -> boolval bound_class : string -> t -> boolval bound_cltype : string -> t -> boolval 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 -> rebind: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 persistent_structures_of_dir : Load_path.Dir.t -> Misc.Stdlib.String.Set.tval add_item : Types.signature_item -> t -> tval add_signature : Types.signature -> t -> tval open_signature : ?used_slot:bool ref -> ?loc:Location.t -> ?toplevel:bool ->
Asttypes.override_flag -> Path.t -> t -> (t, [ `Not_found | `Functor ]) resultval 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 -> rebind:bool -> 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 : scope:int -> ?arg:bool -> string -> Types.module_presence -> Types.module_declaration -> t -> Ident.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 enter_unbound_value : string -> value_unbound_reason -> t -> tval enter_unbound_module : string -> module_unbound_reason -> t -> tval read_signature : Misc.modname -> Misc.filepath -> Types.signatureval save_signature : alerts:Misc.alerts -> Types.signature -> Misc.modname -> Misc.filepath -> Cmi_format.cmi_infosval save_signature_with_imports : alerts:Misc.alerts -> Types.signature -> Misc.modname -> Misc.filepath -> Misc.crcs -> Cmi_format.cmi_infosval crc_of_unit : Misc.modname -> Digest.tval imports : unit -> Misc.crcsval import_crcs : source:string -> Misc.crcs -> unitval is_imported_opaque : Misc.modname -> boolval register_import_as_opaque : Misc.modname -> unittype error = | Missing_module of Location.t * Path.t * Path.t |
| Illegal_value_name of Location.t * string |
| Lookup_error of Location.t * t * lookup_error |
exception Error of errorval report_error : Format.formatter -> error -> unitval report_lookup_error : Location.t -> t -> Format.formatter -> lookup_error -> unitval is_in_signature : t -> boolval set_value_used_callback : Types.value_description -> (unit -> unit) -> unitval set_type_used_callback : Types.type_declaration -> ((unit -> unit) -> unit) -> unitval check_functor_application : (errors:bool -> loc:Location.t -> t -> Types.module_type -> Path.t -> Types.module_type -> Path.t -> unit) refval check_well_formed_module : (t -> Location.t -> string -> Types.module_type -> unit) refval add_delayed_check_forward : ((unit -> unit) -> unit) refval strengthen : (aliasable:bool -> t -> Types.module_type -> Path.t -> Types.module_type) refval same_constr : (t -> Types.type_expr -> Types.type_expr -> bool) refval print_longident : (Format.formatter -> Longident.t -> unit) refval print_path : (Format.formatter -> Path.t -> unit) refFolds
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 -> '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 : Format.formatter -> address -> unit