1:- module(
    2  gv,
    3  [
    4  % EXPORT/VIEW
    5    gv_export/2,            % +File, :Goal_1
    6    gv_export/3,            % +File, :Goal_1, +Options
    7    gv_view/1,              % :Goal_1
    8    gv_view/2,              % :Goal_1, +Options
    9  % FORMATS/METHODS
   10    gv_format/1,            % ?Format
   11    gv_format_media_type/2, % ?Format, ?MediaType
   12    gv_format_type/2,       % ?Format, ?Type
   13    gv_method/1             % ?Method
   14  ]
   15).   16:- reexport(library(dot)).

GraphViz export

*/

   22:- use_module(library(error)).   23:- use_module(library(process)).   24:- use_module(library(settings)).   25
   26:- use_module(library(call_ext)).   27:- use_module(library(dict)).   28:- use_module(library(file_ext)).   29
   30:- discontiguous
   31    gv_format_synonym__/2,
   32    gv_format_type__/2,
   33    gv_format_type__/3.   34
   35:- meta_predicate
   36    gv_export(+, 1),
   37    gv_export(+, 1, +),
   38    gv_export_stream_(1, +, +, +, +, +),
   39    gv_view(1),
   40    gv_view(1, +).   41
   42:- setting(default_gv_export_format, atom, svg,
   43           "The default format that is used when exporting a graph using GraphViz.").   44:- setting(default_gv_method, atom, dot,
   45           "The default method that is used when creating a GraphViz visualization.").   46:- setting(default_gv_view_format, atom, x11,
   47           "The default format that is used when viewing a graph using GraphViz.").   48
   49
   50
   51
   52
   53% EXPORT/VIEW %
 gv_export(+File:atom, :Goal_1) is det
 gv_export(+File:atom, :Goal_1, +Options:options) is det
Arguments:
File- is the name of the file to which the graph export is written.
Goal_1- is a unary goal that takes a Prolog output stream that receives DOT formatted messages.
Options- is a dictionary that may include any of the following options:
  • format(+atom) The format that is used to store the output in. Both binary and text output formats are supported. See gv_format_type(-Format, Type), memberchk(Type, [binary,text]) for possible values. The default value is based on the file extension of File, if this can be heuristically mapped to a GraphViz format, or else uses the value of setting default_gv_export_format.
  • method(+atom) The method that is used by GraphViz to calculate the graph layout. See gv_method(-Method) for possible values. The default value is stored in setting default_gv_method.
  • Other options are passed to dot_graph/4.
   84gv_export(File, Goal_1) :-
   85  gv_export(File, Goal_1, options{}).
   86
   87
   88gv_export(File, Goal_1, Options0) :-
   89  gv_export_default_format_(File, DefaultFormat),
   90  gv_options_(Options0, DefaultFormat, Format, Type, Method, Options),
   91  must_be(oneof([binary,text]), Type),
   92  write_to_file(
   93    File,
   94    gv_export_stream_(Goal_1, Format, Type, Method, Options),
   95    options{type: Type}
   96  ).
   97
   98gv_export_default_format_(File, DefaultFormat) :-
   99  file_extension(File, DefaultFormat),
  100  gv_format(DefaultFormat), !.
  101gv_export_default_format_(_, DefaultFormat) :-
  102  setting(default_gv_export_format, DefaultFormat).
 gv_options_(+Options0:dict, +DefaultFormat:gv_format, -Format:gv_format, -Type:gv_type, -Method:gv_method, -Options:options) is det
  111gv_options_(Options0, DefaultFormat, Format, Type, Method, Options3) :-
  112  % Set default option values.
  113  setting(default_gv_method, DefaultMethod),
  114  merge_dicts(
  115    Options0,
  116    options{format: DefaultFormat, method: DefaultMethod},
  117    Options1
  118  ),
  119  % Typecheck option values.
  120  dict_select(format, Options1, Options2, Format),
  121  call_must_be(gv_format, Format),
  122  dict_select(method, Options2, Options3, Method),
  123  call_must_be(gv_method, Method),
  124  gv_format_type(Format, Type).
  125
  126gv_export_stream_(Goal_1, Format, Type, Method, Options, Out) :-
  127  setup_call_cleanup(
  128    (
  129      % Open a GraphViz input and a GraphViz output stream.  The input
  130      % stream expects statments in the DOT language.  The output
  131      % stream is in the specified Format.
  132      process_create(
  133        path(Method),
  134        ['-T',Format],
  135        [stdin(pipe(ProcIn)),stdout(pipe(ProcOut))]
  136      ),
  137      % Binary and text streams are treated differently.
  138      set_stream(ProcOut, type(Type))
  139    ),
  140    (
  141      call_cleanup(
  142        dot_graph(ProcIn, Goal_1, Options),
  143        close(ProcIn)
  144      ),
  145      copy_stream_data(ProcOut, Out)
  146    ),
  147    close(ProcOut)
  148  ).
 gv_view(:Goal_1) is det
 gv_view(:Goal_1, +Options:options) is det
