swish/commit

Upstream files

authorJan Wielemaker
Mon Oct 29 16:19:24 2018 +0100
committerJan Wielemaker
Mon Oct 29 16:19:42 2018 +0100
commit0b5f43e785db287dbaccb1674172c1075e0f7c2d
tree3dbdab97e9c9b5cb297e6950f1b2456e772ace92
parent13819db3ba32a1a95a470a9c891962c3972a8051
Diff style: patch stat
diff --git a/examples/htmlcell.swinb b/examples/htmlcell.swinb
index 6fc397e..b0b10e2 100644
--- a/examples/htmlcell.swinb
+++ b/examples/htmlcell.swinb
@@ -18,8 +18,8 @@
 </p>
 
 <style>
-  dl.htmlcell-doc dt { text-align: left; }
-  dt.htmlcell-doc-title { color: blue; margin-top: 5px;}
+  dl.htmlcell-doc dt { text-align: left; margin-top: 1ex;}
+  dl.htmlcell-doc dt.htmlcell-doc-title { color: blue; margin-top: 2ex;}
 </style>
 <div class="list-group">
   <dl class="dl-horizontal htmlcell-doc">
@@ -38,7 +38,12 @@
     </dd><dt>.run(query, parameters)</dt><dd>Run the named query cell.  <var>Parameters</var> is an object
     binding Prolog variables in the query to specified values.
     </dd><dt>.swish(options)</dt><dd>Wrapper around <code>new Pengine()</code> that fetches the sources
-    using the same algorithm as a query cell and sets the <code>application</code> to <code>swish</code>.
+    using the same algorithm as a query cell and provides the defaults below:
+    <ul>
+      <li>Set <code>application</code> to <code>swish</code>.</li>
+      <li>Set <code>chunk</code> to <code>5</code>.  This should be set to <code>1</code> for code
+        that acts on <b>both</b> <code>onprompt</code> and <code>onsuccess.</code></li>
+    </ul>
     </dd><dt>.submit(form, options)</dt><dd>Submit a (Bootstrap) form to a predicate.  This provides a
     wrapper around <code>.swish</code> that collects the content of the indicated <code>form</code> (a
     jQuery selector), calls <code>options.predicate</code> with a single argument that is a dict that
diff --git a/lib/swish/authenticate.pl b/lib/swish/authenticate.pl
index 271318a..5256ce4 100644
--- a/lib/swish/authenticate.pl
+++ b/lib/swish/authenticate.pl
@@ -67,10 +67,10 @@ based on the HTTP request.
 
 authenticate(Request, Auth) :-
     http_peer(Request, Peer),
-    http_auth(Request, Auth0),
-    profile_auth(Request, Auth1),
-    Auth2 = Auth0.put(Auth1).put(peer, Peer),
-    identity(Auth2, Auth),
+    http_auth(Request, HTTPAuth),
+    profile_auth(Request, ProfileAuth),
+    Auth2 = HTTPAuth.put(ProfileAuth).put(peer, Peer),
+    identity(Request, Auth2, Auth),
     debug(authenticate, 'Identity: ~p', [Auth]).
 
 :- multifile
@@ -97,12 +97,21 @@ profile_auth(Request, Auth) :-
     !.
 profile_auth(_, auth{}).
 
-identity(Auth0, Auth) :-
+identity(Request, Auth0, Auth) :-
     _{identity_provider:Provider, external_identity:ExtID} :< Auth0,
     !,
+    (   swish_config:user_info(Request, Provider, UserInfo),
+        is_dict(UserInfo, Tag),
+        (   var(Tag)
+        ->  Tag = user_info
+        ;   true
+        )
+    ->  true
+    ;   UserInfo = user_info{}
+    ),
     atomic_list_concat([Provider,ExtID], :, Identity),
-    Auth = Auth0.put(identity, Identity).
-identity(Auth, Auth).
+    Auth = Auth0.put(_{identity:Identity, user_info:UserInfo}).
+identity(_, Auth, Auth).
 
 
 %!  user_property(+Identity, ?Property) is nondet.
