]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/typing/env.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / typing / env.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: env.mli 9074 2008-10-06 13:53:54Z doligez $ *)
14
15 (* Environment handling *)
16
17 open Types
18
19 type t
20
21 val empty: t
22 val initial: t
23 val diff: t -> t -> Ident.t list
24
25 (* Lookup by paths *)
26
27 val find_value: Path.t -> t -> value_description
28 val find_type: Path.t -> t -> type_declaration
29 val find_module: Path.t -> t -> module_type
30 val find_modtype: Path.t -> t -> modtype_declaration
31 val find_class: Path.t -> t -> class_declaration
32 val find_cltype: Path.t -> t -> cltype_declaration
33
34 val find_type_expansion: Path.t -> t -> type_expr list * type_expr
35 val find_type_expansion_opt: Path.t -> t -> type_expr list * type_expr
36 (* Find the manifest type information associated to a type for the sake
37    of the compiler's type-based optimisations. *)
38 val find_modtype_expansion: Path.t -> t -> Types.module_type
39
40 (* Lookup by long identifiers *)
41
42 val lookup_value: Longident.t -> t -> Path.t * value_description
43 val lookup_annot: Longident.t -> t -> Path.t * Annot.ident
44 val lookup_constructor: Longident.t -> t -> constructor_description
45 val lookup_label: Longident.t -> t -> label_description
46 val lookup_type: Longident.t -> t -> Path.t * type_declaration
47 val lookup_module: Longident.t -> t -> Path.t * module_type
48 val lookup_modtype: Longident.t -> t -> Path.t * modtype_declaration
49 val lookup_class: Longident.t -> t -> Path.t * class_declaration
50 val lookup_cltype: Longident.t -> t -> Path.t * cltype_declaration
51
52 (* Insertion by identifier *)
53
54 val add_value: Ident.t -> value_description -> t -> t
55 val add_annot: Ident.t -> Annot.ident -> t -> t
56 val add_type: Ident.t -> type_declaration -> t -> t
57 val add_exception: Ident.t -> exception_declaration -> t -> t
58 val add_module: Ident.t -> module_type -> t -> t
59 val add_modtype: Ident.t -> modtype_declaration -> t -> t
60 val add_class: Ident.t -> class_declaration -> t -> t
61 val add_cltype: Ident.t -> cltype_declaration -> t -> t
62
63 (* Insertion of all fields of a signature. *)
64
65 val add_item: signature_item -> t -> t
66 val add_signature: signature -> t -> t
67
68 (* Insertion of all fields of a signature, relative to the given path.
69    Used to implement open. *)
70
71 val open_signature: Path.t -> signature -> t -> t
72 val open_pers_signature: string -> t -> t
73
74 (* Insertion by name *)
75
76 val enter_value: string -> value_description -> t -> Ident.t * t
77 val enter_type: string -> type_declaration -> t -> Ident.t * t
78 val enter_exception: string -> exception_declaration -> t -> Ident.t * t
79 val enter_module: string -> module_type -> t -> Ident.t * t
80 val enter_modtype: string -> modtype_declaration -> t -> Ident.t * t
81 val enter_class: string -> class_declaration -> t -> Ident.t * t
82 val enter_cltype: string -> cltype_declaration -> t -> Ident.t * t
83
84 (* Initialize the cache of in-core module interfaces. *)
85 val reset_cache: unit -> unit
86
87 (* Remember the name of the current compilation unit. *)
88 val set_unit_name: string -> unit
89
90 (* Read, save a signature to/from a file *)
91
92 val read_signature: string -> string -> signature
93         (* Arguments: module name, file name. Results: signature. *)
94 val save_signature: signature -> string -> string -> unit
95         (* Arguments: signature, module name, file name. *)
96 val save_signature_with_imports:
97             signature -> string -> string -> (string * Digest.t) list -> unit
98         (* Arguments: signature, module name, file name,
99            imported units with their CRCs. *)
100
101 (* Return the CRC of the interface of the given compilation unit *)
102
103 val crc_of_unit: string -> Digest.t
104
105 (* Return the set of compilation units imported, with their CRC *)
106
107 val imported_units: unit -> (string * Digest.t) list
108
109 (* Direct access to the table of imported compilation units with their CRC *)
110
111 val crc_units: Consistbl.t
112
113 (* Summaries -- compact representation of an environment, to be
114    exported in debugging information. *)
115
116 type summary =
117     Env_empty
118   | Env_value of summary * Ident.t * value_description
119   | Env_type of summary * Ident.t * type_declaration
120   | Env_exception of summary * Ident.t * exception_declaration
121   | Env_module of summary * Ident.t * module_type
122   | Env_modtype of summary * Ident.t * modtype_declaration
123   | Env_class of summary * Ident.t * class_declaration
124   | Env_cltype of summary * Ident.t * cltype_declaration
125   | Env_open of summary * Path.t
126
127 val summary: t -> summary
128
129 (* Error report *)
130
131 type error =
132     Not_an_interface of string
133   | Corrupted_interface of string
134   | Illegal_renaming of string * string
135   | Inconsistent_import of string * string * string
136   | Need_recursive_types of string * string
137
138 exception Error of error
139
140 open Format
141
142 val report_error: formatter -> error -> unit
143
144 (* Forward declaration to break mutual recursion with Includemod. *)
145 val check_modtype_inclusion:
146       (t -> module_type -> Path.t -> module_type -> unit) ref