Gprinttyp
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
.------------.
| <desc> id |---->
| |--->
.------------.
where the description part might be:
list/8!
'name
, α
, β
, γ
*
for tuples→
for arrows type[β]∀
, 'name ∀
, ...[mod X with ...]
for a first class module∀
for a universal type binderThe 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 nodeThen each nodes is relied by arrows to any of its children types.
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 |
.----------.
(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 |
.------.
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 | |
| .-------. |
.-----------------.
Various possible choices on how to represent types, see the params
functions for more detail.
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.
val nodes : title:string -> params -> (decoration * element) list -> unit
Full version of types
that allow to print any kind of graph element
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:
elide_links
is true
link nodes are not displayed (default:true
)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
).short_ids
, we use an independent counter for node ids, in order to have shorter ids for small digraphs (default:true
).colorize
nodes are colorized according to their typechecker ids (default:true
).follow_expansions
, we add memoized type constructor expansions to the digraph (default:true
).val update_params :
?elide_links:bool ->
?expansion_as_hyperedge:bool ->
?short_ids:bool ->
?colorize:bool ->
?follow_expansions:bool ->
params ->
params
Update an existing params
with new values.
val node : Types.type_expr -> element
val edge : Types.type_expr -> Types.type_expr -> element
val hyperedge : (dir * decoration * Types.type_expr) list -> element
Edges between more than two elements.
module Decoration : sig ... end
val make : params -> (decoration * element) list -> digraph
val add : params -> (decoration * element) list -> digraph -> digraph
val add_subgraph :
params ->
decoration ->
(decoration * element) list ->
digraph ->
digraph
add a subgraph to a digraph, only fresh nodes are added to the subgraph
val group_nodes : (decoration * digraph) -> digraph -> digraph
groups existing nodes inside a subgraph
val pp : Stdlib.Format.formatter -> digraph -> unit
val debug_on : (unit -> bool) ref
Conditional graph printing
val register_type : (decoration * Types.type_expr) -> unit
register_type (lbl,ty)
adds the type t
to all graph printed until forget
is called
val register_subgraph :
params ->
?decoration:decoration ->
Types.type_expr list ->
unit
register_subgraph params tys
groups together all types reachable from tys
at this point in printed digraphs, until forget
is called
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.
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