diff --git a/lib/swish/chat.pl b/lib/swish/chat.pl
index 16d6e8c..6c2f653 100644
--- a/lib/swish/chat.pl
+++ b/lib/swish/chat.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@cs.vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (C): 2016-2017, VU University Amsterdam
+    Copyright (C): 2016-2018, VU University Amsterdam
 			      CWI Amsterdam
     All rights reserved.
 
@@ -94,6 +94,7 @@ browsers which in turn may have multiple SWISH windows opened.
 :- multifile swish_config:config/2.
 
 swish_config:config(hangout, 'Hangout.swinb').
+swish_config:config(avatars, svg).		% or 'noble'
 
 
 		 /*******************************
@@ -285,7 +286,6 @@ wsid_visitor(WSID, Visitor) :-
 	session_user(Session, Visitor),
 	visitor_session(WSID, Session).
 
-
 %!	existing_visitor(+WSID, +Session, +Token, -TmpUser, -UserData) is semidet.
 %
 %	True if we are dealing with  an   existing  visitor for which we
@@ -779,9 +779,16 @@ reply_avatar(Request) :-
 noble_avatar_url(HREF, Options) :-
 	option(avatar(HREF), Options), !.
 noble_avatar_url(HREF, _Options) :-
+	swish_config:config(avatars, noble),
+	!,
 	noble_avatar(_Gender, Path, true),
 	file_base_name(Path, File),
 	http_absolute_location(swish(avatar/File), HREF, []).
+noble_avatar_url(HREF, _Options) :-
+	A is random(0x1FFFFF+1),
+	http_absolute_location(icons('avatar.svg'), HREF0, []),
+	format(atom(HREF), '~w#~d', [HREF0, A]).
+
 
 
 		 /*******************************
@@ -977,8 +984,11 @@ dict_file_name(Dict, File) :-
 %
 %	  - Demands the user to be logged on
 %	  - Limits the size of the message and its payloads
+%
+%	@tbd Call authorized/2 with all proper identity information.
 
 forbidden(Message, DocID, Why) :-
+	\+ swish_config:config(chat_spam_protection, false),
 	\+ ws_authorized(chat(post(Message, DocID)), Message.user), !,
 	Why = "Due to frequent spamming we were forced to limit \c
 	       posting chat messages to users who are logged in.".
@@ -992,6 +1002,7 @@ forbidden(Message, _DocID, Why) :-
 	member(Payload, Payloads),
 	large_payload(Payload, Why), !.
 forbidden(Message, _DocID, Why) :-
+	\+ swish_config:config(chat_spam_protection, false),
 	eval_content(Message.get(text), _WC, Score),
 	user_score(Message, Score, Cummulative, _Count),
 	Score*2 + Cummulative < 0,
diff --git a/lib/swish/download.pl b/lib/swish/download.pl
index fb61eaa..528a38b 100644
--- a/lib/swish/download.pl
+++ b/lib/swish/download.pl
@@ -3,7 +3,8 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2016, VU University Amsterdam
+    Copyright (c)  2018, VU University Amsterdam
+		         CWI, Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -37,45 +38,241 @@
 	  ]).
 :- use_module(library(pengines)).
 :- use_module(library(option)).
+:- use_module(library(settings)).
+:- use_module(library(apply)).
 :- use_module(library(http/mimetype)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
 
-/** <module> Provide data for downloading
+/** <module> Provide a button for downloading data
+
+This module allows a button to be  inserted into the Pengine output that
+allows for downloading data. Originally this   used the `data` type URL.
+This has been disabled in recent   browsers. Also considering the length
+limitations on URLs on some browsers we   now store the data server-side
+and make the link simply download the  data.   The  data  is kept on the
+server for `keep_downloads_time` seconds, default 24 hours.
 */
 
-%%	download_button(+Data:string, +Options)
+:- setting(keep_downloads_time, number, 86400,
+	   "Seconds to keep a downloaded file").
+
+%!	download_button(+Data:string, +Options)
 %
 %	Emit a button in the SWISH   output window for downloading Data.
-%	The provided data is associated with   the button and (thus) not
-%	stored on the server.  A small tests indicates this works fairly
-%	well up to several tens of megabytes.
+%	The provided data  is  stored  on   the  server.
 %
 %	Options:
 %
