1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Environment handling *)
|
|
|
|
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2012-05-30 07:52:37 -07:00
|
|
|
type summary =
|
|
|
|
Env_empty
|
|
|
|
| Env_value of summary * Ident.t * value_description
|
|
|
|
| Env_type of summary * Ident.t * type_declaration
|
|
|
|
| Env_exception of summary * Ident.t * exception_declaration
|
|
|
|
| Env_module of summary * Ident.t * module_type
|
|
|
|
| Env_modtype of summary * Ident.t * modtype_declaration
|
|
|
|
| Env_class of summary * Ident.t * class_declaration
|
|
|
|
| Env_cltype of summary * Ident.t * class_type_declaration
|
|
|
|
| Env_open of summary * Path.t
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type t
|
|
|
|
|
|
|
|
val empty: t
|
|
|
|
val initial: t
|
2003-11-25 01:20:45 -08:00
|
|
|
val diff: t -> t -> Ident.t list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Lookup by paths *)
|
|
|
|
|
|
|
|
val find_value: Path.t -> t -> value_description
|
2012-05-30 07:52:37 -07:00
|
|
|
val find_annot: Path.t -> t -> Annot.ident
|
1995-05-04 03:15:53 -07:00
|
|
|
val find_type: Path.t -> t -> type_declaration
|
2010-11-15 22:01:59 -08:00
|
|
|
val find_constructors: Path.t -> t -> constructor_description list
|
1996-11-29 10:36:42 -08:00
|
|
|
val find_module: Path.t -> t -> module_type
|
1995-05-04 03:15:53 -07:00
|
|
|
val find_modtype: Path.t -> t -> modtype_declaration
|
1998-06-24 12:22:26 -07:00
|
|
|
val find_class: Path.t -> t -> class_declaration
|
2012-05-30 07:52:37 -07:00
|
|
|
val find_cltype: Path.t -> t -> class_type_declaration
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2011-07-29 03:32:43 -07:00
|
|
|
val find_type_expansion:
|
2011-11-24 01:02:48 -08:00
|
|
|
?level:int -> Path.t -> t -> type_expr list * type_expr * int option
|
|
|
|
val find_type_expansion_opt:
|
|
|
|
Path.t -> t -> type_expr list * type_expr * int option
|
2007-11-01 11:36:43 -07:00
|
|
|
(* Find the manifest type information associated to a type for the sake
|
|
|
|
of the compiler's type-based optimisations. *)
|
1997-04-01 12:53:02 -08:00
|
|
|
val find_modtype_expansion: Path.t -> t -> Types.module_type
|
|
|
|
|
2010-10-31 22:33:29 -07:00
|
|
|
val has_local_constraints: t -> bool
|
2011-11-24 01:02:48 -08:00
|
|
|
val add_gadt_instance_level: int -> t -> t
|
|
|
|
val gadt_instance_level: t -> type_expr -> int option
|
|
|
|
val add_gadt_instances: t -> int -> type_expr list -> unit
|
|
|
|
val add_gadt_instance_chain: t -> int -> type_expr -> unit
|
2010-10-31 22:33:29 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Lookup by long identifiers *)
|
|
|
|
|
|
|
|
val lookup_value: Longident.t -> t -> Path.t * value_description
|
2007-05-16 01:21:41 -07:00
|
|
|
val lookup_annot: Longident.t -> t -> Path.t * Annot.ident
|
2012-05-30 07:52:37 -07:00
|
|
|
val lookup_constructor: Longident.t -> t -> Path.t * constructor_description
|
|
|
|
val lookup_label: Longident.t -> t -> Path.t * label_description
|
1995-05-04 03:15:53 -07:00
|
|
|
val lookup_type: Longident.t -> t -> Path.t * type_declaration
|
|
|
|
val lookup_module: Longident.t -> t -> Path.t * module_type
|
|
|
|
val lookup_modtype: Longident.t -> t -> Path.t * modtype_declaration
|
1998-06-24 12:22:26 -07:00
|
|
|
val lookup_class: Longident.t -> t -> Path.t * class_declaration
|
2012-05-30 07:52:37 -07:00
|
|
|
val lookup_cltype: Longident.t -> t -> Path.t * class_type_declaration
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Insertion by identifier *)
|
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
val add_value:
|
|
|
|
?check:(string -> Warnings.t) -> Ident.t -> value_description -> t -> t
|
2007-05-16 01:21:41 -07:00
|
|
|
val add_annot: Ident.t -> Annot.ident -> t -> t
|
1995-05-04 03:15:53 -07:00
|
|
|
val add_type: Ident.t -> type_declaration -> t -> t
|
|
|
|
val add_exception: Ident.t -> exception_declaration -> t -> t
|
|
|
|
val add_module: Ident.t -> module_type -> t -> t
|
|
|
|
val add_modtype: Ident.t -> modtype_declaration -> t -> t
|
1998-06-24 12:22:26 -07:00
|
|
|
val add_class: Ident.t -> class_declaration -> t -> t
|
2012-05-30 07:52:37 -07:00
|
|
|
val add_cltype: Ident.t -> class_type_declaration -> t -> t
|
2011-03-09 22:27:24 -08:00
|
|
|
val add_local_constraint: Ident.t -> type_declaration -> int -> t -> t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Insertion of all fields of a signature. *)
|
|
|
|
|
1996-07-25 06:18:53 -07:00
|
|
|
val add_item: signature_item -> t -> t
|
1995-05-04 03:15:53 -07:00
|
|
|
val add_signature: signature -> t -> t
|
|
|
|
|
|
|
|
(* Insertion of all fields of a signature, relative to the given path.
|
|
|
|
Used to implement open. *)
|
|
|
|
|
2012-06-01 07:05:49 -07:00
|
|
|
val open_signature: ?loc:Location.t -> ?toplevel:bool -> Path.t -> signature -> t -> t
|
1995-05-04 03:15:53 -07:00
|
|
|
val open_pers_signature: string -> t -> t
|
|
|
|
|
|
|
|
(* Insertion by name *)
|
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
val enter_value:
|
|
|
|
?check:(string -> Warnings.t) ->
|
|
|
|
string -> value_description -> t -> Ident.t * t
|
1995-05-04 03:15:53 -07:00
|
|
|
val enter_type: string -> type_declaration -> t -> Ident.t * t
|
|
|
|
val enter_exception: string -> exception_declaration -> t -> Ident.t * t
|
|
|
|
val enter_module: string -> module_type -> t -> Ident.t * t
|
|
|
|
val enter_modtype: string -> modtype_declaration -> t -> Ident.t * t
|
1998-06-24 12:22:26 -07:00
|
|
|
val enter_class: string -> class_declaration -> t -> Ident.t * t
|
2012-05-30 07:52:37 -07:00
|
|
|
val enter_cltype: string -> class_type_declaration -> t -> Ident.t * t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2005-07-31 05:03:40 -07:00
|
|
|
(* Initialize the cache of in-core module interfaces. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val reset_cache: unit -> unit
|
2012-03-21 04:35:51 -07:00
|
|
|
val reset_missing_cmis: unit -> unit
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2008-10-06 06:53:54 -07:00
|
|
|
(* Remember the name of the current compilation unit. *)
|
2005-07-31 05:03:40 -07:00
|
|
|
val set_unit_name: string -> unit
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Read, save a signature to/from a file *)
|
|
|
|
|
1997-05-15 06:30:02 -07:00
|
|
|
val read_signature: string -> string -> signature
|
|
|
|
(* Arguments: module name, file name. Results: signature. *)
|
2012-05-30 07:52:37 -07:00
|
|
|
val save_signature: signature -> string -> string -> signature
|
1997-05-15 06:30:02 -07:00
|
|
|
(* Arguments: signature, module name, file name. *)
|
2002-08-19 05:23:23 -07:00
|
|
|
val save_signature_with_imports:
|
2012-05-31 01:07:31 -07:00
|
|
|
signature -> string -> string -> (string * Digest.t) list -> signature
|
2008-09-10 08:03:33 -07:00
|
|
|
(* Arguments: signature, module name, file name,
|
2002-08-19 05:23:23 -07:00
|
|
|
imported units with their CRCs. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2000-03-26 07:49:08 -08:00
|
|
|
(* Return the CRC of the interface of the given compilation unit *)
|
|
|
|
|
|
|
|
val crc_of_unit: string -> Digest.t
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Return the set of compilation units imported, with their CRC *)
|
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
val imported_units: unit -> (string * Digest.t) list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-11-17 08:42:12 -08:00
|
|
|
(* Direct access to the table of imported compilation units with their CRC *)
|
|
|
|
|
|
|
|
val crc_units: Consistbl.t
|
|
|
|
|
1996-11-29 10:36:42 -08:00
|
|
|
(* Summaries -- compact representation of an environment, to be
|
|
|
|
exported in debugging information. *)
|
|
|
|
|
|
|
|
val summary: t -> summary
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Error report *)
|
|
|
|
|
|
|
|
type error =
|
|
|
|
| Illegal_renaming of string * string
|
1997-05-15 06:30:02 -07:00
|
|
|
| Inconsistent_import of string * string * string
|
2006-06-26 02:38:06 -07:00
|
|
|
| Need_recursive_types of string * string
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
exception Error of error
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
open Format
|
|
|
|
|
|
|
|
val report_error: formatter -> error -> unit
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2012-04-18 02:01:17 -07:00
|
|
|
|
2011-12-21 07:40:54 -08:00
|
|
|
val mark_value_used: string -> value_description -> unit
|
2011-12-22 07:42:40 -08:00
|
|
|
val mark_type_used: string -> type_declaration -> unit
|
2012-04-18 02:01:17 -07:00
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
type constructor_usage = Positive | Pattern | Privatize
|
|
|
|
val mark_constructor_used:
|
|
|
|
constructor_usage -> string -> type_declaration -> string -> unit
|
|
|
|
val mark_constructor:
|
|
|
|
constructor_usage -> t -> string -> constructor_description -> unit
|
|
|
|
val mark_exception_used:
|
|
|
|
constructor_usage -> exception_declaration -> string -> unit
|
2012-01-12 03:24:30 -08:00
|
|
|
|
2012-04-18 11:45:49 -07:00
|
|
|
val in_signature: t -> t
|
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
val set_value_used_callback:
|
|
|
|
string -> value_description -> (unit -> unit) -> unit
|
|
|
|
val set_type_used_callback:
|
|
|
|
string -> type_declaration -> ((unit -> unit) -> unit) -> unit
|
2011-12-21 07:40:54 -08:00
|
|
|
|
2000-02-05 04:11:34 -08:00
|
|
|
(* Forward declaration to break mutual recursion with Includemod. *)
|
2005-08-13 13:59:37 -07:00
|
|
|
val check_modtype_inclusion:
|
|
|
|
(t -> module_type -> Path.t -> module_type -> unit) ref
|
2011-12-21 07:40:54 -08:00
|
|
|
(* Forward declaration to break mutual recursion with Typecore. *)
|
|
|
|
val add_delayed_check_forward: ((unit -> unit) -> unit) ref
|
2012-05-30 07:52:37 -07:00
|
|
|
|
|
|
|
(** Folding over all identifiers (for analysis purpose) *)
|
|
|
|
|
|
|
|
val fold_values:
|
|
|
|
(string -> Path.t -> Types.value_description -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
val fold_types:
|
|
|
|
(string -> Path.t -> Types.type_declaration -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
val fold_constructors:
|
|
|
|
(string -> Path.t -> Types.constructor_description -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
val fold_labels:
|
|
|
|
(string -> Path.t -> Types.label_description -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
|
|
|
|
(** Persistent structures are only traversed if they are already loaded. *)
|
|
|
|
val fold_modules:
|
|
|
|
(string -> Path.t -> Types.module_type -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
|
|
|
|
val fold_modtypes:
|
|
|
|
(string -> Path.t -> Types.modtype_declaration -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
val fold_classs:
|
|
|
|
(string -> Path.t -> Types.class_declaration -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
val fold_cltypes:
|
|
|
|
(string -> Path.t -> Types.class_type_declaration -> 'a -> 'a) ->
|
|
|
|
Longident.t option -> t -> 'a -> 'a
|
|
|
|
|
|
|
|
|
|
|
|
|