View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010, University of Amsterdam,
    7		   VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(c_cpack,
   32	  [ package_table//1,		% +Options
   33	    cpack//2,			% +Pack, +Options
   34	    cpack_status_icon//1,	% +Pack
   35	    cpack_link//1,		% +Resource
   36	    cpack_prop//2,		% +Resource, +Prop
   37	    commit_info//3,		% +Record, +Body, +Options
   38	    current_package/2		% -Package, +Options
   39	  ]).   40:- include(bundle(html_page)).
   41:- use_module(user(user_db)).   42:- use_module(library(http/http_path)).   43:- use_module(library(dcg/basics)).   44:- use_module(library(cpack/repository)).   45:- use_module(library(cpack/dependency)).   46:- use_module(library(semweb/rdf_db)).   47:- use_module(library(semweb/rdfs)).   48:- use_module(library(semweb/rdf_label)).   49:- use_module(library(pldoc/doc_wiki)).   50:- use_module(library(pldoc/doc_html)).   51:- use_module(components(label)).   52:- use_module(cliopatria(hooks)).   53:- use_module('cpack/graphs').

CPACK HTML components

This module defines vizualisation primitives for CPACK resources. It also hooks the local-view of ClioPatria to provide nicer pages for instances of CPACK objects such as cpack:Package.

To be done
- Use PlDoc Wiki for rendering the description. Should that be yet another package? */
 cliopatria:list_resource(+Pack)//
Hook the ClioPatria local view page to create a more sensible represention of a package.
   70cliopatria:list_resource(Pack) -->
   71	{ rdfs_individual_of(Pack, cpack:'Package') },
   72	cpack(Pack, []).
   73cliopatria:list_resource(Pack) -->
   74	{ rdfs_individual_of(Pack, cpack:'File') },
   75	cpack_file(Pack, []).
 package_table(Options)// is det
Emit a table that describes Packages. Options supported:
sort_by(Column)
Sort table by given column.
   85package_table(Options) -->
   86	{ option(sort_by(By), Options, name),
   87	  findall(Package, current_package(Package, Options), List),
   88	  sort(List, ListUniq),
   89	  sort_packages(By, ListUniq, Packages)
   90	},
   91	html_requires(css('cpack.css')),
   92	html(table(class(block),
   93		   [ tr([ \sort_th(status, By, 'OK?'),
   94			  \sort_th(name,   By, 'Name'),
   95			  \sort_th(title,  By, 'Title'),
   96			  \sort_th(type,   By, 'Type'),
   97			  \sort_th(author, By, 'Author'),
   98			  \sort_th(date,   By, 'Date')
   99			])
  100		   | \package_rows(Packages, 1, Options)
  101		   ])).
  102
  103current_package(Package, Options) :-
  104	(   option(user(User), Options)
  105	->  rdf_has(Package, cpack:submittedBy, User)
  106	;   true
  107	),
  108	rdfs_individual_of(Package, cpack:'Package').
  109
  110
  111package_rows([], _, _) --> [].
  112package_rows([H|T], Row, Options) -->
  113	odd_even_row(Row, Next, \package_row(H, Options)),
  114	package_rows(T, Next, Options).
  115
  116package_row(Package, _Options) -->
  117	html([ td(class(status),
  118		  \cpack_status_icon(Package)),
  119	       td(class(name),
  120		  \cpack_link(Package)),
  121	       td(class(title),
  122		  div(\cpack_prop(Package, dcterms:title))),
  123	       td(class(type),
  124		  div(\cpack_prop(Package, rdf:type))),
  125	       td(class(author),
  126		  div(\cpack_prop(Package, cpack:author))),
  127	       td(class(date),
  128		  div(\cpack_prop(Package, cpack:submittedDate)))
  129	     ]).
 sort_packages(By, Packs, Sorted)
Sort a list of packages by the key By.
  136sort_packages(Key, Packs, Sorted) :-
  137	map_list_to_pairs(cpack_sort_key(Key), Packs, Keyed),
  138	keysort(Keyed, KeySorted),
  139	pairs_values(KeySorted, Sorted0),
  140	(   Key == date % sort on date by most recent first
  141	->  reverse(Sorted0, Sorted)
  142	;   Sorted = Sorted0
  143	).
 cpack_sort_key(+KeyName, +CPACK, -KeyValue) is det