-%	  - name(+Name)
-%	  (Base-)Name of the file created (default: 'swish-download')
-%	  - ext(+Ext)
-%	  Extension for the file (default: 'dat')
+%	  - filename(+Name)
+%	    (Base-)Name of the file created (default:
+%	    `swish-download.dat`),
+%	  - content_type(+Type)
+%	    Full content type.  By default this is derived from the
+%	    extension of the filename and the encoding.
 %	  - encoding(+Enc)
-%	  Encoding to use.  One of `utf8` or `octet`.  default is `utf8`
+%	    Encoding to use. One of `utf8` or `octet`. default is
+%	    `utf8`.
 %
 %	@see https://en.wikipedia.org/wiki/Data_URI_scheme
 
 download_button(Data, Options) :-
 	option(filename(FileName), Options, 'swish-download.dat'),
-	file_mime_type(FileName, Major/Minor),
-	atomics_to_string([Major, Minor], /, ContentType),
 	option(encoding(Enc), Options, utf8),
-	encode_data(Enc, Data, CharSet, EncData),
+	(   option(content_type(ContentType), Options)
+	->  true
+	;   file_mime_type(FileName, Major/Minor),
+	    atomics_to_string([Major, Minor], /, ContentType0),
+	    add_charset(Enc, ContentType0, ContentType)
+	),
+	save_download_data(Data, UUID, Enc),
 	pengine_output(
 	    json{action:downloadButton,
 		 content_type:ContentType,
-		 data:EncData,
-		 filename:FileName,
-		 charset:CharSet
+		 encoding: Enc,
+		 uuid:UUID,
+		 filename:FileName
 		}).
 
