View source with raw comments or as raw
    1:- module(skos_graph,
    2	  [ skos_context_graph/3,	% +URI, -Graph, +Options
    3	    skos_node_shape/3		% +URI, -Shape, +Options
    4	  ]).    5:- use_module(cliopatria(hooks)).    6:- use_module(library(uri)).    7:- use_module(library(semweb/rdf_db)).    8:- use_module(library(semweb/rdfs)).    9:- use_module(library(semweb/rdf_abstract)).   10:- use_module(library(http/html_write)).   11:- use_module(library(lists)).   12:- use_module(components(label)).   13:- use_module(library(settings)).   14:- use_module(library(count)).

SKOS Context graphs

This module customises context graphs, both in how they are computed and in the rendering of the SKOS classes.

See also
- cliopatria(hooks) for a description of the hooks. */
   24% Use SVG context graphs
   25
   26:- set_setting_default(graphviz:format, svg).
 skos_context_graph(+URI, -Graph, +Options)
Compute the EDM context graph. This is currently defined to do a two-step breadth-first expansion of the graph from URI using the known EDM properties. Branching from a single node is limited to 20 and the total graph is not expanded beyond 100 nodes.
   35:- rdf_meta
   36	skos_relation(r),
   37	skos_class(r).   38
   39skos_context_graph(R, RDF, Options) :-
   40	option(style(skos), Options),
   41	bf_graph(R, 2, 100, 20, RDF0),
   42	minimise_graph(RDF0, RDF1),		% remove inverse/symmetric/...
   43	bagify_graph(RDF1, RDF2, Bags, []), 	% Create bags of similar resources
   44	append(RDF2, Bags, RDF),
   45	graph_resources(RDF, Resources, _Preds, _Types),
   46	include(skos_resource, Resources, EDMResources),
   47	EDMResources = [_,_|_].
 bf_graph(+Start, +MaxDist, +MaxEdges, +MaxBranch, -Graph)
   51bf_graph(Start, MaxDist, MaxEdges, MaxBranch, Graph) :-
   52	bf_graph_2([0-Start], MaxDist, MaxEdges, MaxBranch, [], Graph).
   53
   54bf_graph_2([], _, _, _, G, G) :- !.
   55bf_graph_2([D-_|_], MaxDist, _, _, G, G) :-
   56	D >= MaxDist, !.
   57bf_graph_2(AG0, MaxDist, MaxEdges, MaxBranch, G0, G) :-
   58	bf_expand(AG0, AG, MaxBranch, G1),
   59	(   G1 == []
   60	->  bf_graph_2(AG, MaxDist, MaxEdges, MaxBranch, G0, G)
   61	;   append(G1, G0, G2),
   62	    sort(G2, G3),
   63	    length(G3, Edges),
   64	    (   Edges >= MaxEdges
   65	    ->  G = G0
   66	    ;   bf_graph_2(AG, MaxDist, MaxEdges, MaxBranch, G3, G)
   67	    )
   68	).
   69
   70bf_expand([D-F|AG0], AG, MaxBranch, Triples) :-
   71	D1 is D + 1,
   72	Key = D1-Dst,
   73	answer_set(Key-Triple, related(F, Dst, Triple), MaxBranch, Pairs),
   74	pairs_keys_values(Pairs, Dsts, Triples),
   75	append(AG0, Dsts, AG).
   76
   77related(S, O, rdf(S,P,O)) :-
   78	skos_relation(Rel),
   79	rdf_has(S, Rel, O, P).
   80related(O, S, rdf(S,P,O)) :-
   81	skos_relation(Rel),
   82	rdf_has(S, Rel, O, P).
   83
   84skos_relation(skos:semanticRelation).
   85
   86
   87skos_resource(R) :-
   88	skos_class(Class),
   89	rdfs_individual_of(R, Class), !.
   90
   91skos_class(skos:'Concept').
 skos_node_shape(+URI, -Shape, +Options)
Realise EDM-specific vizualisation of nodes in the context-graph.
   99skos_node_shape(URI, Shape, Options) :-
  100	option(style(skos), Options),
  101	node_shape(URI, Shape, Options).
  102
  103node_shape(URI, Shape, Options) :-
  104	memberchk(start(URI), Options),
  105	Shape = [shape(tripleoctagon),style(filled),fillcolor('#ff85fd')]