forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
btype.mli
316 lines (252 loc) · 11.7 KB
/
btype.mli
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Basic operations on core types *)
open Asttypes
open Types
(**** Sets, maps and hashtables of types ****)
module TypeSet : sig
include Set.S with type elt = transient_expr
val add: type_expr -> t -> t
val mem: type_expr -> t -> bool
val singleton: type_expr -> t
val exists: (type_expr -> bool) -> t -> bool
val elements: t -> type_expr list
end
module TransientTypeMap : Map.S with type key = transient_expr
module TypeMap : sig
include Map.S with type key = transient_expr
and type 'a t = 'a TransientTypeMap.t
val add: type_expr -> 'a -> 'a t -> 'a t
val find: type_expr -> 'a t -> 'a
val singleton: type_expr -> 'a -> 'a t
val fold: (type_expr -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
end
module TypeHash : sig
include Hashtbl.S with type key = transient_expr
val add: 'a t -> type_expr -> 'a -> unit
val remove : 'a t -> type_expr -> unit
val find: 'a t -> type_expr -> 'a
val iter: (type_expr -> 'a -> unit) -> 'a t -> unit
end
module TypePairs : sig
type t
val create: int -> t
val clear: t -> unit
val add: t -> type_expr * type_expr -> unit
val mem: t -> type_expr * type_expr -> bool
val iter: (type_expr * type_expr -> unit) -> t -> unit
end
(**** Levels ****)
val generic_level: int
val newgenty: type_desc -> type_expr
(* Create a generic type *)
val newgenvar: ?name:string -> unit -> type_expr
(* Return a fresh generic variable *)
val newgenstub: scope:int -> type_expr
(* Return a fresh generic node, to be instantiated
by [Transient_expr.set_stub_desc] *)
(* Use Tsubst instead
val newmarkedvar: int -> type_expr
(* Return a fresh marked variable *)
val newmarkedgenvar: unit -> type_expr
(* Return a fresh marked generic variable *)
*)
(**** Types ****)
val is_Tvar: type_expr -> bool
val is_Tunivar: type_expr -> bool
val is_Tconstr: type_expr -> bool
val dummy_method: label
(**** polymorphic variants ****)
val is_fixed: row_desc -> bool
(* Return whether the row is directly marked as fixed or not *)
val has_fixed_explanation: row_desc -> bool
(* Return whether the row should be treated as fixed or not.
In particular, [is_fixed row] implies [has_fixed_explanation row].
*)
val fixed_explanation: row_desc -> fixed_explanation option
(* Return the potential explanation for the fixed row *)
val merge_fixed_explanation:
fixed_explanation option -> fixed_explanation option
-> fixed_explanation option
(* Merge two explanations for a fixed row *)
val static_row: row_desc -> bool
(* Return whether the row is static or not *)
val hash_variant: label -> int
(* Hash function for variant tags *)
val proxy: type_expr -> type_expr
(* Return the proxy representative of the type: either itself
or a row variable *)
(**** Utilities for private abbreviations with fixed rows ****)
val row_of_type: type_expr -> type_expr
val has_constr_row: type_expr -> bool
val is_row_name: string -> bool
val is_constr_row: allow_ident:bool -> type_expr -> bool
(* Set the polymorphic variant row_name field *)
val set_static_row_name: type_declaration -> Path.t -> unit
(**** Utilities for type traversal ****)
val iter_type_expr: (type_expr -> unit) -> type_expr -> unit
(* Iteration on types *)
val fold_type_expr: ('a -> type_expr -> 'a) -> 'a -> type_expr -> 'a
val iter_row: (type_expr -> unit) -> row_desc -> unit
(* Iteration on types in a row *)
val fold_row: ('a -> type_expr -> 'a) -> 'a -> row_desc -> 'a
val iter_abbrev: (type_expr -> unit) -> abbrev_memo -> unit
(* Iteration on types in an abbreviation list *)
val iter_type_expr_kind: (type_expr -> unit) -> (type_decl_kind -> unit)
val iter_type_expr_cstr_args: (type_expr -> unit) ->
(constructor_arguments -> unit)
val map_type_expr_cstr_args: (type_expr -> type_expr) ->
(constructor_arguments -> constructor_arguments)
type type_iterators =
{ it_signature: type_iterators -> signature -> unit;
it_signature_item: type_iterators -> signature_item -> unit;
it_value_description: type_iterators -> value_description -> unit;
it_type_declaration: type_iterators -> type_declaration -> unit;
it_extension_constructor: type_iterators -> extension_constructor -> unit;
it_module_declaration: type_iterators -> module_declaration -> unit;
it_modtype_declaration: type_iterators -> modtype_declaration -> unit;
it_class_declaration: type_iterators -> class_declaration -> unit;
it_class_type_declaration: type_iterators -> class_type_declaration -> unit;
it_functor_param: type_iterators -> functor_parameter -> unit;
it_module_type: type_iterators -> module_type -> unit;
it_class_type: type_iterators -> class_type -> unit;
it_type_kind: type_iterators -> type_decl_kind -> unit;
it_do_type_expr: type_iterators -> type_expr -> unit;
it_type_expr: type_iterators -> type_expr -> unit;
it_path: Path.t -> unit; }
val type_iterators: type_iterators
(* Iteration on arbitrary type information.
[it_type_expr] calls [mark_node] to avoid loops. *)
val unmark_iterators: type_iterators
(* Unmark any structure containing types. See [unmark_type] below. *)
val copy_type_desc:
?keep_names:bool -> (type_expr -> type_expr) -> type_desc -> type_desc
(* Copy on types *)
val copy_row:
(type_expr -> type_expr) ->
bool -> row_desc -> bool -> type_expr -> row_desc
module For_copy : sig
type copy_scope
(* The private state that the primitives below are mutating, it should
remain scoped within a single [with_scope] call.
While it is possible to circumvent that discipline in various
ways, you should NOT do that. *)
val redirect_desc: copy_scope -> type_expr -> type_desc -> unit
(* Temporarily change a type description *)
val with_scope: (copy_scope -> 'a) -> 'a
(* [with_scope f] calls [f] and restores saved type descriptions
before returning its result. *)
end
val lowest_level: int
(* Marked type: ty.level < lowest_level *)
val not_marked_node: type_expr -> bool
(* Return true if a type node is not yet marked *)
val logged_mark_node: type_expr -> unit
(* Mark a type node, logging the marking so it can be backtracked *)
val try_logged_mark_node: type_expr -> bool
(* Mark a type node if it is not yet marked, logging the marking so it
can be backtracked.
Return false if it was already marked *)
val flip_mark_node: type_expr -> unit
(* Mark a type node.
The marking is not logged and will have to be manually undone using
one of the various [unmark]'ing functions below. *)
val try_mark_node: type_expr -> bool
(* Mark a type node if it is not yet marked.
The marking is not logged and will have to be manually undone using
one of the various [unmark]'ing functions below.
Return false if it was already marked *)
val mark_type: type_expr -> unit
(* Mark a type recursively *)
val mark_type_params: type_expr -> unit
(* Mark the sons of a type node recursively *)
val unmark_type: type_expr -> unit
val unmark_type_decl: type_declaration -> unit
val unmark_extension_constructor: extension_constructor -> unit
val unmark_class_type: class_type -> unit
val unmark_class_signature: class_signature -> unit
(* Remove marks from a type *)
(**** Memorization of abbreviation expansion ****)
val find_expans: private_flag -> Path.t -> abbrev_memo -> type_expr option
(* Look up a memorized abbreviation *)
val cleanup_abbrev: unit -> unit
(* Flush the cache of abbreviation expansions.
When some types are saved (using [output_value]), this
function MUST be called just before. *)
val memorize_abbrev:
abbrev_memo ref ->
private_flag -> Path.t -> type_expr -> type_expr -> unit
(* Add an expansion in the cache *)
val forget_abbrev:
abbrev_memo ref -> Path.t -> unit
(* Remove an abbreviation from the cache *)
(**** Backtracking ****)
val snapshot: unit -> snapshot
val backtrack: snapshot -> unit
(* Backtrack to a given snapshot. Only possible if you have
not already backtracked to a previous snapshot.
Calls [cleanup_abbrev] internally *)
(**** Utilities for labels ****)
val is_optional : arg_label -> bool
val label_name : arg_label -> label
(* Returns the label name with first character '?' or '~' as appropriate. *)
val prefixed_label_name : arg_label -> label
val extract_label :
label -> (arg_label * 'a) list ->
(arg_label * 'a * bool * (arg_label * 'a) list) option
(* actual label,
value,
whether (label, value) was at the head of the list,
list without the extracted (label, value) *)
(**** Utilities for class types ****)
(* Get the class signature within a class type *)
val signature_of_class_type : class_type -> class_signature
(* Get the body of a class type (i.e. without parameters) *)
val class_body : class_type -> class_type
(* Fully expand the head of a class type *)
val scrape_class_type : class_type -> class_type
(* Return the number of parameters of a class type *)
val class_type_arity : class_type -> int
(* Given a path and type parameters, add an abbreviation to a class type *)
val abbreviate_class_type :
Path.t -> type_expr list -> class_type -> class_type
(* Get the self type of a class *)
val self_type : class_type -> type_expr
(* Get the row variable of the self type of a class *)
val self_type_row : class_type -> type_expr
(* Return the methods of a class signature *)
val methods : class_signature -> string list
(* Return the virtual methods of a class signature *)
val virtual_methods : class_signature -> string list
(* Return the concrete methods of a class signature *)
val concrete_methods : class_signature -> MethSet.t
(* Return the public methods of a class signature *)
val public_methods : class_signature -> string list
(* Return the instance variables of a class signature *)
val instance_vars : class_signature -> string list
(* Return the virtual instance variables of a class signature *)
val virtual_instance_vars : class_signature -> string list
(* Return the concrete instance variables of a class signature *)
val concrete_instance_vars : class_signature -> VarSet.t
(* Return the type of a method.
@raises [Assert_failure] if the class has no such method. *)
val method_type : label -> class_signature -> type_expr
(* Return the type of an instance variable.
@raises [Assert_failure] if the class has no such method. *)
val instance_variable_type : label -> class_signature -> type_expr
(**** Forward declarations ****)
val print_raw: (Format.formatter -> type_expr -> unit) ref
(**** Type information getter ****)
val cstr_type_path : constructor_description -> Path.t