-encode_data(utf8,  Data, "charset=UTF-8", Data).
-encode_data(octet, Data, "base64", Data64) :-
-	string_codes(Data, Codes),
-	phrase(base64(Codes), Codes64),
-	string_codes(Data64, Codes64).
+add_charset(utf8, Enc0, Enc) :- !,
+	atom_concat(Enc0, '; charset=UTF-8', Enc).
+add_charset(_, Enc, Enc).
+
+
+		 /*******************************
+		 *	      SERVER		*
+		 *******************************/
+
+:- http_handler(swish(download), download, [id(download), prefix, method(get)]).
+
+%!	download(+Request)
+%
+%	Handle a download request.
+
+download(Request) :-
+	http_parameters(Request,
+			[ uuid(UUID, []),
+			  content_type(Type, [])
+			]),
+	download_file(UUID, File),
+	http_reply_file(File,
+			[ mime_type(Type),
+			  unsafe(true)
+			],
+			Request).
+
+
+		 /*******************************
+		 *	       STORE		*
+		 *******************************/
+
+%!	save_download_data(+Data, -UUID, +Encoding) is det.
+%
+%	Save the string Data in the download store and return a UUID to
+%	retreive it.
+
+save_download_data(Data, UUID, Encoding) :-
+	download_file(UUID, Path),
+	ensure_parents(Path),
+	setup_call_cleanup(
+	    open(Path, write, Out, [encoding(Encoding)]),
+	    write(Out, Data),
+	    close(Out)),
+	prune_downloads.
+
+
+%!	download_file(?UUID, -Path)
+%
+%	Path is the full file from which to download Name.
+%
+%	@tbd We could use the SHA1 of the  data. In that case we need to
+%	_touch_ the file if it exists and we   need  a way to ensure the
+%	file is completely saved by a   concurrent  thread that may save
+%	the same file.
+
+download_file(UUID, Path) :-
+	(   var(UUID)
+	->  uuid(UUID)
+	;   true
+	),
+	variant_sha1(UUID, SHA1),
+	sub_atom(SHA1, 0, 2, _, Dir0),
+	sub_atom(SHA1, 2, 2, _, Dir1),
+	sub_atom(SHA1, 4, _, 0, File),
+	download_dir(Dir),
+	atomic_list_concat([Dir, Dir0, Dir1, File], /, Path).
+
+
+%!	download_dir(-Dir) is det.
+%
+%	Find the download base directory.
+
+:- dynamic download_dir_cache/1.
+:- volatile download_dir_cache/1.
+
+download_dir(Dir) :-
+	download_dir_cache(Dir),
+	!.
+download_dir(Dir) :-
+	absolute_file_name(data(download), Dir,
+			   [ file_type(directory),
+			     access(write),
+			     file_errors(fail)
+			   ]),
+	!,
+	asserta(download_dir_cache(Dir)).
+download_dir(Dir) :-
+	absolute_file_name(data(download), Dir,
+			   [ solutions(all)
+			   ]),
+	catch(make_directory(Dir), error(_,_), fail),
+	!,
+	asserta(download_dir_cache(Dir)).
+
+ensure_parents(Path) :-
+	file_directory_name(Path, Dir1),
+	file_directory_name(Dir1, Dir0),
+	ensure_directory(Dir0),
+	ensure_directory(Dir1).
+
+ensure_directory(Dir) :-
+	exists_directory(Dir),
+	!.
+ensure_directory(Dir) :-
+	make_directory(Dir).
+
+
+%!	prune_downloads
+%
+%	Prune old download files. This is actually executed every 1/4th
+%	of the time we keep the files.  This makes this call fast.
+
+:- dynamic pruned_at/1.
+:- volatile pruned_at/1.
+
+prune_downloads :-
+	E = error(_,_),
+	with_mutex(download,
+		   catch(prune_downloads_sync, E,
+			 print_message(warning, E))).
+
+prune_downloads_sync :-
+	pruned_at(Last),
+	setting(keep_downloads_time, Time),
+	get_time(Now),
+	Now < Last + Time/4,
+	!.
+prune_downloads_sync :-
+	thread_create(do_prune_downloads, _,
+		      [ alias(prune_downloads),
+			detached(true)
+		      ]),
+	get_time(Now),
+	retractall(pruned_at(_)),
+	asserta(pruned_at(Now)).
+
+do_prune_downloads :-
+	get_time(Now),
+	setting(keep_downloads_time, Time),
+	Before is Now - Time,
+	download_dir(Dir),
+	prune_dir(Dir, Before, false).
+
+%!	prune_dir(+Dir, +Time, +PruneDir) is det.
+%
+%	Find all files older than Time and  delete them as well as empty
+%	directories.
+
+prune_dir(Dir, Time, PruneDir) :-
+	directory_files(Dir, Files0),
+	exclude(reserved, Files0, Files),
+	exclude(clean_entry(Dir, Time), Files, Rest),
+	(   Rest == [],
+	    PruneDir == true
+	->  E = error(_,_),
+	    catch(delete_directory(Dir), E,
+		  print_message(warning, E))
+	;   true
+	).
+
+reserved(.).
+reserved(..).
+
+%!	clean_entry(+Dir, +Time, +File) is semidet.
+%
+%	True when Dir/File has been cleaned and is removed.
+
+clean_entry(Dir, Time, File) :-
+	directory_file_path(Dir, File, Path),
+	(   exists_directory(Path)
+	->  prune_dir(Path, Time, true),
+	    \+ exists_directory(Path)
+	;   time_file(Path, FTime),
+	    FTime < Time
+	->  E = error(_,_),
+	    catch(delete_file(Path), E,
+		  ( print_message(warning, E),
+		    fail
+		  ))
+	).
+
diff --git a/lib/swish/gitty.pl b/lib/swish/gitty.pl
index 9a66294..df50d66 100644
--- a/lib/swish/gitty.pl
+++ b/lib/swish/gitty.pl
@@ -298,8 +298,10 @@ load_plain_commit(Store, Hash, Meta) :-
 
 %%	gitty_history(+Store, +NameOrHash, -History, +Options) is det.
 %
-%	History is a list of dicts representating the history of Name in
-%	Store.  Options:
+%	History is a dict holding a key   `history` with a list of dicts
+%	representating the history of Name in   Store. The toplevel dict
+%	also contains `skipped`, indicating the  number of skipped items
+%	from the HEAD. Options:
 %
 %	  - depth(+Depth)
 %	  Number of entries in the history.  If not present, defaults
@@ -309,17 +311,23 @@ load_plain_commit(Store, Hash, Meta) :-
 %	  history includes the entry with HASH an (depth+1)//2 entries
 %	  after the requested HASH.
 