KeyValue is a sort-key for sorting package by KeyName.
  149cpack_sort_key(status, Pack, Status) :-
  150	(   package_problem(Pack, _Problem)
  151	->  Status = bad
  152	;   Status = good
  153	).
  154cpack_sort_key(name, Pack, Key) :-
  155	rdf_display_label(Pack, Name),
  156	collation_key(Name, Key).
  157cpack_sort_key(title, Pack, Key) :-
  158	(   rdf_has(Pack, dcterms:title, Literal)
  159	->  literal_text(Literal, Title),
  160	    collation_key(Title, Key)
  161	;   collation_key('', Key)
  162	).
  163cpack_sort_key(type, Pack, Key) :-
  164	(   rdf_has(Pack, rdf:type, Type)
  165	->  rdf_display_label(Type, Label),
  166	    collation_key(Label, Key)
  167	;   Key = ''
  168	).
  169cpack_sort_key(author, Pack, Key) :-
  170	(   rdf_has(Pack, cpack:author, Author)
  171	->  (   rdf_has(Author, foaf:name, Literal)
  172	    ->  literal_text(Literal, Title),
  173		collation_key(Title, Key)
  174	    ;   Key = Author
  175	    )
  176	;   Key = ''
  177	).
  178cpack_sort_key(date, Pack, Key) :-
  179	(   rdf_has(Pack, cpack:submittedDate, Key)
  180	->  true
  181	;   Key = ''
  182	).
  183
  184
  185		 /*******************************
  186		 *	      PACKAGE		*
  187		 *******************************/
 cpack(+Pack, +Options)// is det
Display information about Pack.
  193cpack(Pack, _Options) -->
  194	{ rdf_has(Pack, cpack:name, literal(Name)),
  195	  package_status(Pack, Problems)
  196	},
  197	html_requires(css('cpack.css')),
  198	html(div(class(cpack),
  199		 [ h2([ 'Package "', Name, '" -- ',
  200			\cpack_prop(Pack, dcterms:title),
  201			span([class(status), style('float:right')],
  202			     [ \cpack_update_icon(Pack),
  203			       \cpack_status_icon(Pack, Problems)
  204			     ])
  205		      ]),
  206		   table(class(infobox),
  207			 [ \p_row(Pack, rdf:type),
  208			   \p_row(Pack, cpack:home),
  209			   \p_row(Pack, cpack:author),
  210			   \p_row(Pack, cpack:submittedBy),
  211			   \p_row(Pack, cpack:submittedDate),
  212			   \p_row(Pack, cpack:requires),
  213			   \p_row(Pack, cpack:clonedRepository),
  214			   \p_row(Pack, cpack:mirrorRepository),
  215			   \install_url_row(Pack)
  216			 ]),
  217		   br([class('after-ptable')]),
  218		   div(class(description),
  219		       \cpack_wiki(Pack, cpack:description)),
  220		   br(clear(all)),
  221		   \cpack_issues(Pack, Problems),
  222		   \git_shortlog(Pack, [limit(5)]),
  223		   h3('Files in package'),
  224		   \files_in_pack(Pack),
  225		   \cpack_dependency_graph(Pack, [])
  226		 ])).
 install_url_row(+Pack)//
  231install_url_row(Pack) -->
  232	{ rdf_has(Pack, cpack:packageName, literal(Name)),
  233	  cpack_uri(pack, Name, URL)
  234	},
  235	html(tr([th('Install URL:'), td(a(href(URL), URL))])).
 git_shortlog(+Pack, +Options)//
Component that show the top-N most recent changes in Pack.
  243git_shortlog(Pack, Options) -->
  244	{ cpack_log(Pack, ShortLog, Options) },
  245	html([ h3('Recent changes'),
  246	       table(class(git_shortlog),
  247		     \shortlog_rows(ShortLog, Pack, 1))
  248	     ]).
  249
  250shortlog_rows([], _, _) --> [].
  251shortlog_rows([H|T], Pack, Row) -->
  252	odd_even_row(Row, Next, \shortlog_row(H, Pack)),
  253	shortlog_rows(T, Pack, Next).
  254
  255shortlog_row(Record, Pack) -->
  256	html([ \td_git_log(Pack, author_date_relative, Record),
  257	       \td_git_log(Pack, author_name, Record),
  258	       \td_git_log(Pack, subject_and_refnames, Record)
  259	     ]).
  260
  261td_git_log(Pack, subject_and_refnames, Record) --> !,
  262	{ git_log_data(subject, Record, Subject),
  263	  git_log_data(ref_names, Record, RefNames),
  264	  git_log_data(commit_hash, Record, Commit),
  265	  http_link_to_id(git_show, [a(commit),h(Commit),r(Pack)], HREF)
  266	},
  267	html(td(class(subject),
  268		[ a(href(HREF), \trunc(Subject, 50)), \ref_names(RefNames)])).
  269td_git_log(_, Field, Record) -->
  270	{ git_log_data(Field, Record, Value),
  271	  (   Value == ''
  272	  ->  Class = empty
  273	  ;   Class = Field
  274	  )
  275	},
  276	html(td(class(Class), Value)).
  277
  278ref_names([]) --> !.
  279ref_names(List) -->
  280	html(span(class(ref_names), \ref_name_list(List))).
  281
  282ref_name_list([]) --> [].
  283ref_name_list([H|T]) -->
  284	html(span(class(ref_name), H)), ref_name_list(T).
  285
  286trunc(Text, Max) -->
  287	{ truncate_atom(Text, Max, Show) },
  288	html(Show).
 commit_info(+Pack, +Hash, +Options)//