Generate a GraphViz graph visualization and open the result in a viewer application.
Arguments:
Goal_1- is a unary goal that takes a Prolog output stream that receives DOT formatted messages.
Options- is a dictionary that may include any of the options defined for gv_export/3, but option `format' is set to the value of setting `default_gv_view_format'.
  165gv_view(Goal_1) :-
  166  gv_view(Goal_1, options{}).
  167
  168
  169gv_view(Goal_1, Options0) :-
  170  setting(default_gv_view_format, DefaultFormat),
  171  gv_options_(Options0, DefaultFormat, Format, Type, Method, Options),
  172  must_be(oneof([viewer]), Type),
  173  setup_call_cleanup(
  174    process_create(path(Method), ['-T',Format], [stdin(pipe(ProcIn))]),
  175    dot_graph(ProcIn, Goal_1, Options),
  176    close(ProcIn)
  177  ).
  178
  179
  180
  181
  182
  183% FORMATS/METHODS %
  184%
  185% GraphViz provides two types of export: binary (e.g., `jpeg`) and
  186% text (e.g., `svg`).  The third type `viewer` is use to directly open
  187% GraphViz output in a viewer application (without storing the result
  188% to a file).
 gv_format(+Format:atom) is semidet
gv_format(-Format:atom) is nondet
  193gv_format(Format) :-
  194  gv_format_type(Format, _).
 gv_format_media_type(+Format:atom, +MediaType:media_type) is semidet
gv_format_media_type(+Format:atom, -MediaType:media_type) is semidet
gv_format_media_type(-Format:atom, +MediaType:media_type) is semidet
gv_format_media_type(-Format:atom, -MediaType:media_type) is multi
  203gv_format_media_type(Format1, MediaType) :-
  204  ground(Format1), !,
  205  gv_format_synonym__(Format1, Format2),
  206  gv_format_type__(Format2, _, MediaType).
  207gv_format_media_type(Format2, MediaType) :-
  208  gv_format_type__(Format1, _, MediaType),
  209  gv_format_synonym__(Format1, Format2).
 gv_format_type(+Format:atom, +Type:gv_type) is semidet