-gitty_history(Store, Name, History, Options) :-
+gitty_history(Store, Name, json{history:History,skipped:Skipped}, Options) :-
 	history_hash_start(Store, Name, Hash0),
 	option(depth(Depth), Options, 5),
 	(   option(includes(Hash), Options)
-	->  read_history_to_hash(Store, Hash0, Hash, History0),
-	    length(History0, Before),
+	->  read_history_to_hash(Store, Hash0, Hash, History00),
+	    length(History00, Before),
 	    After is max(Depth-Before, (Depth+1)//2),
 	    read_history_depth(Store, Hash, After, History1),
-	    append(History0, History1, History2),
-	    list_prefix(Depth, History2, History)
-	;   read_history_depth(Store, Hash0, Depth, History)
+	    length(History1, AfterLen),
+	    BeforeLen is Depth - AfterLen,
+	    list_prefix(BeforeLen, History00, History0),
+	    length(History00, Len00),
+	    length(History0, Len0),
+	    Skipped is Len00-Len0,
+	    append(History0, History1, History)
+	;   read_history_depth(Store, Hash0, Depth, History),
+	    Skipped is 0
 	).
 
 history_hash_start(Store, Name, Hash) :-
diff --git a/lib/swish/highlight.pl b/lib/swish/highlight.pl
index 56cd9e9..177150f 100644
--- a/lib/swish/highlight.pl
+++ b/lib/swish/highlight.pl
@@ -3,7 +3,8 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014-2017, VU University Amsterdam
+    Copyright (c)  2014-2018, VU University Amsterdam
+			      CWI, Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -33,7 +34,8 @@
 */
 
 :- module(swish_highlight,
-	  [ current_highlight_state/2
+	  [ current_highlight_state/2,		% +UUID, -State
+	    man_predicate_summary/2		% +PI, -Summary
 	  ]).
 :- use_module(library(debug)).
 :- use_module(library(settings)).
@@ -49,7 +51,9 @@
 :- use_module(library(memfile)).
 :- use_module(library(prolog_colour)).
 :- use_module(library(lazy_lists)).
-:- if(exists_source(library(helpidx))).
+:- if(exists_source(library(pldoc/man_index))).
+:- use_module(library(pldoc/man_index)).
+:- elif(exists_source(library(helpidx))).
 :- use_module(library(helpidx), [predicate/5]).
 :- endif.
 
@@ -789,6 +793,8 @@ style(neck(Neck),     neck, [ text(Text) ]) :-
 style(head(Class, Head), Type, [ text, arity(Arity) ]) :-
 	goal_arity(Head, Arity),
 	head_type(Class, Type).
+style(goal_term(_Class, Goal), var, []) :-
+	var(Goal), !.
 style(goal_term(Class, {_}), brace_term_open-brace_term_close,
       [ name({}), arity(1) | More ]) :-
 	goal_type(Class, _Type, More).
@@ -1144,13 +1150,27 @@ predicate_info(Module:Name/Arity, Key, Value) :-
 	functor(Head, Name, Arity),
 	predicate_property(system:Head, iso), !,
 	ignore(Module = system),
-	(   catch(once(predicate(Name, Arity, Summary, _, _)), _, fail),
+	(   man_predicate_summary(Name/Arity, Summary),
 	    Key = summary,
 	    Value = Summary
 	;   Key = iso,
 	    Value = true
 	).
-predicate_info(_Module:Name/Arity, summary, Summary) :-
-	catch(once(predicate(Name, Arity, Summary, _, _)), _, fail), !.
-predicate_info(PI, summary, Summary) :-	% PlDoc
-	once(prolog:predicate_summary(PI, Summary)).
+predicate_info(PI, summary, Summary) :-
+	(   PI = _Module:Name/Arity,
+	    man_predicate_summary(Name/Arity, Summary)
+	->  true
+	;   prolog:predicate_summary(PI, Summary)
+	->  true
+	).
+
+:- if(current_predicate(man_object_property/2)).
+man_predicate_summary(PI, Summary) :-
+    man_object_property(PI, summary(Summary)).
+:- elif(current_predicate(predicate/5)).
+man_predicate_summary(Name/Arity, Summary) :-
+    predicate(Name, Arity, Summary, _, _).
+:- else.
+man_predicate_summary(_, _) :-
+    fail.
+:- endif.
diff --git a/lib/swish/markdown.pl b/lib/swish/markdown.pl
index 6792634..33e3974 100644
--- a/lib/swish/markdown.pl
+++ b/lib/swish/markdown.pl
@@ -32,7 +32,9 @@
     POSSIBILITY OF SUCH DAMAGE.
 */
 
-:- module(swish_markdown, []).
+:- module(swish_markdown,
+	  [ wiki_file_codes_to_dom/3		% +Code, +Files, -DOM
+	  ]).
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_parameters)).
 :- use_module(library(http/http_client)).
diff --git a/lib/swish/page.pl b/lib/swish/page.pl
index c8a21bd..ced67b4 100644
--- a/lib/swish/page.pl
+++ b/lib/swish/page.pl
@@ -362,7 +362,8 @@ swish_navbar(Options) -->
 			    [ li(\notifications(Options)),
 			      li(\search_box(Options)),
 			      \li_login_button(Options),
-			      li(\broadcast_bell(Options))
+			      li(\broadcast_bell(Options)),
+			      li(\updates(Options))
 			    ])
 		       ])
 		 ])).
