1:- module( wgraph, [
    2                        wgraph/2, wgraph/3,
    3                        wgraph_add_edges/3,
    4                        wgraph_add_vertices/3,
    5                        wgraph_adjacency/2,wgraph_adjacency/3,
    6                        wgraph_clique/2, wgraph_clique/4,
    7                        wgraph_known_cliques_replace/4,
    8                        wgraph_vertices/2,
    9                        wgraph_plot/2,
   10                        wgraph_ugraph/2,
   11                        wgraph_version/2
   12                ] 
   13                    ).   14
   15:- use_module( library(lib) ).   16:- lib(real).   17
   18:- lib(suggests(r(igraph))).   19:- lib(suggests(r(qgraph))).   20:- lib(suggests(r('GGally'))).   21:- lib(suggests(r(network))).   % silent required from GGally ? 
   22:- lib(suggests(r(sna))).       % silent required from GGally ? 
   23:- lib(suggests(r(svglite))).

Weighted graphs, with plotting function via Real

For now the emphasis is on plotting via igraph, qgraph and ggnet2, R libraries via Real.

A weighted graphs is represented as a list of From-To:W edges or Node entries for orphans.

See wgraph_plot/2.

author
- nicos angelopoulos
version
- 0.1 2015/6/12
- 0:2 2016/1/23
- 0.3 2017/3/12
- 0.4 2019/4/21
- 0.5 2019/5/8
license
- 0.6 2019/5/12

*/

 wgraph_version(-Version, -Date)
Version (Mj:Mn:Fx) and Date of publication (date(Y,M,D)).
 ?- wgraph_version( V, D ).
 V = 0:6:0
 D = date(2019,5,12)
   52wgraph_version( 0:6:0, date(2019,5,12) ).
   53
   54:- lib( source(wgraph), homonyms(true) ).   55:- lib(wgraph/2).   56:- lib(wgraph_plot/2).   57:- lib(wgraph_clique/2).   58:- lib(wgraph_ugraph/2).   59:- lib(wgraph_vertices/2).   60:- lib(wgraph_adjacency/2).   61:- lib(wgraph_add_edges/3).   62:- lib(wgraph_neighbours/3).   63:- lib(wgraph_add_vertices/3).   64:- lib(wgraph_known_cliques_replace/4 ).   65:- lib(end(wgraph)).