gv_format_type(+Format:atom, -Type:gv_type) is det
gv_format_type(-Format:atom, +Type:gv_type) is multi
gv_format_type(-Format:atom, -Type:gv_type) is nondet
  218gv_format_type(Format1, Type) :-
  219  call_det_when_ground(Format1, (
  220    gv_format_synonym_(Format1, Format2),
  221    gv_format_type_(Format2, Type)
  222  )).
  223
  224gv_format_synonym_(Format1, Format2) :-
  225  gv_format_synonym__(Format1, Format2).
  226gv_format_synonym_(Format, Format).
  227
  228gv_format_type_(Format, Type) :-
  229  gv_format_type__(Format, Type).
  230gv_format_type_(Format, Type) :-
  231  gv_format_type__(Format, Type, _).
  232
  233gv_format_type__(bmp, binary, media(image/bmp,[])).
  234% DOT, pretty-printed, no layout.
  235gv_format_type__(canon, text).
  236% CGImage, a drawable image object in Core Graphics (the low-level
  237% procedural drawing API for iOS and Mac OS X).
  238gv_format_type__(cgimage, binary).
  239% Client-side imagemap (deprecated).
  240gv_format_type__(cmap, text).
  241% Server-side and client-side imagemap.
  242gv_format_type__(cmapx, text).
  243% Server-side and client-side imagemap.
  244gv_format_type__(cmapx_np, text).
  245% JSON version of `-Txdot' without layout.
  246gv_format_type__(dot, text, media(text/'vnd.graphviz',[])).
  247% JSON version of `-Tdot' without layout.
  248gv_format_type__(dot_json, text, media(application/json,[])).
  249gv_format_type__(eps, binary, media(image/eps,[])).
  250gv_format_type__(exr, binary).
  251gv_format_type__(fig, text).
  252gv_format_type__(gd, text).
  253gv_format_type__(gd2, binary).
  254gv_format_type__(gif, binary, media(image/gif,[])).
  255gv_format_type__(gtk, viewer).
  256gv_format_synonym__(gv, dot).
  257gv_format_type__(ico, binary, media(image/'vnd.microsoft.icon')).
  258% Server-side and client-side imagemap.
  259gv_format_type__(imap, text).
  260gv_format_synonym__(imap_np, imap).
  261% Server-side and client-side imagemap (deprecated).
  262gv_format_type__(ismap, text).
  263gv_format_type__(jp2, binary, media(image/jp2,[])).
  264gv_format_synonym__(jpe, jpeg).
  265gv_format_type__(jpeg, binary, media(image/jpeg,[])).
  266gv_format_synonym__(jpg, jpeg).
  267% JSON version of `-Tdot'.
  268gv_format_type__(json, text, media(application/json,[])).
  269% JSON version of `-Txdot'.
  270gv_format_type__(json0, text, media(application/json,[])).
  271gv_format_type__(pct, binary, media(image/'x-pict',[])).
  272gv_format_type__(pdf, binary, media(application/pdf,[])).
  273gv_format_type__(pic, text).
  274gv_format_synonym__(pict, pic).
  275gv_format_type__(plain, text).
  276gv_format_synonym__('plain-ext', plain).
  277gv_format_type__(png, binary, media(image/png,[])).
  278gv_format_type__(pov, binary).
  279gv_format_type__(ps, binary, media(application/postscript,[])).
  280% PostScript output with PDF notations.
  281gv_format_type__(ps2, binary).
  282gv_format_type__(psd, binary, media(image/'vnd.adobe.photoshop',[])).
  283gv_format_type__(sgi, binary, media(image/sgi,[])).
  284gv_format_type__(svg, text, media(image/'svg+xml',[])).
  285gv_format_type__(svgz, binary, media(application/gzip,[])).
  286gv_format_type__(tga, binary, media(image/'x-targa',[])).
  287gv_format_synonym__(tif, tiff).
  288gv_format_type__(tiff, binary, media(image,tiff,[])).
  289gv_format_type__(tk, text).
  290gv_format_type__(vdx, text).
  291gv_format_type__(vml, text, media(application,'vnd.openxmlformats-officedocument.vmlDrawing',[])).
  292gv_format_type__(vmlz, binary).
  293gv_format_type__(vrml, text, media(model/vrml,[])).
  294gv_format_type__(wbmp, binary, media(image,'vnd.wap.wbmp',[])).
  295gv_format_type__(webp, binary, media(image/webp,[])).
  296gv_format_type__(x11, viewer).
  297gv_format_type__(xdot, text, media(text/'vnd.graphviz',[])).
  298gv_format_type__(xdot_json, text, media(application/json,[])).
  299gv_format_type__('xdot1.2', text, media(text/'vnd.graphviz',[])).
  300gv_format_type__('xdot1.4', text, media(text/'vnd.graphviz',[])).
  301gv_format_type__(xlib, viewer).
 gv_method(?Method:atom) is nondet
Layout methods supported by GraphViz.
  309gv_method(circo).
  310gv_method(dot).
  311gv_method(fdp).
  312gv_method(neato).
  313gv_method(osage).
  314gv_method(sfdp).
  315gv_method(twopi)