@@ -384,6 +385,9 @@ collapsed_button -->
 		      span(class('icon-bar'), [])
 		    ])).
 
+updates(_Options) -->
+	html([ a(id('swish-updates'), []) ]).
+
 
 		 /*******************************
 		 *	      BRANDING		*
diff --git a/lib/swish/pep.pl b/lib/swish/pep.pl
index e96182e..052d037 100644
--- a/lib/swish/pep.pl
+++ b/lib/swish/pep.pl
@@ -58,8 +58,7 @@ Examples are:
 */
 
 :- multifile
-    swish_config:approve/2,
-    swish_config:deny/2.
+    swish_config:approve/3.
 
 %!  authorized(+Action, +Options) is det.
 %
@@ -130,6 +129,10 @@ ws_authorized(chat(post(_,_)), WSUser) :-
     approve/2,
     deny/2.
 
+authorize(Action, Id) :-
+    swish_config:approve(Action, Id, Approve),
+    !,
+    Approve == true.
 authorize(Action, Id) :-
     approve(Action, Id), !,
     \+ deny(Action, Id).
@@ -152,8 +155,13 @@ approve(run(any, _), Auth) :-
     user_property(Auth, login(local)).
 approve(chat(open), _).
 
-%!  deny(+Auth, +Id)
+%!  deny(+Action, +Id)
 
+%!  swish_config:approve(+Action, +Identity, -Approve) is semidet.
+%
+%   This hook is called by approve/2 and deny/2 before the default
+%   rules.  If this hook succeeds it must unify Approve with `true`
+%   or `false`.  Action is approved if Approve is `true`.
 
 
 
diff --git a/lib/swish/template_hint.pl b/lib/swish/template_hint.pl
index 7e49788..363e8b4 100644
--- a/lib/swish/template_hint.pl
+++ b/lib/swish/template_hint.pl
@@ -3,7 +3,8 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014-2016, VU University Amsterdam
+    Copyright (c)  2014-2018, VU University Amsterdam
+			      CWI, Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -56,6 +57,7 @@
 :- use_module(library(error)).
 
 :- use_module(render).
