forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
printtyp.mli
259 lines (220 loc) · 10.1 KB
/
printtyp.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
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
(* Printing functions *)
open Format_doc
open Types
open Outcometree
val longident: Longident.t printer
val ident: Ident.t printer
val namespaced_ident: Shape.Sig_component_kind.t -> Ident.t -> string
val tree_of_path: Path.t -> out_ident
val path: Path.t printer
val string_of_path: Path.t -> string
val type_path: Path.t printer
(** Print a type path taking account of [-short-paths].
Calls should be within [wrap_printing_env]. *)
module Out_name: sig
val create: string -> out_name
val print: out_name -> string
end
type namespace := Shape.Sig_component_kind.t option
val strings_of_paths: namespace -> Path.t list -> string list
(** Print a list of paths, using the same naming context to
avoid name collisions *)
val wrap_printing_env: error:bool -> Env.t -> (unit -> 'a) -> 'a
(* Call the function using the environment for type path shortening *)
(* This affects all the printing functions below *)
(* Also, if [~error:true], then disable the loading of cmis *)
module Naming_context: sig
val enable: bool -> unit
(** When contextual names are enabled, the mapping between identifiers
and names is ensured to be one-to-one. *)
end
(** The [Conflicts] module keeps track of conflicts arising when attributing
names to identifiers and provides functions that can print explanations
for these conflict in error messages *)
module Conflicts: sig
val exists: unit -> bool
(** [exists()] returns true if the current naming context renamed
an identifier to avoid a name collision *)
type explanation =
{ kind: Shape.Sig_component_kind.t;
name:string;
root_name:string;
location:Location.t
}
val list_explanations: unit -> explanation list
(** [list_explanations()] return the list of conflict explanations
collected up to this point, and reset the list of collected
explanations *)
val print_located_explanations: explanation list printer
val err_msg: unit -> doc option
(** [err_msg ()] return an error message if there are pending conflict
explanations at this point. It is often important to check for conflicts
after all printing is done, thus the delayed nature of [err_msg]*)
val reset: unit -> unit
end
val reset: unit -> unit
(** Print out a type. This will pick names for type variables, and will not
reuse names for common type variables shared across multiple type
expressions. (It will also reset the printing state, which matters for
other type formatters such as [prepared_type_expr].) If you want multiple
types to use common names for type variables, see [prepare_for_printing] and
[prepared_type_expr]. *)
val type_expr: type_expr printer
(** [prepare_for_printing] resets the global printing environment, a la [reset],
and prepares the types for printing by reserving names and marking loops.
Any type variables that are shared between multiple types in the input list
will be given the same name when printed with [prepared_type_expr]. *)
val prepare_for_printing: type_expr list -> unit
(** [add_type_to_preparation ty] extend a previous type expression preparation
to the type expression [ty]
*)
val add_type_to_preparation: type_expr -> unit
val prepared_type_expr: type_expr printer
(** The function [prepared_type_expr] is a less-safe but more-flexible version
of [type_expr] that should only be called on [type_expr]s that have been
passed to [prepare_for_printing]. Unlike [type_expr], this function does no
extra work before printing a type; in particular, this means that any loops
in the type expression may cause a stack overflow (see #8860) since this
function does not mark any loops. The benefit of this is that if multiple
type expressions are prepared simultaneously and then printed with
[prepared_type_expr], they will use the same names for the same type
variables. *)
val constructor_arguments: constructor_arguments printer
val tree_of_type_scheme: type_expr -> out_type
val type_scheme: type_expr printer
val prepared_type_scheme: type_expr printer
val shared_type_scheme: type_expr printer
(** [shared_type_scheme] is very similar to [type_scheme], but does not reset
the printing context first. This is intended to be used in cases where the
printing should have a particularly wide context, such as documentation
generators; most use cases, such as error messages, have narrower contexts
for which [type_scheme] is better suited. *)
val tree_of_value_description: Ident.t -> value_description -> out_sig_item
val value_description: Ident.t -> value_description printer
val label : label_declaration printer
val add_constructor_to_preparation : constructor_declaration -> unit
val prepared_constructor : constructor_declaration printer
val constructor : constructor_declaration printer
val tree_of_type_declaration:
Ident.t -> type_declaration -> rec_status -> out_sig_item
val add_type_declaration_to_preparation :
Ident.t -> type_declaration -> unit
val prepared_type_declaration: Ident.t -> type_declaration printer
val type_declaration: Ident.t -> type_declaration printer
val tree_of_extension_constructor:
Ident.t -> extension_constructor -> ext_status -> out_sig_item
val add_extension_constructor_to_preparation :
extension_constructor -> unit
val prepared_extension_constructor:
Ident.t -> extension_constructor printer
val extension_constructor:
Ident.t -> extension_constructor printer
(* Prints extension constructor with the type signature:
type ('a, 'b) bar += A of float
*)
val extension_only_constructor:
Ident.t -> extension_constructor printer
(* Prints only extension constructor without type signature:
A of float
*)
val tree_of_module:
Ident.t -> ?ellipsis:bool -> module_type -> rec_status -> out_sig_item
val modtype: module_type printer
val signature: signature printer
val tree_of_modtype: module_type -> out_module_type
val tree_of_modtype_declaration:
Ident.t -> modtype_declaration -> out_sig_item
(** Print a list of functor parameters while adjusting the printing environment
for each functor argument.
Currently, we are disabling disambiguation for functor argument name to
avoid the need to track the moving association between identifiers and
syntactic names in situation like:
got: (X: sig module type T end) (Y:X.T) (X:sig module type T end) (Z:X.T)
expect: (_: sig end) (Y:X.T) (_:sig end) (Z:X.T)
*)
val functor_parameters:
sep:unit printer -> ('b -> Format_doc.formatter -> unit) ->
(Ident.t option * 'b) list -> Format_doc.formatter -> unit
type type_or_scheme = Type | Type_scheme
val tree_of_signature: Types.signature -> out_sig_item list
val tree_of_typexp: type_or_scheme -> type_expr -> out_type
val modtype_declaration: Ident.t -> modtype_declaration printer
val class_type: class_type printer
val tree_of_class_declaration:
Ident.t -> class_declaration -> rec_status -> out_sig_item
val class_declaration: Ident.t -> class_declaration printer
val tree_of_cltype_declaration:
Ident.t -> class_type_declaration -> rec_status -> out_sig_item
val cltype_declaration: Ident.t -> class_type_declaration printer
val type_expansion :
type_or_scheme -> Errortrace.expanded_type printer
val prepare_expansion: Errortrace.expanded_type -> Errortrace.expanded_type
module Compat: sig
(** {!Format} compatible printers *)
type 'a printer := Format.formatter -> 'a -> unit
val longident : Longident.t printer
val path: Path.t printer
val type_expr: type_expr printer
val shared_type_scheme: type_expr printer
val signature: signature printer
val modtype: module_type printer
val class_type: class_type printer
val string_of_label: Asttypes.arg_label -> string
end
val report_ambiguous_type_error:
formatter -> Env.t -> (Path.t * Path.t) -> (Path.t * Path.t) list ->
Format_doc.t -> Format_doc.t -> Format_doc.t -> unit
val report_unification_error :
formatter ->
Env.t -> Errortrace.unification_error ->
?type_expected_explanation:Format_doc.t -> Format_doc.t -> Format_doc.t ->
unit
val report_equality_error :
formatter ->
type_or_scheme ->
Env.t -> Errortrace.equality_error ->
Format_doc.t -> Format_doc.t ->
unit
val report_moregen_error :
formatter ->
type_or_scheme ->
Env.t -> Errortrace.moregen_error ->
Format_doc.t -> Format_doc.t ->
unit
val report_comparison_error :
formatter ->
type_or_scheme ->
Env.t -> Errortrace.comparison_error ->
Format_doc.t -> Format_doc.t ->
unit
module Subtype : sig
val report_error :
formatter ->
Env.t ->
Errortrace.Subtype.error ->
string ->
unit
end
(* for toploop *)
val print_items: (Env.t -> signature_item -> 'a option) ->
Env.t -> signature_item list -> (out_sig_item * 'a option) list
(* Simple heuristic to rewrite Foo__bar.* as Foo.Bar.* when Foo.Bar is an alias
for Foo__bar. This pattern is used by the stdlib. *)
val rewrite_double_underscore_paths: Env.t -> Path.t -> Path.t
(** [printed_signature sourcefile ppf sg] print the signature [sg] of
[sourcefile] with potential warnings for name collisions *)
val printed_signature: string -> Format.formatter -> signature -> unit