Component to show an individual commit. Options:
diff(Diff)
One of stat (default) or patch (full difference)
  298commit_info(Pack, Hash, Options) -->
  299	{ select_option(diff(Diff), Options, Rest, stat),
  300	  cpack_show(Pack, Hash, Record-Body, [diff(Diff)|Rest]),
  301	  commit_data(subject, Record, Subject)
  302	},
  303	html_requires(css('cpack.css')),
  304	html(div(class(cpack),
  305		 [ h2(Subject),
  306		   table(class(commit),
  307			 [ \tr_commit(author,	 author_name, Record),
  308			   \tr_commit('',        author_date, Record),
  309			   \tr_commit(committer, committer_name, Record),
  310			   \tr_commit('',        committer_date, Record),
  311			   tr([th(commit),       td(class(commit), Hash)]),
  312			   \tr_commit(tree,      tree_hash, Record),
  313			   \tr_commit(parent,    parent_hashes, Record)
  314			 ]),
  315		   \select_diff(Diff),
  316		   pre(class(commitdiff),
  317		       \diff_lines(Body, Diff))
  318		 ])).
  319
  320select_diff(Now) -->
  321	{ other_diff(Now, Other),
  322	  http_current_request(Request),
  323	  http_reload_with_parameters(Request, [diff(Other)], HREF)
  324	},
  325	html(div(class(diffstyle),
  326	       ['Diff style: ', b(Now), ' ', a(href(HREF), Other)])).
  327
  328other_diff(patch, stat).
  329other_diff(stat, patch).
  330
  331diff_lines([], _) --> [].
  332diff_lines([Line|T], Diff) -->
  333	(   { diff_line_class(Line, Diff, Class) }
  334	->  html(span(class(Class), ['~s'-[Line]]))
  335	;   diff_line(Line, Diff)
  336	->  []
  337	;   html('~s'-[Line])
  338	),
  339	(   {T==[]}
  340	->  []
  341	;   ['\n'],
  342	    diff_lines(T, Diff)
  343	).
  344
  345:- if(current_predicate(string_codes/2)).  346term_expansion(diff_line_class(Start, Diff, Class),
  347	       diff_line_class(Codes, Diff, Class)) :-
  348	string_codes(Start, ClosedCodes),
  349	append(ClosedCodes, _, Codes).
  350:- else.  351term_expansion(diff_line_class(Start, Diff, Class),
  352	       diff_line_class(Codes, Diff, Class)) :-
  353	is_list(Start),
  354	append(Start, _, Codes).
  355:- endif.  356
  357diff_line_class("diff ", patch, diff).
  358diff_line_class("--- ", patch, a).
  359diff_line_class("+++ ", patch, b).
  360diff_line_class("-", patch, del).
  361diff_line_class("+", patch, add).
  362
  363diff_line(Line, stat) -->
  364	{ phrase(dirstat(File, Sep, Count, Plusses, Minus), Line) },
  365	html([ ' ', span(class(file), '~s'-[File]),
  366	       '~s'-[Sep],
  367	       '~s'-[Count], ' ',
  368	       span(class(add), '~s'-[Plusses]),
  369	       span(class(del), '~s'-[Minus])
  370	     ]).
  371
  372dirstat(File, Sep, [D0|RD], Plusses, Minus) -->
  373	" ",
  374	string_without(" ", File),
  375	string(Sep),
  376	digit(D0),digits(RD),
  377	" ",
  378	plusses(Plusses),
  379	minuss(Minus).
  380
  381plusses([0'+|T]) --> "+", !, plusses(T).
  382plusses([]) --> [].
  383
  384minuss([0'+|T]) --> "-", !, minuss(T).
  385minuss([]) --> [].
  386
  387tr_commit(Label, Field, Record) -->
  388	{ commit_data(Field, Record, Value) },
  389	html(tr([th(Label), td(class(Field), Value)])).
 files_in_pack(+Pack)// is det
Create a ul for all files that appear in the pack. Maybe we should consider a tree-styled nested ul?
  397files_in_pack(Pack) -->
  398	{ findall(File, rdf_has(File, cpack:inPack, Pack), Files),
  399	  files_to_tree(Files, Trees)
  400	},
  401	pack_size(Files),
  402	html_requires(css('ul_tree.css')),
  403	html(ul(class(tree),
  404		\dir_nodes(Trees))).
  405
  406pack_size(Files) -->
  407	{ maplist(cpack_file_size, Files, Sizes),
  408	  length(Files, Count),
  409	  sumlist(Sizes, Total)
  410	},
  411	html(p([ 'Pack contains ', \n('~D', Count), ' files holding a total of ',
  412		 b(\n(human, Total)), 'bytes. ',
  413		 'Below is the file hierarchy of the package. ',
  414		 'The tree link to pages that provide history and dependencies ',
  415		 'for each file.'
  416	       ])).
  417
  418cpack_file_size(File, Size) :-
  419	rdf_has(File, cpack:size, Literal),
  420	literal_text(Literal, Text),
  421	atom_number(Text, Size).
  422
  423dir_nodes([]) --> [].
  424dir_nodes([H|T]) --> dir_node(H), dir_nodes(T).
  425
  426dir_node(leaf(File)) --> !,
  427	html(li(class(file), \cpack_link(File))).
  428dir_node(tree(Dir, SubTrees)) -->
  429	html(li(class(dir),
  430		[ span(class(dir), Dir),
  431		  ul(class(dir),
  432		     \dir_nodes(SubTrees))
  433		])).
  434
  435files_to_tree(Files, Tree) :-
  436	map_list_to_pairs(path_of, Files, Pairs),
  437	keysort(Pairs, Sorted),
  438	make_tree(Sorted, Tree).
  439
  440path_of(File, Segments) :-
  441	rdf_has(File, cpack:path, literal(Path)),
  442	atomic_list_concat(Segments, /, Path).
  443
  444make_tree([], []).
  445make_tree([H|T], [Node|More]) :-
  446	first_path(H, HS, Dir),
  447	(   HS = []-File
  448	->  Node = leaf(File),
  449	    Rest = T
  450	;   Node = tree(Dir, SubTrees),
  451	    same_first_path(T, Dir, TS, Rest),
  452	    make_tree([HS|TS], SubTrees)
  453	),
  454	make_tree(Rest, More).
  455
  456first_path([Dir|Sub]-File, Sub-File, Dir).
  457
  458same_first_path([], _, [], []) :- !.
  459same_first_path([H|T], Dir, [HS|TS], Rest) :-
  460	first_path(H, HS, Dir), !,
  461	same_first_path(T, Dir, TS, Rest).
  462same_first_path(Rest, _, [], Rest).
  463
  464
  465		 /*******************************
  466		 *     STATUS AND CONFLICTS	*
  467		 *******************************/
 cpack_issues(+Pack, +Problems)
  471cpack_issues(_, []) --> !.
  472cpack_issues(Pack, Problems) -->
  473	html([ h3('Issues with this package'),
  474	       \list(Problems, problem(Pack), ul)
  475	     ]).
  476
  477problem(_Pack, conflict(Pack2, Why)) --> !,
  478	html([ span(class(msg_warning),
  479		    [ 'Conflict with package ', \cpack_link(Pack2) ]),
  480	       \list(Why, conflict_reason, ul)
  481	     ]).
  482problem(_Pack, not_satified(Why)) --> !,
  483	html([ span(class(msg_warning),
  484		    [ 'The following requirements cannot be satisfied' ]),
  485	       \list(Why, not_satisfied_reason, ul)
  486	     ]).
  487
  488conflict_reason(same_module(M, File1, File2)) -->
  489	html([ 'Module ', M, ' is provided by ', \cpack_link(File1), ' and ',
  490	       \cpack_link(File2)
  491	     ]).
  492conflict_reason(same_file(Path, File1, File2)) -->
  493	html([ 'Path alias ', Path, ' can be resolved by the files ',
  494	       \cpack_link(File1), ' and ', \cpack_link(File2)
  495	     ]).
  496conflict_reason(Term) -->
  497	html('Unknown reason: ~q'-Term).
  498
  499not_satisfied_reason(no_token(Token)) --> !,
  500	html(['No package provides the required token ',
  501	      a(span(class(token), \cpack_link(Token)))]).
  502not_satisfied_reason(file(File, Problems)) --> !,
  503	html([ 'The following dependencies of ', \cpack_link(File, cpack:path),
  504	       ' cannot be satisfied',
  505	       \list(Problems, file_problem, ul)
  506	     ]).
  507not_satisfied_reason(Term) -->
  508	html('Unknown reason: ~q'-Term).
  509
  510file_problem(double_import(PI, File1, File2)) -->
  511	html([ 'Both ', \cpack_link(File1), ' and ', \cpack_link(File2),
  512	       ' export ', \pi(PI)
  513	     ]).
  514file_problem(file_not_found(FileRef)) -->
  515	html([ 'File reference ', \cpack_link(FileRef), ' cannot be resolved'
  516	     ]).
  517file_problem(predicate_not_found(PI)) -->
  518	html([ 'Predicate ', \pi(PI), ' cannot be resolved'
  519	     ]).
  520file_problem(Term) -->
  521	html('Unknown reason: ~q'-Term).
  522
  523pi(PI) -->
  524	html(span(class(pi), PI)).
 cpack_status_icon(+Package)// is det
Show an icon for the sanity-state of the package
  530cpack_status_icon(Package) -->
  531	{ package_status(Package, Problems) },
  532	cpack_status_icon(Package, Problems).
  533
  534cpack_status_icon(_Package, []) -->
  535	{ http_absolute_location(icons('webdev-ok-icon.png'), IMG, [])
  536	}, !,
  537	html(img([class(status), alt('OK'), src(IMG)])).
  538cpack_status_icon(_Package, _Problems) -->
  539	{ http_absolute_location(icons('webdev-alert-icon.png'), IMG, [])
  540	}, !,
  541	html(img([class(status), alt('Not satisfied'), src(IMG)])).
  542
  543
  544package_status(Pack, Problems) :-
  545	findall(Problem, package_problem(Pack, Problem), Problems).
  546
  547package_problem(Pack, conflict(Pack2, Why)) :-
  548	cpack_conflicts(Pack, Pack2, Why).
  549package_problem(Pack, not_satified(What)) :-
  550	cpack_not_satisfied(Pack, What).
 cpack_update_icon(+Pack)//
Show an icon to update the Pack if the current user is the submitter.
  557cpack_update_icon(Pack) -->
  558	{ logged_on(User),
  559	  (   user_property(User, url(UserURI)),
  560	      rdf_has(Pack, cpack:submittedBy, UserURI)
  561	  ;   catch(check_permission(User, admin(cpack)), _, fail)
  562	  ), !,
  563	  http_absolute_location(icons('webdev-arrow-up-icon.png'), IMG, []),
  564	  http_current_request(Request),
  565	  memberchk(request_uri(ReturnTo), Request),
  566	  http_link_to_id(cpack_resubmit,
  567			  [ pack(Pack),
  568			    return_to(ReturnTo)
  569			  ],
  570			  Resubmit)
  571	},
  572	html(a(href(Resubmit),
  573	       img([ class(update),
  574		     alt('Update'),
  575		     title('Pull a new version'),
  576		     src(IMG)
  577		   ]))).
  578cpack_update_icon(_) --> [].
  579
  580
  581		 /*******************************
  582		 *	      FILE		*
  583		 *******************************/
 cpack_file(+FileURL, +Options)// is det
Show local view for the file FileURL
  589cpack_file(FileURL, _Options) -->
  590	{ rdf_has(FileURL, cpack:path, literal(Path)),
  591	  rdf_has(FileURL, cpack:inPack, Pack)
  592	},
  593	html_requires(css('cpack.css')),
  594	html(div(class(cpack),
  595		 [ h2(['File "', Path, '"', \download(FileURL)]),
  596		   table(class(infobox),
  597			 [ \p_row(FileURL, cpack:inPack),
  598			   \p_row(FileURL, cpack:module),
  599			   \p_row(FileURL, cpack:size)
  600			 ]),
  601		   br(clear(all)),
  602		   \git_shortlog(Pack, [limit(5), git_path(Path)]),
  603		   \prolog_file(FileURL)
  604		 ])).
  605
  606download(FileURL) -->
  607	{ http_link_to_id(cpack_show_file, [r(FileURL)], HREF)
  608	},
  609	html(a([href(HREF), style('float:right')], '[download]')).
 prolog_file(+FileURL)// is det
Describe our knowledge about a Prolog source file.
  616prolog_file(FileURL) -->
  617	{ rdfs_individual_of(FileURL, cpack:'PrologFile') }, !,
  618	html([ \file_imports(FileURL),
  619	       \used_by(FileURL),
  620	       \exported_predicates(FileURL),
  621	       \required_predicates(FileURL)
  622	     ]).
  623prolog_file(_) --> [].
  624
  625
  626exported_predicates(FileURL) -->
  627	{ findall(PI, rdf_has(FileURL, cpack:exportsPredicate, PI), List),
  628	  List \== []
  629	}, !,
  630	html(h3('Exported predicates')),
  631	list_ul(List, []).
  632exported_predicates(_) --> [].
  633
  634required_predicates(FileURL) -->
  635	{ findall(PI, rdf_has(FileURL, cpack:requiresPredicate, PI), List)
  636	},
  637	html(h3('Required predicates')),
  638	list(List, required_predicate(FileURL), ul).
  639
  640required_predicate(File, PI) -->
  641	{ rdf_has(File2, cpack:exportsPredicate, PI),
  642	  (   rdf_has(File2, cpack:resolves, FileRef),
  643	      rdf_has(File, cpack:usesFile, FileRef)
  644	  ->  Ref = FileRef
  645	  ;   rdf_has(File, cpack:usesFile, File2)
  646	  ->  Ref = File2
  647	  )
  648	}, !,
  649	cpack_link(PI),
  650	html([span(class(msg_informational), ' from '), \cpack_link(Ref)]).
  651required_predicate(_File, literal(LPI)) -->
  652	{ atom_to_term(LPI, PI, []),
  653	  pi_head(PI, Head),
  654	  predicate_property(Head, autoload(_From)) % TBD: indicate location
  655	}, !,
  656	cpack_link(literal(LPI)),
  657	html([span(class(msg_informational), ' autoloaded')]).
  658required_predicate(_File, literal(LPI)) -->
  659	{ atom_to_term(LPI, Name/Arity, []),
  660	  current_predicate(user:Name/Arity)
  661	}, !,
  662	cpack_link(literal(LPI)),
  663	html([span(class(msg_informational),
  664		   ' global predicate in module user')]).
  665required_predicate(_File, literal(LPI)) -->
  666	{ atom_to_term(LPI, PI, []),
  667	  pi_head(PI, Head),
  668	  predicate_property(Head, multifile)
  669	}, !,
  670	cpack_link(literal(LPI)),
  671	html([span(class(msg_informational),
  672		   ' multifile')]).
  673required_predicate(File, literal(LPI)) -->
  674	{ file_calls_public_from(File, UsedFile, LPI)
  675	},
  676	cpack_link(literal(LPI)),
  677	html([span(class(msg_informational),
  678		   [' public in ', \cpack_link(UsedFile)])]).
  679required_predicate(_File, PI) -->
  680	cpack_link(PI),
  681	html(span(class(msg_error), ' undefined')).
  682
  683pi_head(M:PI, M:Head) :- !,
  684	pi_head(PI, Head).
  685pi_head(Name/Arity, Head) :-
  686	functor(Head, Name, Arity).
 file_imports(+File)// is det
Show required dependencies of this file.
  692file_imports(File) -->
  693	html([ h3('This file requires'),
  694	       ul([ \li_imports(File, 'From packages',
  695				cpack:usesPackageFile),
  696		    \li_imports(File, 'From ClioPatria',
  697				cpack:usesClioPatriaFile),
  698		    \li_imports(File, 'From the Prolog library',
  699				cpack:usesSystemFile)
  700		  ])
  701	     ]).
  702
  703li_imports(File, Label, P0) -->
  704	{ rdf_global_id(P0, P),
  705	  findall(I, rdf_has(File, P, I), Imports),
  706	  Imports \== []
  707	}, !,
  708	html(li([ Label,
  709		  \list(Imports, import_into(File), ul)
  710		])).
  711li_imports(_, _, _) -->
  712	[].
  713
  714import_into(Me, FileRef) -->
  715	{ rdfs_individual_of(FileRef, cpack:'FileRef'),
  716	  findall(File-PIs, resolves_required(Me, FileRef, File, PIs), ByFile)
  717	},
  718	cpack_link(FileRef),
  719	(   {ByFile==[]}
  720	->  html([' ', span(class(msg_error), 'file not found')])
  721	;   (   {ByFile=[_]}
  722	    ->  html([' ', span(class(msg_informational),
  723				 'resolved by')])
  724	    ;	html([' ', span(class(msg_warning),
  725				'can be resolved by one of these')])
  726	    ),
  727	    list(ByFile, import_from_file, ul)
  728	).
  729import_into(Me, File) -->
  730	{ rdfs_individual_of(File, cpack:'PrologFile'), !,
  731	  predicates_resolved_by(Me, File, Predicates)
  732	},
  733	cpack_link(File),
  734	imported_predicate_list(File, Predicates).
  735
  736import_from_file(File-Predicates) -->
  737	cpack_link(File),
  738	imported_predicate_list(File, Predicates).
  739
  740imported_predicate_list(File, []) -->
  741	{ rdf_has(File, cpack:exportsPredicate, _) }, !,
  742	html([' ', span([ class(msg_warning),
  743			  title('Prolog cross-reference analysis is \c
  744			         incomplete, so this is not proof of an error')
  745			],
  746			'could not find proof of dependency')]).
  747imported_predicate_list(_, []) --> !,
  748	html([' ', span(class(msg_informational), 'no exports')]).
  749imported_predicate_list(_, Predicates) -->
  750	html([': ', span(class(pi_list), \pi_list(Predicates))]).
  751
  752pi_list([H|T]) -->
  753	html(span(class(pred), \cpack_link(H))),
  754	(   {T==[]}
  755	->  []
  756	;   html(', '),
  757	    pi_list(T)
  758	).
  759
  760resolves_required(Me, Import, File, PIs) :-
  761	  rdf_has(File, cpack:resolves, Import),
  762	  predicates_resolved_by(Me, File, PIs).
  763
  764predicates_resolved_by(Me, File, PIs) :-
  765	  findall(PI, (rdf_has(File, cpack:exportsPredicate, PI),
  766		       rdf_has(Me, cpack:requiresPredicate, PI)
  767		      ),
  768		  PIs).
 used_by(+File)// is det
Indicates which other files in which package depend on this file.
  775used_by(File) -->
  776	{ findall(By-Pack,
  777		  file_used_by_file_in_package(File, By, Pack),
  778		  Pairs),
  779	  Pairs \== []
  780	}, !,
  781	html([ h3('This file is used by'),
  782	       \list(Pairs, file_in_package(File), ul)
  783	     ]).
  784used_by(_) --> [].
  785
  786file_in_package(Me, File-Pack) -->
  787	{ rdf_has(Me, cpack:inPack, Pack) }, !,
  788	html([ \cpack_link(File, cpack:path),
  789	       span(class(msg_informational),
  790		    ' (from the same package)')
  791	     ]).
  792file_in_package(_, File-Pack) -->
  793	html([ \cpack_link(File, cpack:path),
  794	       ' from package ',
  795	       \cpack_link(Pack)
  796	     ]).
  797
  798
  799		 /*******************************
  800		 *	       BASICS		*
  801		 *******************************/
 p_row(+R, +P)// is det
Row in a propery table.
  807p_row(R, P0) -->
  808	{ rdf_global_id(P0, P),
  809	  rdf_display_label(P, Label),
  810	  rdf_has(R, P, _)
  811	}, !,
  812	html(tr([th([Label, :]), td(\cpack_prop(R, P))])).
  813p_row(_, _) --> [].
 list_ul(+ItemList, +Options)
Create an ul list from the items in ItemList. Options are passed as attributes to the ul element, except for:
predicate(P)
Use the predicate P as preferenced prediate to generate a label.
To be done
- : Allow for sorting
  827list_ul(List, Options) -->
  828	{ (   select_option(predicate(P0), Options, Rest)
  829	  ->  rdf_global_id(P0, P)
  830	  ;   P = (-),
  831	      Rest = Options
  832	  )
  833	},
  834	html(ul(Rest,
  835		\list_li(List, P))).
  836
  837list_li([], _) --> [].
  838list_li([H|T], P) -->
  839	html(li(\cpack_link(H, P))),
  840	list_li(T, P).
 list(+List, :Goal, +Type)// is det
Create an HTML list from the elements of List. Each member of List is typeset in an li element by calling call(Goal, Member). Type is one of ul or ol, optionally with an extra argument that provides attributes for the list. For example:
      list(List, make_item, ul(class(mylist))),
      ...

make_item(Name, Mail) -->
      html([Name, ' <mailto:', Mail, '>']).
  858:- meta_predicate
  859	list(+,3,+,?,?).  860
  861list(List, Goal, Type) -->
  862	{ Type =.. L,
  863	  append(L, [\list_item(List, Goal)], L1),
  864	  Term =.. L1
  865	},
  866	html(Term).
  867
  868list_item([], _) --> [].
  869list_item([H|T], Goal) -->
  870	html(li(\call(Goal, H))),
  871	list_item(T, Goal).
 cpack_prop(+Resource, +Property)
Display the value of Property for Resource in the current location.
To be done
- : Deal with multiple values?
  881cpack_prop(R, P0) -->
  882	{ rdf_global_id(P0, P),
  883	  rdf_has(R, P, O0), !,
  884	  representer(O0, O)
  885	},
  886	(   { rdf_is_literal(O) }
  887	->  literal(O)
  888	;   cpack_link(O, P)
  889	).
  890cpack_prop(_, _) --> [].
 cpack_wiki(+Resource, +Property)
Display the value of Property for Resource in the current location, where the value is represented in wiki format.
  898cpack_wiki(R, P0) -->
  899	{ rdf_global_id(P0, P),
  900	  rdf_has(R, P, O),
  901	  rdf_is_literal(O)
  902	}, !,
  903	wiki(O).
  904cpack_wiki(_, _) --> [].
 representer(+R0, -R) is det
Find representers among equivalent objects. This deals with the author case.
To be done
- Move to an OWL library
  914representer(R0, R) :-
  915	rdf_is_bnode(R0),
  916	rdf_has(R0, owl:sameAs, R),
  917	\+ rdf_is_bnode(R), !.
  918representer(R, R).
  919
  920
  921literal(literal(type(Type, Value))) -->
  922	{ rdf_equal(Type, xsd:dateTime),
  923	  parse_time(Value, Time), !,
  924	  format_time(atom(Human),
  925		      '%a, %d %b %Y %T %Z',
  926		      Time)
  927	},
  928	html(Human).
  929literal(O) -->
  930	{ literal_text(O, Text) },
  931	html(Text).
 wiki(O)//
Render text as Wiki
  937wiki(L) -->
  938	{ literal_text(L, Text),
  939	  atom_codes(Text, Codes),
  940	  wiki_codes_to_dom(Codes, [], DOM)
  941	},
  942	html_requires(pldoc),
  943	html(DOM).
 cpack_link(+R)// is det
 cpack_link(+R, +P)// is det
Display a link to a CPACK resource. The version cpack_link//2 can be used to select a given property for producing the label.
  953:- rdf_meta
  954	cpack_label_property(r),
  955	cpack_external_link(r).  956
  957cpack_link(R) -->
  958	cpack_link(R, '-').
  959
  960cpack_link(R, P0) -->
  961	{ P0 \== (-),
  962	  rdf_global_id(P0, P),
  963	  cpack_label_property(P),
  964	  rdf_has(R, P, Name), !,
  965	  literal_text(Name, Text),
  966	  resource_link(R, HREF)
  967	},
  968	html(a(href(HREF), Text)).
  969cpack_link(L, _) -->
  970	{ rdf_is_literal(L), !,
  971	  literal_text(L, Text)
  972	},
  973	html(Text).
  974cpack_link(R, P) -->
  975	{ cpack_external_link(P) }, !,
  976	html(a(href(R),R)).
  977cpack_link(R, _) -->
  978	rdf_link(R).
  979
  980cpack_label_property(cpack:name).
  981cpack_label_property(foaf:name).
  982cpack_label_property(rdfs:label).
  983
  984cpack_external_link(cpack:home).
  985
  986
  987		 /*******************************
  988		 *	       LABELS		*
  989		 *******************************/
 rdf_label:display_label_hook(+Pack, ?Lang, -Label) is semidet
Provide the label of a package using the cpack:packageName property.
  996rdf_label:display_label_hook(R, _, Label) :-
  997	rdfs_individual_of(R, cpack:'Package'),
  998	rdf_has(R, cpack:packageName, Literal),
  999	literal_text(Literal, Label)