+:- use_module(highlight).
 
 /** <module> Generate template hints for CondeMirror
 
@@ -262,7 +264,7 @@ man_predicate_info(PI, Name-Value) :-
 	    Name-Value = name-PString
 	;   Name-Value = arity-Arity
 	;   Name-Value = (mode)-ModeLine
-	;   once(catch(predicate(PName, Arity, Summary, _, _), _, fail)),
+	;   once(man_predicate_summary(PName/Arity, Summary)),
 	    Name-Value = summary-Summary
 	;   predicate_property(system:PHead, iso),
 	    Name-Value = iso-true
diff --git a/web/help/about.html b/web/help/about.html
index 3619b9d..51813f2 100644
--- a/web/help/about.html
+++ b/web/help/about.html
@@ -13,7 +13,7 @@
     border: 0px;
   }
   div.acknowledgement { width: 90%;
-			margin-top: 2em; margin-left: auto; margin-right: auto;
+			margin-top: 5px; margin-left: auto; margin-right: auto;
 			border-top: 1px solid #bbb;
 			padding-top: 5px;
 			text-align: center;
@@ -81,6 +81,8 @@ Master Games</a>, designed by
 <iframe class="github-btn" src="https://ghbtns.com/github-btn.html?user=SWI-Prolog&amp;repo=swish&amp;type=fork&amp;count=true" width="102" height="20" title="Fork on GitHub"></iframe>
 </div>
 
+<div class="swish-versions v-compact"></div>
+
 <div class=acknowledgement>
 <a href="http://vu.nl" target="_blank">
 <img src="../icons/VU-logo.png" class="vu sponsor-logo top"></a>
diff --git a/web/help/privacy.html b/web/help/privacy.html
new file mode 100644
index 0000000..5f79850
--- /dev/null
+++ b/web/help/privacy.html
@@ -0,0 +1,100 @@
+<!DOCTYPE HTML>
+
+<html>
+  <head>
+  <title>SWISH privacy statement</title>
+  </head>
+<body>
+
+<style>
+dl.privacy dd { margin-left: 2ex;}
+</style>
+
+<h3>Summary</h3>
+
+<ul>
+<li>
+<span style="color:darkblue">SWI</span><span
+style="color:maroon">SH</span> stores HTTP logs and saved programs on
+the server. If the user is logged on, the connecting IP addresses and a
+basic profile is stored based on information provided by federated login
+and entered by the user.
+
+<li>
+Stored information is used to remember user choices and restore
+sessions. The HTTP logs are used for analysis and debugging purposes.
+
+<li>
+Public saved programs may be searched and retrieved by anyone. HTTP logs
+may be shared with research partners under a non-diclosure agreement.
+Other data is never shared.
+
+<li>
+HTTP logs are deleted after 6 months.  Saved programs are never deleted.
+User profiles may be deleted by the user when logged in.
+
+<li>
+<b>If you do not agree with these policies, disconnect now.</b>
+</ul>
+
+<h3>Details</h3>
+
+<p>
+Below we specify which information is stored where and how it may be
+used. Details depend on the installation. Notably login may or may not
+be supported and logging may or may not be enabled.
+
+  <dl class="privacy">
+  <dt>User preferences<dd>
+  Preferences such as <i>semantic highlighting</i> or default <i>profile</i>,
+  etc. are stored in your browser's <em>local store</em> and passed along to
+  the server when applicable.</dd>
+
+  <dt>User profiles<dd>
+  If the user logs on a basic profile is established from data provided
+  by the <i>identity service provider</i> (ISP, e.g., Google) and details
+  added by the user.  The given <i>name</i> and <i>avatar URL</i> are
+  used in the <b>chat</b> service and associated with saved programs.
+  The <i>email</i> is used for user-enabled notifications only. This profile
+  may be deleted at any time using the <b>Profile</b> menu associated with
+  the login avatar.</dd>
+
+  <dt>Stored files<dd>
+  Saved files are stored on the server along with the IP address, a time
+  stamp and the information provided by the user in the <em>Save</em>
+  dialog.  If the file is marked <em>public</em>, it may be searched for,
+  opened and edited by anyone, honouring user selected access restrictions.
+  Saving a file after editing creates a new <em>version</em>.
+  All versions are kept and never deleted.</dd>
+
+  <dt>Cookies<dd>
+  If the user is logged in <span style="color:darkblue">SWI</span><span
+  style="color:maroon">SH</span> uses a session cookie to verify the
+  login status.</dd>
+
+  <dt>HTTP logging<dd>
+  HTTP interaction is logged with full detail.  This information is used
+  to reproduce and fix stability issues.  The data may be used for
+  analysing the user interface and aspects of Prolog programming such
+  as program evolution, debugging, etc.  This information will not be
+  made public.  Server interaction includes:
+  <ul>
+    <li>If semantic highlighting is used, the server maintains a mirror
+    of your source while it is being edited.
+    <li>Queries posted
+    <li>The program against which a query was posted
+    <li>Interaction with the query such as asking for more answers and
+    debugging interaction.
+  </ul>
+  </dd>
+  </dl>
+</body>
+</html>
+
+
+
+
+
+
+
+