1/* ontodot.pl 2 Author: Giménez, Christian. 3 4 Copyright (C) 2019 Giménez, Christian 5 6 This program is free software: you can redistribute it and/or modify 7 it under the terms of the GNU General Public License as published by 8 the Free Software Foundation, either version 3 of the License, or 9 at your option) any later version. 10 11 This program is distributed in the hope that it will be useful, 12 but WITHOUT ANY WARRANTY; without even the implied warranty of 13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the 14 GNU General Public License for more details. 15 16 You should have received a copy of the GNU General Public License 17 along with this program. If not, see <http://www.gnu.org/licenses/>. 18 19 11 oct 2019 20*/ 21 22 23:- module(ontodot, [ 24 load_ttl/1, 25 draw_all/1, 26 draw_graph/2, 27 draw_prefix/2, 28 draw_hierarchy/1, 29 list_nodes/1, 30 dot_all/1, 31 dot_prefix/2, 32 dot_graph/2, 33 dot_hierarchy/1 34 ]).
42:- use_module(library(semweb/turtle)). 43:- use_module(library(semweb/rdf11)). 44% :- ensure_loaded(library(semweb/rdf_db)). 45 46 47:- rdf_load(library(semweb/rdfs)). 48:- rdf_register_prefix(mm, 'http://mm.fi.uncoma.edu.ar/kb/journals#'). 49:- rdf_register_prefix(owl, 'http://www.w3.org/2002/07/owl#'). 50:- rdf_register_prefix(swrc, 'http://swrc.ontoware.org/ontology#').
This is an easy predicate for using the rdf_load/1 predicate.
62load_ttl(File) :-
63 rdf_default_graph(_Old, graph),
64 rdf_load(File).
In other words, return the Objects from the (Node, Pred, Object) tripples that appear in the graph. Prefer the abbreviated form of each Subject if it exists.
79get_objects(Node, Objects) :-
80 rdf_subject(Node),
81 findall((Node,B,C), rdf(Node, B, C), Objects).
In other words, return the Subjects from the (Subject, Pred, Node) tripples that appear in the graph. Prefer the abbreviated form of each Subject if it exists.
97get_subjects(Node, Subjects) :-
98 rdf_object(Node),
99 findall((A, B, Node), rdf(A, B, Node), Subjects).
In other words, return the Subjects from the (Subject, Pred, Node) tripples and the Objects from the (Node, Pred, Object) that appear in the graph. Prefer the abbreviated form of each Subject and Object if it exists.
115get_associated(Node, Associations) :-
116 rdf_global_id(Node, NodeAbbrv),
117 get_subjects(NodeAbbrv, Subjects),
118 get_objects(NodeAbbrv, Objects),
119 append(Subjects, Objects, Associations).
130get_isa_subjects(Node, Assocs) :-
131 rdf_object(Node),
132 findall((A,rdfs:subClassOf,Node),
133 rdf(A,rdfs:subClassOf,Node),
134 Assocs).
144get_isa_objects(Node, Assocs) :-
145 rdf_subject(Node),
146 findall((Node,rdfs:subClassOf,A),
147 rdf(Node,rdfs:subClassOf,A),
148 Assocs).
159get_isa(Node, Assocs) :-
160 rdf_global_id(Node, NodeAbbrv),
161 get_isa_subjects(NodeAbbrv, Assocs1),
162 get_isa_objects(NodeAbbrv, Assocs2),
163 append(Assocs1, Assocs2, Assocs).
Return the prefix:suffix form of Name if it exists, if not, return the IRI.
176abbrev_name(Name, Abbrev) :- 177 rdf_global_id(Abbrev, Name), !. 178abbrev_name(Name, Name).
Generate a dot graph node of the given RDF graph Node. Change the representation according to the type of the node.
If it is a datatype (is not an IRI), use a box node. If it is an IRI, use an ellipse node.
195draw_node(Node, Str) :- 196 \+ rdf_is_iri(Node), !, 197 format(string(Str), '"~w" [shape=box, color=blue];', [Node]). 198draw_node(Node, Str) :- 199 abbrev_name(Node, Name), 200 (Name = owl:_Suffix ; Name = rdf:_Suffix ; Name = rdfs:_Suffix), !, 201 format(string(Str), '"~w" [color=red, shape=ellipse];', [Name]). 202draw_node(Node, Str) :- 203 rdf(Node, rdf:type, owl:'NamedIndividual'),!, 204 abbrev_name(Node, Name), 205 format(string(Str), '"~w" [color=blue];', [Name]). 206draw_node(Node, Str) :- 207 rdf(Node, rdf:type, owl:'Class'),!, 208 abbrev_name(Node, Name), 209 format(string(Str), '"~w" [shape=ellipse];', [Name]). 210draw_node(Node, Str) :-
212 abbrev_name(Node, Name), 213 format(string(Str), '"~w" [shape=box, color=blue];', [Name])
213. 214
Use the Triple to create a dot representation of the edge of the graph. The node dot string is generated with draw_node/1.
226draw_edge((A, B, C), Str) :- 227 abbrev_name(B, rdfs:subClassOf), 228 abbrev_name(A, A2), 229 abbrev_name(C, C2), 230 format( 231 string(Str), 232 'edge [label="~w", style=solid, arrowhead=none] "~w" -> "~w";\n', 233 [rdfs:subclassOf, A2, C2]). 234draw_edge((A, B, C), Str) :- 235 abbrev_name(A, A2), 236 abbrev_name(B, B2), 237 abbrev_name(C, C2), 238 format( 239 string(Str), 240 'edge [label="~w", style=dashed, arrowhead=normal] "~w" -> "~w";\n', 241 [B2, A2, C2]).
251draw_edges_noprops([], "") :- !. 252draw_edges_noprops([(_A, _B, C)|Rest], Str) :- 253 % Ignore if it is an IRI, is probably a property. 254 \+ rdf_is_iri(C), !,
255 draw_edges_noprops(Rest, Str)
255. 256draw_edges_noprops([Edge|Rest], Str) :- 257 draw_edge(Edge, Str), 258 draw_edges_noprops(Rest, RestStr), 259 string_concat(Str, RestStr, Str).
268draw_edges([], "") :- !. 269draw_edges([Assoc|Rest], Str) :- 270 draw_edge(Assoc, EdgeStr), 271 draw_edges(Rest, RestStr), 272 string_concat(EdgeStr, RestStr, Str).
Use the subject and object nodes only.
285draw_nodes([], "") :- !. 286draw_nodes([(S, _P, O)|Rest], Str) :- 287 draw_node(S, SubjectStr), 288 draw_node(O, ObjectStr), 289 290 draw_nodes(Rest, NodesStr), 291 292 format(string(Str), '~s~n~s~n~s', 293 [SubjectStr, ObjectStr, NodesStr]).
Generate all associations related to the give Node (all subjects and objects related to it).
307draw_graph(Node, Str) :-
308 get_associated(Node, Assocs),
309
310 draw_nodes(Assocs, NodesStr),
311 draw_edges(Assocs, EdgesStr),
312
313 format(string(Str),
314 'digraph {~n~s~n~n~s}~n',
315 [NodesStr,EdgesStr]).
Use findall/3 for searching all the nodes in the graph in its abbreviated form. The prefix is obtained according to the registered ones. Use rdf_register_prefix/2 to register new prefixes.
330abbrev_nodes(Node) :-
331 rdf_iri(Node1),
332 rdf_node(Node1),
333 abbrev_name(Node1, Node).
Return all the nodes in the RDF graph in its abbreviated form. The current registered prefixes are used for making abbreviations. */
344list_nodes(Nodes) :-
345 findall(Node, abbrev_nodes(Node), Nodes).
352get_all_assocs([], []) :- !. 353get_all_assocs([Node|NRest], Lst) :- 354 get_all_assocs(NRest, Lst1), 355 (get_associated(Node, Assocs); Assocs = []), 356 append(Assocs, Lst1, Lst).
Assocs will have an is-a relationship whose each node is a parent or child of other node.
371get_all_isa([], []) :- !. 372get_all_isa([Node|NRest], Lst) :- 373 get_all_isa(NRest, Lst1), 374 (get_isa(Node, Assocs); Assocs = []), 375 append(Assocs, Lst1, Lst).
Generate a dot representation of the default RDF graph. To improve readability, property objects are not represented associated with the other subjects. See draw_edges_noprops/1 for more information.
This predicate can be used with load_ttl/1. For instance:
?- load_ttl('my_kb.ttl'), draw_all(Str).
392draw_all(Str) :-
393 list_nodes(Nodes),
394 get_all_assocs(Nodes, Assocs),
395
396 draw_nodes(Assocs, NodesStr),
397 draw_edges_noprops(Assocs, EdgesStr),
398
399 format(string(Str),
400 'digraph {~n~s~n~n~s}~n',
401 [NodesStr, EdgesStr]).
413nodes_with_prefix(Prefix, Nodes) :-
414 list_nodes(AllNodes),
415 findall(Prefix:Name, member(Prefix:Name, AllNodes), Nodes).
426draw_prefix(Prefix, Str) :-
427 nodes_with_prefix(Prefix, Nodes),
428 get_all_assocs(Nodes, Assocs),
429
430 draw_nodes(Assocs, NodesStr),
431 draw_edges(Assocs, EdgesStr),
432
433 format(
434 string(Str),
435 'digraph {~n~s~n~n~s}~n',
436 [NodesStr, EdgesStr]).
445draw_hierarchy(Str) :-
446 list_nodes(AllNodes),
447 get_all_isa(AllNodes, Assocs),
448
449 draw_nodes(Assocs, NodesStr),
450 draw_edges(Assocs, EdgesStr),
451
452 format(
453 string(Str),
454 'digraph {~n~s~n~n~s}~n',
455 [NodesStr, EdgesStr]).
The type of the image to generate is determined by the File name extension.
468prepare_cmd(File, Stream) :-
469 file_name_extension(_Base, Type, File),
470 dot_command(Type, File, CMD),
471 open(pipe(CMD), write, Stream).
484dot_command(Type, File, CMD) :-
485 format(atom(CMD), 'dot -T~s -o \'~w\'', [Type, File]).
The image type is deduce by the File extension. 'example.png
' will create a PNG
image.
498dot_graph(Node, File) :-
499 prepare_cmd(File, Stream),
500 draw_graph(Node, Str),
501 write(Stream, Str),
502 close(Stream).
The image type is deduce by the File extension. 'example.png
' will create a PNG
image.
514dot_all(File) :-
515 prepare_cmd(File, Stream),
516 draw_all(Str),
517 write(Stream, Str),
518 close(Stream).
The image type is deduce by the File extension. 'example.png
' will create a PNG
image.
532dot_prefix(Prefix, File) :-
533 prepare_cmd(File, Stream),
534 draw_prefix(Prefix, Str),
535 write(Stream, Str),
536 close(Stream).
The image type is deduce by the File extension. 'example.png
' will create a PNG
image.
548dot_hierarchy(File) :-
549 prepare_cmd(File, Stream),
550 draw_hierarchy(Str),
551 write(Stream, Str),
552 close(Stream)
Graph KB: Make graphs with the input ontology.