View source with formatted comments or as raw
    1:- module(prophier, []).    2:- use_module(library(semweb/rdf_db)).    3:- use_module(library(assoc)).    4:- use_module(library(http/http_dispatch)).    5:- use_module(library(http/html_write)).    6
    7:- use_module(components(label)).	% Get rdf_link//1
    8:- use_module(cliopatria(hooks)).	% Declaration to extend the menu
    9
   10/** <module> Vizualize the RDF property hierarchy
   11
   12This program demonstrates simple data   processing and vizualization. In
   13order to process the request, we
   14
   15    1. compute the hierarchy as a Prolog datastructure (using
   16    property_tree/1). This allows for reuse, for example emitting the
   17    same datastructure as JSON, so we can do the rendering in Javscript
   18    at the client side.
   19
   20    2. emit the tree as a nested =ul= structure
   21
   22Finally, we can add it to the  ClioPatria   menu  by adding a clause for
   23cliopatria:menu_item/2.
   24
   25@tbd	Add style to make it look pretty.
   26*/
   27
   28% Make our predicate respond to /prophier
   29
   30:- http_handler(root(prophier), property_hierarchy, []).   31
   32% add our application to the Places  menu.   300  is the location in the
   33% menu (check cp_menu:menu_item/2 for the initial   menu). places is the
   34% popup and property_hierarchy is the identifier  of our handlers, which
   35% defaults to the predicate name. See http_handler/3 for details.
   36
   37cliopatria:menu_item(300=places/property_hierarchy, 'Predicate tree').
   38
   39%%	property_hierarchy(+Request)
   40%
   41%	HTTP Handler that emits the RDF   property hierarchy as a nested
   42%	=ul= tree where the properties are links to the ClioPatria local
   43%	view.
   44
   45property_hierarchy(_Request) :-
   46	property_tree(Tree),
   47	reply_html_page(cliopatria(default),
   48			title('Property hierarchy'),
   49			[ h1('RDF Property hierarchy'),
   50			  \emit_tree(Tree)
   51			]).
   52
   53
   54emit_tree([]) --> !.
   55emit_tree(List) -->
   56	html(ul(\emit_children(List))).
   57
   58emit_children([]) --> [].
   59emit_children([node(P,Children)|T]) -->
   60	html(li([ \rdf_link(P)		% Create link to local view
   61		| \emit_tree(Children)
   62		])),
   63	emit_children(T).
   64
   65
   66%%	property_tree(-List) is det.
   67%
   68%	Compute the entire property hierarchy for the RDF database. Most
   69%	of the complication is due to the fact that we need to take care
   70%	of possible loops in the property   hierarchy. For this purpose,
   71%	we use library(assoc) to maintain an   binary tree of predicates
   72%	we already expanded.
   73%
   74%	@param List is a list of terms node(Predicate, Children)
   75
   76property_tree(List) :-
   77	empty_assoc(Done0),
   78	findall(node(P, _), p_root(P), List),
   79	children(List, Done0, _Done).
   80
   81p_root(P) :-
   82	rdf_current_predicate(P),
   83	\+ rdf_has(P, rdfs:subPropertyOf, _).
   84
   85children([], Done, Done).
   86children([node(P, Children)|T], Done0, Done) :-
   87	(   get_assoc(P, Done0, _)	% Already in the tree
   88	->  Done = Done0
   89	;   put_assoc(P, Done0, true, Done1),
   90	    findall(node(P2, _), rdf_has(P2, rdfs:subPropertyOf, P), Children),
   91	    children(T, Done1, Done2),
   92	    children(Children, Done2, Done)
   93	)