1:- module(
    2  gml,
    3  [
    4    gml_edge/3,  % +Out, +FromTerm, +ToTerm
    5    gml_edge/4,  % +Out, +FromTerm, +ToTerm, +Options
    6    gml_graph/2, % +Out, :Goal_1
    7    gml_graph/3, % +Out, :Goal_1, +Options
    8    gml_node/2,  % +Out, +Term
    9    gml_node/3   % +Out, +Term, +Options
   10  ]
   11).

Support for the Graph Markup Language (GML)

GML ::= List
List ::= (whitespace * Key whitespace + Value) *
Value ::= Integer | Real | String | [ List ]
Key ::= [ a-z A-Z ] [ a-z A-Z 0-9 ] *
Integer ::= sign digit +
Real ::= sign digit * . digit * mantissa
String ::= " instring "
sign ::= empty | + | -
digit ::= [0-9]
Mantissa ::= empty | E sign digit
instring ::= ASCII - {&,"} | & character + ;
whitespace ::= space | tabulator | newline

*/

   32:- use_module(library(apply)).   33
   34:- use_module(library(call_ext)).   35:- use_module(library(dcg)).   36:- use_module(library(dict)).   37:- use_module(library(file_ext)).   38:- use_module(library(debug_ext)).   39:- use_module(library(hash_ext)).   40:- use_module(library(term_ext)).   41
   42:- meta_predicate
   43    gml_graph(+, 1),
   44    gml_graph(+, 1, +).
 gml_attributes(+Options:options, -String:string) is det
   52gml_attributes(Options, String) :-
   53  dict_pairs(Options, Pairs),
   54  maplist(gml_attribute_, Pairs, Strings),
   55  atomics_to_string(Strings, " ", String).
   56
   57gml_attribute_(Key-Value1, String) :-
   58  number(Value1), !,
   59  format(string(String), "~a ~w", [Key,Value1]).
   60gml_attribute_(Key-Value, String) :-
   61  %(   Key == label
   62  %->  string_phrase(gml_encode_label, Value1, Value2)
   63  %;   Value2 = Value1
   64  %),
   65  format(string(String), "~a \"~w\"", [Key,Value]).
 gml_edge(+Out:ostream, +FromTerm:term, +ToTerm:term) is det
 gml_edge(+Out:ostream, +FromTerm:term, +ToTerm:term, +Options:options) is det
   72gml_edge(Out, FromTerm, ToTerm) :-
   73  gml_edge(Out, FromTerm, ToTerm, options{}).
   74
   75
   76gml_edge(Out, FromTerm, ToTerm, Options) :-
   77  maplist(ascii_id, [FromTerm,ToTerm,FromTerm-ToTerm], [FromId,ToId,Id]),
   78  gml_attributes(Options, String),
   79  format_debug(gml, Out, "  edge [ id \"~a\" source \"~a\" target \"~a\" ~s ]", [Id,FromId,ToId,String]).
 gml_graph(+Out:ostream, :Goal_1) is det
 gml_graph(+Out:ostream, :Goal_1, +Options:options) is det
Arguments:
Options- The following options are supported:
directed(+boolean)
Whether the graph is directed (true) or undirected (false, default).
   93gml_graph(Out, Goal_1) :-
   94  gml_graph(Out, Goal_1, options{}).
   95
   96
   97gml_graph(Out, Goal_1, Options) :-
   98  dict_get(directed, false, Options, Directed),
   99  must_be(boolean, Directed),
  100  boolean_value(Directed, DirectedN),
  101  format_debug(gml, Out, "graph [ directed ~d", [DirectedN]),
  102  call(Goal_1, Out),
  103  format_debug(gml, Out, "]").
 gml_node(+Out:ostream, +Term:term) is det
 gml_node(+Out:ostream, +Term:term, +Options:options) is det
  110gml_node(Out, Term) :-
  111  gml_node(Out, Term, []).
  112
  113
  114gml_node(Out, Term, Options) :-
  115  ascii_id(Term, Id),
  116  gml_attributes(Options, String),
  117  format_debug(gml, Out, "  node [ id \"~a\" ~s ]", [Id,String]).
  118
  119
  120
  121
  122
  123% HELPERS %
 boolean_value(+Directed:boolean, +N:between(0,1)) is semidet
boolean_value(+Directed:boolean, -N:between(0,1)) is det
boolean_value(-Directed:boolean, +N:between(0,1)) is det
boolean_value(-Directed:boolean, -N:between(0,1)) is multi
  130boolean_value(false, 0).
  131boolean_value(true, 1)