Skip to content

Commit b849a00

Browse files
committed
Use the ASCII ID predicate and Media Type type from PLC.
1 parent 2409c8b commit b849a00

File tree

4 files changed

+16
-43
lines changed

4 files changed

+16
-43
lines changed

example/parse_tree.pl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
:- use_module(library(yall)).
99

1010
:- use_module(library(gv)).
11+
:- use_module(library(term_ext)).
1112

1213
export :-
1314
tree(Tree),
@@ -27,7 +28,7 @@
2728

2829
export_tree_(Out, Tree, Id) :-
2930
Tree =.. [Op|Trees],
30-
dot_id(Id),
31+
ascii_id(Id),
3132
dot_node_id(Out, Id, [label(Op)]),
3233
maplist(export_tree_(Out), Trees, Ids),
3334
maplist(dot_edge_id(Out, Id), Ids).

prolog/dot.pl

Lines changed: 9 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,6 @@
2020
dot_graph/2, % +Out, :Goal_1
2121
dot_graph/3, % +Out, :Goal_1, +Options
2222
dot_html_replace/2, % +Unescaped, -Escaped
23-
dot_id/1, % -Id
24-
dot_id/2, % +Term, -Id
2523
dot_node/2, % +Out, +Term
2624
dot_node/3, % +Out, +Term, +Options
2725
dot_node_id/2, % +Out, +Id
@@ -37,14 +35,13 @@
3735

3836
:- use_module(library(apply)).
3937
:- use_module(library(error)).
40-
:- use_module(library(uuid)).
4138
:- use_module(library(yall)).
4239

4340
:- use_module(library(dcg)).
4441
:- use_module(library(dict)).
4542
:- use_module(library(debug_ext)).
4643
:- use_module(library(file_ext)).
47-
:- use_module(library(hash_ext)).
44+
:- use_module(library(term_ext)).
4845

4946
:- use_module(dot_html).
5047

@@ -74,14 +71,14 @@
7471
% preferable. However, there are legitimate use cases where the
7572
% programmer would like to generate and use the DOT IDs herself.
7673
% For these purposes, dot_arc_id/[3,4] can be used -- in
77-
% combination with dot_id/2 -- instead.
74+
% combination with ascii_id/2 -- instead.
7875

7976
dot_arc(Out, FromTerm, ToTerm) :-
8077
dot_arc(Out, FromTerm, ToTerm, options{}).
8178

8279

8380
dot_arc(Out, FromTerm, ToTerm, Options) :-
84-
maplist(dot_id, [FromTerm,ToTerm], [FromId,ToId]),
81+
maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
8582
dot_arc_id(Out, FromId, ToId, Options).
8683

8784

@@ -163,7 +160,7 @@
163160

164161

165162
dot_cluster(Out, Term, Goal_1, Options) :-
166-
dot_id(Term, Id),
163+
ascii_id(Term, Id),
167164
dot_cluster_id(Out, Id, Goal_1, Options).
168165

169166

@@ -176,7 +173,7 @@
176173

177174

178175
dot_cluster_arc(Out, FromTerm, ToTerm, Options) :-
179-
maplist(dot_id, [FromTerm,ToTerm], [FromId,ToId]),
176+
maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
180177
dot_cluster_arc_id(Out, FromId, ToId, Options).
181178

182179

@@ -227,14 +224,14 @@
227224
% preferable. However, there are legitimate use cases where the
228225
% programmer would like to generate and use the DOT IDs
229226
% themselves. For these purposes, dot_edge_id/[3,4] can be used
230-
% -- in combination with dot_id/2 -- instead.
227+
% -- in combination with ascii_id/2 -- instead.
231228

232229
dot_edge(Out, FromTerm, ToTerm) :-
233230
dot_edge(Out, FromTerm, ToTerm, options{}).
234231

235232

236233
dot_edge(Out, FromTerm, ToTerm, Options) :-
237-
maplist(dot_id, [FromTerm,ToTerm], [FromId,ToId]),
234+
maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
238235
dot_edge_id(Out, FromId, ToId, Options).
239236

240237

@@ -348,31 +345,6 @@
348345

349346

350347

351-
%! dot_id(-Id:atom) is det.
352-
353-
dot_id(Id) :-
354-
uuid(Id0, [format(integer)]),
355-
atom_concat(n, Id0, Id).
356-
357-
358-
359-
%! dot_id(+Term:term, -Id:atom) is det.
360-
%
361-
% Create a DOT ID that can be used to represent a Prolog term in the
362-
% DOT language. When the same Prolog term is supplied, the DOT ID is
363-
% also the same.
364-
365-
dot_id(Term, Id) :-
366-
% DOT IDs cannot contain all characters allowed in Prolog terms.
367-
% Also, Prolog terms can have arbitrary length. For these reasons,
368-
% we calculate the MD5 hash of a serialization of the Prolog term.
369-
md5(Term, Hash),
370-
% DOT IDs must start with an ASCII letter. Since an MD5 hash may
371-
% start with a decimal digit, an specific ASCII letter is prefixed.
372-
atomic_concat(n, Hash, Id).
373-
374-
375-
376348
%! dot_node(+Out:stream, +Term:term) is det.
377349
%! dot_node(+Out:stream, +Term:term, +Options:options) is det.
378350
%
@@ -400,14 +372,14 @@
400372
% preferable. However, there are legitimate use cases where the
401373
% programmer would like to generate and use the DOT IDs
402374
% themselves. For these purposes, dot_node_id/[2,3] can be used --
403-
% in combination with dot_id/2 -- instead.
375+
% in combination with ascii_id/2 -- instead.
404376

405377
dot_node(Out, Term) :-
406378
dot_node(Out, Term, options{label: Term}).
407379

408380

409381
dot_node(Out, Term, Options) :-
410-
dot_id(Term, Id),
382+
ascii_id(Term, Id),
411383
dot_node_id(Out, Id, Options).
412384

413385

prolog/gv.pl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -195,10 +195,10 @@
195195

196196

197197

198-
%! gv_format_media_type(+Format:atom, +MediaType:compound) is semidet.
199-
%! gv_format_media_type(+Format:atom, -MediaType:compound) is semidet.
200-
%! gv_format_media_type(-Format:atom, +MediaType:compound) is semidet.
201-
%! gv_format_media_type(-Format:atom, -MediaType:compound) is multi.
198+
%! gv_format_media_type(+Format:atom, +MediaType:media_type) is semidet.
199+
%! gv_format_media_type(+Format:atom, -MediaType:media_type) is semidet.
200+
%! gv_format_media_type(-Format:atom, +MediaType:media_type) is semidet.
201+
%! gv_format_media_type(-Format:atom, -MediaType:media_type) is multi.
202202

203203
gv_format_media_type(Format1, MediaType) :-
204204
ground(Format1), !,

test/test_graphviz.pl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@
4343

4444
export_tree_(Out, Tree, Id) :-
4545
Tree =.. [Op|Trees],
46-
dot_id(Id),
46+
ascii_id(Id),
4747
dot_node_id(Out, Id, [label(Op)]),
4848
maplist(export_tree_(Out), Trees, Ids),
4949
maplist(dot_edge_id(Out, Id), Ids).

0 commit comments

Comments
 (0)