forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
gprinttyp.mli
326 lines (270 loc) · 9.69 KB
/
gprinttyp.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
317
318
319
320
321
322
323
324
325
326
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Florian Angeletti, projet Cambium, Inria Paris *)
(* *)
(* Copyright 2024 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. *)
(* *)
(**************************************************************************)
(**
This module provides function for printing type expressions as digraph using
graphviz format. This is mostly aimed at providing a better representation
of type expressions during debugging session.
*)
(**
A type node is printed as
{[
.---------------.
| lvl |
| <desc> ID |---->
| |--->
.---------------.
]}
where the description part might be:
- a path: [list/8!]
- a type variable: ['name], [α], [β], [γ]
- [*] for tuples
- [→] for arrows type
- an universal type variable: [[β]∀], ['name ∀], ...
- [[mod X with ...]] for a first class module
- [∀] for a universal type binder
The more complex encoding for polymorphic variants and object types uses nodes
as head of the subgraph representing those types
- [[obj...]] for the head of an object subgraph
- [[Nil]] for the end of an object subgraph
- [[Row...]] for the head of a polymorphic variant subgraph
- [[Subst]] for a temporary substitution node
Then each nodes is relied by arrows to any of its children types.
- Type variables, universal type variables, [Nil], and [Subst] nodes don't have
children.
- For tuples, the children types are the elements of the tuple. For instance,
[int * float] is represented as
{[
.------. 0 .-------.
| * 1 |-------->| int! 2|
.------. .-------.
|
| 1
v
.----------.
| float! 3 |
.----------.
]}
- For arrows, the children types are the type of the argument and the result
type. For instance, for [int -> float]:
{[
.------. 0 .-------.
| → 4 |-------->| int! 2|
.------. .-------.
|
| 1
v
.----------.
| float! 3 |
.----------.
]}
- For type constructor, like list the main children nodes are the argument
types. For instance, [(int,float) result] is represented as:
{[
.-------------. 0 .-------.
| Result.t 5 |-------->| int! 2|
.-------------. .-------.
|
| 1
v
.----------.
| float! 3 |
.----------.
]}
Moreover, type abbreviations might be linked to the expanded nodes.
If I define: [type 'a pair = 'a * 'a], a type expression [int pair] might
correspond to the nodes:
{[
.--------. 0 .--------.
| pair 6 |------> | int! 2 |
.--------. .--------.
┆ ^
┆ expand |
┆ |
.------. 0 + 1 |
| * 7 |------>-------.
.------.
]}
- Universal type binders have two kind of children: bound variables,
and the main body. For instance, ['a. 'a -> 'a] is represented as
{[
.------. bind .-------.
| ∀ 8 |----------> | 𝛼 10 |
.------. .------.
| ^
| |
v |
.------. 0 + 1 |
| → 9 |------>-------.
.------.
]}
- [[Subst]] node are children are the type graph guarded by the
substitution node, and an eventual link to the parent row variable.
- The children of first-class modules are the type expressions that may appear
in the right hand side of constraints.
For instance, [module M with type t = 'a and type u = 'b] is represented as
{[
.----------------------. 0 .-----.
| [mod M with t, u] 11 |-------->| 𝛼 12|
.----------------------. .-----
|
| 1
v
.------.
| 𝛽 13 |
.------.
]}
- The children of [obj] (resp. [row]) are the methods (resp. constructor) of the
object type (resp. polymorphic variant). Each method is then linked to its
type. To make them easier to read they are grouped inside graphviz cluster.
For instance, [<a:int; m:'self; ..> as 'self] will be represented as:
{[
.----------------.
| .----------. |
| | [obj] 14 |<------<-----<-----.
| .----------. | |
| ┆ | |
| .-------------. | .------. | .-------.
| | a public 15 |----->| ∀ 18 |----->| int! 2 |
| .-------------. | .------. | .-------.
| ┆ | |
| .-------------. | .------. |
| | m public 16 |-----| ∀ 19 |>--|
| .------------. | .------.
| ┆ |
| ┆ row var |
| ┆ |
| .-------. |
| | '_ 17 | |
| .-------. |
.-----------------.
]}
*)
type digraph
(** Digraph with nodes, edges, hyperedges and subgraphes *)
type params
(** Various possible choices on how to represent types, see the {!params}
functions for more detail.*)
type element
(** Graph element, see the {!node}, {!edge} and {!hyperedge} function *)
type decoration
(** Visual decoration on graph elements, see the {!Decoration} module.*)
val types: title:string -> params -> (decoration * Types.type_expr) list -> unit
(** Print a graph to the file
[asprintf "%s/%04d-%s-%a.dot"
dump_dir
session_unique_id
title
pp_context context
]
If the [dump_dir] flag is not set, the local directory is used.
See the {!context} type on how and why to setup the context. *)
(** Full version of {!types} that allow to print any kind of graph element *)
val nodes: title:string -> params -> (decoration * element) list -> unit
val params:
?elide_links:bool ->
?expansion_as_hyperedge:bool ->
?short_ids:bool ->
?colorize:bool ->
?follow_expansions:bool ->
unit -> params
(** Choice of details for printing type graphes:
- if [elide_links] is [true] link nodes are not displayed (default:[true])
- with [expansion_as_hyperedge], memoized constructor expansion are
displayed as a hyperedge between the node storing the memoized expansion,
the expanded node and the expansion (default:[false]).
- with [short_ids], we use an independent counter for node ids, in order to
have shorter ids for small digraphs (default:[true]).
- with [colorize] nodes are colorized according to their typechecker ids
(default:[true]).
- with [follow_expansions], we add memoized type constructor expansions to
the digraph (default:[true]).
*)
(** Update an existing [params] with new values. *)
val update_params:
?elide_links:bool ->
?expansion_as_hyperedge:bool ->
?short_ids:bool ->
?colorize:bool ->
?follow_expansions:bool ->
params -> params
val node: Types.type_expr -> element
val edge: Types.type_expr -> Types.type_expr -> element
type dir = Toward | From
val hyperedge: (dir * decoration * Types.type_expr) list -> element
(** Edges between more than two elements. *)
(** {1 Node and decoration types} *)
module Decoration: sig
type color =
| Named of string
| HSL of {h:float;s:float;l:float}
val green: color
val blue: color
val red:color
val purple:color
val hsl: h:float -> s:float -> l:float -> color
type style =
| Filled of color option
| Dotted
| Dash
type shape =
| Ellipse
| Circle
| Diamond
type property =
| Color of color
| Font_color of color
| Style of style
| Label of string list
| Shape of shape
val filled: color -> property
val txt: string -> property
val make: property list -> decoration
end
(** {1 Digraph construction and printing}*)
val make: params -> (decoration * element) list -> digraph
val add: params -> (decoration * element) list -> digraph -> digraph
(** add a subgraph to a digraph, only fresh nodes are added to the subgraph *)
val add_subgraph:
params -> decoration -> (decoration * element) list -> digraph -> digraph
(** groups existing nodes inside a subgraph *)
val group_nodes: decoration * digraph -> digraph -> digraph
val pp: Format.formatter -> digraph -> unit
(** {1 Debugging helper functions } *)
(** {2 Generic print debugging function} *)
(** Conditional graph printing *)
val debug_on: (unit -> bool) ref
(** [debug_off f] switches off debugging before running [f]. *)
val debug_off: (unit -> 'a) -> 'a
(** [debug f] runs [f] when [!debug_on ()]*)
val debug: (unit -> unit) -> unit
(** {2 Node tracking functions }*)
(** [register_type (lbl,ty)] adds the type [t] to all graph printed until
{!forget} is called *)
val register_type: decoration * Types.type_expr -> unit
(** [register_subgraph params tys] groups together all types reachable from
[tys] at this point in printed digraphs, until {!forget} is called *)
val register_subgraph:
params -> ?decoration:decoration -> Types.type_expr list -> unit
(** Forget all recorded context types *)
val forget : unit -> unit
(** {2 Contextual information}
Those functions can be used to modify the filename of the generated digraphs.
Use those functions to provide contextual information on a graph emitted
during an execution trace.*)
type 'a context
val global: string context
val loc: Warnings.loc context
val set_context: 'a context -> 'a -> unit
val with_context: 'a context -> 'a -> (unit -> 'b) -> 'b