1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2013, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(graphml_ugraph,
   31	  [ graphml_write_ugraph/4,	% +Out, +Map, +Keys, +UGraph
   32	    ugraph_xml_dom/4		% :Map, +Keys, +UGraph, -DOM
   33	  ]).   34:- use_module(library(ugraphs)).   35:- use_module(library(sgml_write)).   36:- use_module(library(assoc)).   37:- use_module(library(error)).   38:- use_module(library(lists)).   39
   40:- meta_predicate
   41	graphml_write_ugraph(+,3,+,+),
   42	ugraph_xml_dom(3,+,+,-).

Convert Prolog ugraph into GraphML

*/

 graphml_write_ugraph(+Out, +Map, +Keys, +UGraph) is det
   51graphml_write_ugraph(Out, Map, Keys, UGraph) :-
   52	ugraph_xml_dom(Map, Keys, UGraph, DOM),
   53	Options = [],
   54	(   is_stream(Out)
   55	->  xml_write(Out, DOM, Options)
   56	;   setup_call_cleanup(
   57		open(Out, write, Stream, [encoding(utf8)]),
   58		xml_write(Stream, DOM, Options),
   59		close(Stream))
   60	).
 ugraph_xml_dom(:Map, +Keys, +UGraph, -DOM) is det
Convert a ugraph into an GraphML DOM.
Arguments:
Map- is a called as call(:Map, +KeyName, +Obj, -KeyValue) and must be semidet. For nodes, Obj is a term node(Node) for edges, it is a term edge(From, To). The reserved key id is used to query an identifier for nodes and edges. If this fails, the nodes and edges are numbered n<N> and e<N>.
Is- a list key(For, KeyName, KeyType).
Ugraph- is a ugraph as defined in library(ugraph)
DOM- is a Prolog XML DOM that can be handed to xml_write/3 to create a GraphML document.
   78ugraph_xml_dom(Map, Keys, Ugraph,
   79	       element(graphml,
   80		       [ xmlns='http://graphml.graphdrawing.org/xmlns',
   81			 'http://www.w3.org/2001/XMLSchema-instance':
   82			 schemaLocation =
   83			 'http://graphml.graphdrawing.org/xmlns/1.0/graphml.xsd'
   84		       ],
   85		       DOM)) :-
   86	key_dom(Keys, KeyDOM, NodeKeys, EdgeKeys),
   87	append(KeyDOM, [ element(graph,
   88				 [ id='G', edgedefault=directed
   89				 ],
   90				 NodeDOM)
   91		       ],
   92	       DOM),
   93	vertices(Ugraph, Vertices),
   94	node_dom(Vertices, Map, NodeKeys, NodeMap, NodeDOM, EdgeDom),
   95	edges(Ugraph, Edges),
   96	edge_dom(Edges, Map, EdgeKeys, NodeMap, EdgeDom).
 key_dom(+Keys, -KeyDom, -NodeKeys, -EdgeKeys) is det
Generate the DOM for the key declarations and split the set into two: NodeKeys and EdgeKeys.

Note that the keys are named k0, k1, ... because Gephi maps d3 to the label, no matter what you do (Gephi 0.8.2).

Arguments:
NodeKeys- and EdgeKeys are lists with terms key(KeyName, KeyType, Id)
  109key_dom(Keys, KeyDOM, NodeKeys, EdgeKeys) :-
  110	key_dom(Keys, KeyDOM, 0, NodeKeys, EdgeKeys).
  111
  112key_dom([], [], _, [], []).
  113key_dom([key(For, KeyName, KeyType)|Keys],
  114	[element(key,
  115		 [id=Id, for=For, 'attr.name'=KeyName, 'attr.type'=KeyType],
  116		 [])|DOM],
  117	N0, NodeKeys, EdgeKeys) :-
  118	must_be(oneof([boolean, int, long, float, double, string]), KeyType),
  119	succ(N0, N),
  120	atomic_list_concat([k, N0], Id),
  121	KeyTerm = key(KeyName, KeyType, Id),
  122	(   For == node
  123	->  NodeKeys = [KeyTerm|NodeKeysT],
  124	    key_dom(Keys, DOM, N, NodeKeysT, EdgeKeys)
  125	;   For == edge
  126	->  EdgeKeys = [KeyTerm|EdgeKeysT],
  127	    key_dom(Keys, DOM, N, NodeKeys, EdgeKeysT)
  128	;   must_be(oneof([node,edge]), For)
  129	).
 node_dom(+Vertices, :Map, +NodeKeys, -NodeMap, NodeDOM, -Tail)
  133node_dom(Vertices, Map, NodeKeys, NodeMap, NodeDOM, Tail) :-
  134	empty_assoc(NodeMap0),
  135	node_dom(Vertices, Map, NodeKeys, 0, NodeMap0, NodeMap, NodeDOM, Tail).
  136
  137node_dom([], _, _, _, NodeMap, NodeMap, DOM, DOM).
  138node_dom([V0|VT], Map, NodeKeys, IdI, NodeMap0, NodeMap,
  139	 [element(node, [id=Id], Data)|DOM0], DOM) :-
  140	node_data(NodeKeys, Map, node(V0), Data),
  141	(   call(Map, id, node(V0), Id)
  142	->  IdI1 = IdI
  143	;   atomic_list_concat([n, IdI], Id),
  144	    succ(IdI, IdI1)
  145	),
  146	put_assoc(V0, NodeMap0, Id, NodeMap1),
  147	node_dom(VT, Map, NodeKeys, IdI1, NodeMap1, NodeMap, DOM0, DOM).
  148
  149node_data([], _, _, []).
  150node_data([key(Name, _Type, Id)|Keys], Map, V, Data) :-
  151	(   call(Map, Name, V, Value)
  152	->  Data = [element(data, [key=Id], [Value])|DataT]
  153	;   Data = DataT
  154	),
  155	node_data(Keys, Map, V, DataT).
 edge_dom(+Edges, :Map, +EdgeKeys, +NodeMap, -EdgeDom)
  159edge_dom(Edges, Map, EdgeKeys, NodeMap, EdgeDom) :-
  160	edge_dom(Edges, Map, 0, EdgeKeys, NodeMap, EdgeDom).
  161
  162edge_dom([], _, _, _, _, []).
  163edge_dom([F-T|Edges], Map, IdI, EdgeKeys, NodeMap,
  164	 [ element(edge, [id=Id, source=FID, target=TID], Data)
  165	 | EdgeDom
  166	 ]) :-
  167	(   get_assoc(F, NodeMap, FID)
  168	->  true
  169	;   print_message(error, graphml(no_node(F))),
  170	    FID = 'ERROR'
  171	),
  172	(   get_assoc(T, NodeMap, TID)
  173	->  true
  174	;   print_message(error, graphml(no_node(T))),
  175	    TID = 'ERROR'
  176	),
  177	(   call(Map, id, edge(F,T), Id)
  178	->  IdI1 = IdI
  179	;   atomic_list_concat([e, IdI], Id),
  180	    succ(IdI, IdI1)
  181	),
  182	node_data(EdgeKeys, Map, edge(F,T), Data),
  183	edge_dom(Edges, Map, IdI1, EdgeKeys, NodeMap, EdgeDom).
  184
  185
  186:- multifile
  187	prolog:message//1.  188
  189prolog:message(graphml(no_node(Node))) -->
  190	[ 'No ID for node ~q'-[Node] ]