View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2016-2017, VU University Amsterdam
    7			      CWI Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swish_chat,
   37	  [ chat_broadcast/1,		% +Message
   38	    chat_broadcast/2,		% +Message, +Channel
   39	    chat_to_profile/2,		% +ProfileID, :HTML
   40	    chat_about/2,		% +DocID, +Message
   41
   42	    notifications//1		% +Options
   43	  ]).   44:- use_module(library(http/hub)).   45:- use_module(library(http/http_dispatch)).   46:- use_module(library(http/http_session)).   47:- use_module(library(http/http_parameters)).   48:- use_module(library(http/websocket)).   49:- use_module(library(http/json)).   50:- use_module(library(error)).   51:- use_module(library(lists)).   52:- use_module(library(option)).   53:- use_module(library(debug)).   54:- use_module(library(uuid)).   55:- use_module(library(random)).   56:- use_module(library(base64)).   57:- use_module(library(apply)).   58:- use_module(library(broadcast)).   59:- use_module(library(ordsets)).   60:- use_module(library(http/html_write)).   61:- use_module(library(http/http_path)).   62:- if(exists_source(library(user_profile))).   63:- use_module(library(user_profile)).   64:- endif.   65:- use_module(library(aggregate)).   66
   67:- use_module(storage).   68:- use_module(gitty).   69:- use_module(config).   70:- use_module(avatar).   71:- use_module(noble_avatar).   72:- use_module(chatstore).   73:- use_module(authenticate).   74:- use_module(pep).   75
   76:- html_meta(chat_to_profile(+, html)).

The SWISH collaboration backbone

We have three levels of identity as enumerated below. Note that these form a hierarchy: a particular user may be logged on using multiple browsers which in turn may have multiple SWISH windows opened.

  1. Any open SWISH window has an associated websocket, represented by the identifier returned by hub_add/3.
  2. Any browser, possibly having multiple open SWISH windows, is identified by a session cookie.
  3. The user may be logged in, either based on the cookie or on HTTP authentication. */
   92		 /*******************************
   93		 *	ESTABLISH WEBSOCKET	*
   94		 *******************************/
   95
   96:- http_handler(swish(chat), start_chat, [ id(swish_chat) ]).   97
   98:- meta_predicate must_succeed(0).
 start_chat(+Request)
HTTP handler that establishes a websocket connection where a user gets an avatar and optionally a name.
  105start_chat(Request) :-
  106	authenticate(Request, Identity),
  107	start_chat(Request, [identity(Identity)]).
  108
  109start_chat(Request, Options) :-
  110	authorized(chat, Options),
  111	(   http_in_session(Session)
  112	->  CheckLogin = false
  113	;   http_open_session(Session, []),
  114	    CheckLogin = true
  115	),
  116	check_flooding,
  117	http_parameters(Request,
  118			[ avatar(Avatar, [optional(true)]),
  119			  nickname(NickName, [optional(true)]),
  120			  reconnect(Token, [optional(true)])
  121			]),
  122	extend_options([ avatar(Avatar),
  123			 nick_name(NickName),
  124			 reconnect(Token),
  125			 check_login(CheckLogin)
  126		       ], Options, ChatOptions),
  127	http_upgrade_to_websocket(
  128	    accept_chat(Session, ChatOptions),
  129	    [ guarded(false),
  130	      subprotocols(['v1.chat.swish.swi-prolog.org', chat])
  131	    ],
  132	    Request).
  133
  134extend_options([], Options, Options).
  135extend_options([H|T0], Options, [H|T]) :-
  136	ground(H), !,
  137	extend_options(T0, Options, T).
  138extend_options([_|T0], Options, T) :-
  139	extend_options(T0, Options, T).
 check_flooding
See whether the client associated with a session is flooding us and if so, return a resource error.
  147check_flooding :-
  148	get_time(Now),
  149	(   http_session_retract(websocket(Score, Last))
  150	->  Passed is Now-Last,
  151	    NewScore is Score*(2**(-Passed/60)) + 10
  152	;   NewScore = 10,
  153	    Passed = 0
  154	),
  155	http_session_assert(websocket(NewScore, Now)),
  156	(   NewScore > 50
  157	->  throw(http_reply(resource_error(
  158				 websocket(reconnect(Passed, NewScore)))))
  159	;   true
  160	).
 accept_chat(+Session, +Options, +WebSocket)
  164accept_chat(Session, Options, WebSocket) :-
  165	must_succeed(accept_chat_(Session, Options, WebSocket)).
  166
  167accept_chat_(Session, Options, WebSocket) :-
  168	create_chat_room,
  169	(   reconnect_token(WSID, Token, Options),
  170	    retractall(visitor_status(WSID, lost(_))),
  171	    existing_visitor(WSID, Session, Token, TmpUser, UserData),
  172	    hub_add(swish_chat, WebSocket, WSID)
  173	->  Reason = rejoined
  174	;   hub_add(swish_chat, WebSocket, WSID),
  175	    must_succeed(create_visitor(WSID, Session, Token,
  176					TmpUser, UserData, Options)),
  177	    Reason = joined
  178	),
  179	visitor_count(Visitors),
  180	option(check_login(CheckLogin), Options, true),
  181	Msg = _{ type:welcome,
  182		 uid:TmpUser,
  183		 wsid:WSID,
  184		 reconnect:Token,
  185		 visitors:Visitors,
  186		 check_login:CheckLogin
  187	       },
  188	hub_send(WSID, json(UserData.put(Msg))),
  189	must_succeed(chat_broadcast(UserData.put(_{type:Reason,
  190						   visitors:Visitors,
  191						   wsid:WSID}))),
  192	gc_visitors.
  193
  194reconnect_token(WSID, Token, Options) :-
  195	option(reconnect(Token), Options),
  196	visitor_session(WSID, _, Token), !.
  197
  198must_succeed(Goal) :-
  199	catch(Goal, E, print_message(warning, E)), !.
  200must_succeed(Goal) :-
  201	print_message(warning, goal_failed(Goal)).
  202
  203
  204		 /*******************************
  205		 *	        DATA		*
  206		 *******************************/
 visitor_session(?WSId, ?Session, ?Token)
 session_user(?Session, ?TmpUser)
 visitor_data(?TmpUser, ?UserData:dict)
 subscription(?Session, ?Channel, ?SubChannel)
These predicates represent our notion of visitors.
Arguments:
WSID- is the identifier of the web socket. As we may have to reconnect lost connections, this is may be replaced.
Session- is the session identifier. This is used to connect SWISH actions to WSIDs.
TmpUser- is the ID with which we identify the user for this run. The value is a UUID and thus doesn't reveal the real identity of the user.
UserDict- is a dict that holds information about the real user identity. This can be empty if no information is known about this user.
  226:- dynamic
  227	visitor_status/2,		% WSID, Status
  228	visitor_session/3,		% WSID, Session, Token
  229	session_user/2,			% Session, TmpUser
  230	visitor_data/2,			% TmpUser, Data
  231	subscription/3.			% WSID, Channel, SubChannel
 visitor(?WSID) is nondet
True when WSID should be considered an active visitor.
  237visitor(WSID) :-
  238	visitor_session(WSID, _Session, _Token),
  239	\+ inactive(WSID, 30).
  240
  241visitor_count(Count) :-
  242	aggregate_all(count, visitor(_), Count).
 inactive(+WSID, +Timeout) is semidet
True if WSID is inactive. This means we lost the connection at least Timeout seconds ago.
  249inactive(WSID, Timeout) :-
  250	visitor_status(WSID, lost(Lost)),
  251	get_time(Now),
  252	Now - Lost > Timeout.
 visitor_session(?WSID, ?Session) is nondet
True if websocket WSID is associated with Session.
  258visitor_session(WSID, Session) :-
  259	visitor_session(WSID, Session, _Token).
 wsid_visitor(?WSID, ?Visitor)
True when WSID is associated with Visitor
  265wsid_visitor(WSID, Visitor) :-
  266	nonvar(WSID), !,
  267	visitor_session(WSID, Session),
  268	session_user(Session, Visitor).
  269wsid_visitor(WSID, Visitor) :-
  270	session_user(Session, Visitor),
  271	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 lost the connection.
  279existing_visitor(WSID, Session, Token, TmpUser, UserData) :-
  280	visitor_session(WSID, Session, Token),
  281	session_user(Session, TmpUser),
  282	visitor_data(TmpUser, UserData), !.
  283existing_visitor(WSID, Session, Token, _, _) :-
  284	retractall(visitor_session(WSID, Session, Token)),
  285	fail.
 create_visitor(+WSID, +Session, ?Token, -TmpUser, -UserData, +Options)
Create a new visitor when a new websocket is established. Options provides information we have about the user:
current_user_info(+Info)
Already logged in user with given information
avatar(Avatar)
Avatar remembered in the browser for this user.
nick_name(NickName)
Nick name remembered in the browser for this user.
  299create_visitor(WSID, Session, Token, TmpUser, UserData, Options) :-
  300	generate_key(Token),
  301	assertz(visitor_session(WSID, Session, Token)),
  302	create_session_user(Session, TmpUser, UserData, Options).
 generate_key(-Key) is det
Generate a random confirmation key
  308generate_key(Key) :-
  309	length(Codes, 16),
  310	maplist(random_between(0,255), Codes),
  311	phrase(base64url(Codes), Encoded),
  312	atom_codes(Key, Encoded).
 destroy_visitor(+WSID)
The web socket WSID has been closed. We should not immediately destroy the temporary user as the browser may soon reconnect due to a page reload or re-establishing the web socket after a temporary network failure. We leave the destruction thereof to the session, but set the session timeout to a fairly short time.
To be done
- We should only inform clients that we have informed about this user.
  325destroy_visitor(WSID) :-
  326	must_be(atom, WSID),
  327	destroy_reason(WSID, Reason),
  328	(   Reason == unload
  329	->  reclaim_visitor(WSID)
  330	;   get_time(Now),
  331	    assertz(visitor_status(WSID, lost(Now)))
  332	),
  333	visitor_count(Count),
  334	chat_broadcast(_{ type:removeUser,
  335			  wsid:WSID,
  336			  reason:Reason,
  337			  visitors:Count
  338			}).
  339
  340destroy_reason(WSID, Reason) :-
  341	retract(visitor_status(WSID, unload)), !,
  342	Reason = unload.
  343destroy_reason(_, close).
 gc_visitors
Reclaim all visitors with whom we have lost the connection and the browser did not reclaim the selection within 5 minutes.
  350:- dynamic last_gc/1.  351
  352gc_visitors :-
  353	last_gc(Last),
  354	get_time(Now),
  355	Now-Last < 300, !.
  356gc_visitors :-
  357	with_mutex(gc_visitors, gc_visitors_sync).
  358
  359gc_visitors_sync :-
  360	get_time(Now),
  361	(   last_gc(Last),
  362	    Now-Last < 300
  363	->  true
  364	;   retractall(last_gc(_)),
  365	    asserta(last_gc(Now)),
  366	    do_gc_visitors
  367	).
  368
  369do_gc_visitors :-
  370	forall(( visitor_session(WSID, _Session, _Token),
  371		 inactive(WSID, 5*60)
  372	       ),
  373	       reclaim_visitor(WSID)).
  374
  375reclaim_visitor(WSID) :-
  376	debug(chat(gc), 'Reclaiming idle ~p', [WSID]),
  377	retractall(visitor_session(WSID, _Session, _Token)),
  378	retractall(visitor_status(WSID, _Status)),
  379	unsubscribe(WSID, _).
 create_session_user(+Session, -User, -UserData, +Options)
Associate a user with the session. The user id is a UUID that is not associated with any persistent notion of a user. The destruction is left to the destruction of the session.
  388:- listen(http_session(end(SessionID, _Peer)),
  389	  destroy_session_user(SessionID)).  390
  391create_session_user(Session, TmpUser, UserData, _Options) :-
  392	session_user(Session, TmpUser),
  393	visitor_data(TmpUser, UserData), !.
  394create_session_user(Session, TmpUser, UserData, Options) :-
  395	uuid(TmpUser),
  396	get_visitor_data(UserData, Options),
  397	assertz(session_user(Session, TmpUser)),
  398	assertz(visitor_data(TmpUser, UserData)).
  399
  400destroy_session_user(Session) :-
  401	forall(visitor_session(WSID, Session, _Token),
  402	       inform_session_closed(WSID, Session)),
  403	retractall(visitor_session(_, Session, _)),
  404	forall(retract(session_user(Session, TmpUser)),
  405	       destroy_visitor_data(TmpUser)).
  406
  407destroy_visitor_data(TmpUser) :-
  408	(   retract(visitor_data(TmpUser, Data)),
  409	    release_avatar(Data.get(avatar)),
  410	    fail
  411	;   true
  412	).
  413
  414inform_session_closed(WSID, Session) :-
  415	ignore(hub_send(WSID, json(_{type:session_closed}))),
  416	session_user(Session, TmpUser),
  417	update_visitor_data(TmpUser, _Data, logout).
 update_visitor_data(+TmpUser, +Data, +Reason) is det
Update the user data for the visitor TmpUser to Data. This is rather complicates due to all the defaulting rules. Reason is one of:
To be done
- Create a more declarative description on where the various attributes must come from.
  434update_visitor_data(TmpUser, _Data, logout) :- !,
  435	anonymise_user_data(TmpUser, NewData),
  436	set_visitor_data(TmpUser, NewData, logout).
  437update_visitor_data(TmpUser, Data, Reason) :-
  438	profile_reason(Reason), !,
  439	(   visitor_data(TmpUser, Old)
  440	;   Old = v{}
  441	),
  442	copy_profile([name,avatar,email], Data, Old, New),
  443	set_visitor_data(TmpUser, New, Reason).
  444update_visitor_data(TmpUser, _{name:Name}, 'set-nick-name') :- !,
  445	visitor_data(TmpUser, Old),
  446	set_nick_name(Old, Name, New),
  447	set_visitor_data(TmpUser, New, 'set-nick-name').
  448update_visitor_data(TmpUser, Data, Reason) :-
  449	set_visitor_data(TmpUser, Data, Reason).
  450
  451profile_reason('profile-edit').
  452profile_reason('login').
  453
  454copy_profile([], _, Data, Data).
  455copy_profile([H|T], New, Data0, Data) :-
  456	copy_profile_field(H, New, Data0, Data1),
  457	copy_profile(T, New, Data1, Data).
  458
  459copy_profile_field(avatar, New, Data0, Data) :-	!,
  460	(   Data1 = Data0.put(avatar,New.get(avatar))
  461	->  Data  = Data1.put(avatar_source, profile)
  462	;   email_gravatar(New.get(email), Avatar),
  463	    valid_gravatar(Avatar)
  464	->  Data = Data0.put(_{avatar:Avatar,avatar_source:email})
  465	;   Avatar = Data0.get(anonymous_avatar)
  466	->  Data = Data0.put(_{avatar:Avatar,avatar_source:client})
  467	;   noble_avatar_url(Avatar, []),
  468	    Data = Data0.put(_{avatar:Avatar,avatar_source:generated,
  469			       anonymous_avatar:Avatar
  470			      })
  471	).
  472copy_profile_field(email, New, Data0, Data) :- !,
  473	(   NewMail = New.get(email)
  474	->  update_avatar_from_email(NewMail, Data0, Data1),
  475	    Data = Data1.put(email, NewMail)
  476	;   update_avatar_from_email('', Data0, Data1),
  477	    (	del_dict(email, Data1, _, Data)
  478	    ->	true
  479	    ;	Data = Data1
  480	    )
  481	).
  482copy_profile_field(F, New, Data0, Data) :-
  483	(   Data = Data0.put(F, New.get(F))
  484	->  true
  485	;   del_dict(F, Data0, _, Data)
  486	->  true
  487	;   Data = Data0
  488	).
  489
  490set_nick_name(Data0, Name, Data) :-
  491	Data = Data0.put(_{name:Name, anonymous_name:Name}).
 update_avatar_from_email(+Email, +DataIn, -Data)
Update the avatar after a change of the known email. If the avatar comes from the profile, no action is needed. If Email has a gravatar, use that. Else use the know or a new generated avatar.
  500update_avatar_from_email(_, Data, Data) :-
  501	Data.get(avatar_source) == profile, !.
  502update_avatar_from_email('', Data0, Data) :-
  503	Data0.get(avatar_source) == email, !,
  504	noble_avatar_url(Avatar, []),
  505	Data = Data0.put(_{avatar:Avatar, anonymous_avatar:Avatar,
  506			   avatar_source:generated}).
  507update_avatar_from_email(Email, Data0, Data) :-
  508	email_gravatar(Email, Avatar),
  509	valid_gravatar(Avatar), !,
  510	Data = Data0.put(avatar, Avatar).
  511update_avatar_from_email(_, Data0, Data) :-
  512	(   Avatar = Data0.get(anonymous_avatar)
  513	->  Data = Data0.put(_{avatar:Avatar, avatar_source:client})
  514	;   noble_avatar_url(Avatar, []),
  515	    Data = Data0.put(_{avatar:Avatar, anonymous_avatar:Avatar,
  516			       avatar_source:generated})
  517	).
 anonymise_user_data(TmpUser, Data)
Create anonymous user profile.
  523anonymise_user_data(TmpUser, Data) :-
  524	visitor_data(TmpUser, Old),
  525	(   _{anonymous_name:AName, anonymous_avatar:AAvatar} :< Old
  526	->  Data = _{anonymous_name:AName, anonymous_avatar:AAvatar,
  527		     name:AName, avatar:AAvatar, avatar_source:client}
  528	;   _{anonymous_avatar:AAvatar} :< Old
  529	->  Data = _{anonymous_avatar:AAvatar,
  530		     avatar:AAvatar, avatar_source:client}
  531	;   _{anonymous_name:AName} :< Old
  532	->  noble_avatar_url(Avatar, []),
  533	    Data = _{anonymous_name:AName, anonymous_avatar:Avatar,
  534		     name:AName, avatar:Avatar, avatar_source:generated}
  535	), !.
  536anonymise_user_data(_, Data) :-
  537	noble_avatar_url(Avatar, []),
  538	Data = _{anonymous_avatar:Avatar,
  539		 avatar:Avatar, avatar_source:generated}.
 set_visitor_data(+TmpUser, +Data, +Reason) is det
Update the user data for the session user TmpUser and forward the changes.
  546set_visitor_data(TmpUser, Data, Reason) :-
  547	retractall(visitor_data(TmpUser, _)),
  548	assertz(visitor_data(TmpUser, Data)),
  549	inform_visitor_change(TmpUser, Reason).
 inform_visitor_change(+TmpUser, +Reason) is det
Inform browsers showing TmpUser that the visitor data has changed. The first clause deals with forwarding from HTTP requests, where we have the session and the second from websocket requests where we have the WSID.
  558inform_visitor_change(TmpUser, Reason) :-
  559	http_in_session(Session), !,
  560	public_user_data(TmpUser, Data),
  561	forall(visitor_session(WSID, Session),
  562	       inform_friend_change(WSID, Data, Reason)).
  563inform_visitor_change(TmpUser, Reason) :-
  564	b_getval(wsid, WSID),
  565	public_user_data(TmpUser, Data),
  566	inform_friend_change(WSID, Data, Reason).
  567
  568inform_friend_change(WSID, Data, Reason) :-
  569	Message = json(_{ type:"profile",
  570			  wsid:WSID,
  571			  reason:Reason
  572			}.put(Data)),
  573	hub_send(WSID, Message),
  574	forall(viewing_same_file(WSID, Friend),
  575	       ignore(hub_send(Friend, Message))).
  576
  577viewing_same_file(WSID, Friend) :-
  578	subscription(WSID, gitty, File),
  579	subscription(Friend, gitty, File),
  580	Friend \== WSID.
 subscribe(+WSID, +Channel) is det
  584subscribe(WSID, Channel) :-
  585	subscribe(WSID, Channel, _SubChannel).
  586subscribe(WSID, Channel, SubChannel) :-
  587	(   subscription(WSID, Channel, SubChannel)
  588	->  true
  589	;   assertz(subscription(WSID, Channel, SubChannel))
  590	).
  591
  592unsubscribe(WSID, Channel) :-
  593	unsubscribe(WSID, Channel, _SubChannel).
  594unsubscribe(WSID, Channel, SubChannel) :-
  595	retractall(subscription(WSID, Channel, SubChannel)).
 sync_gazers(+WSID, +Files:list(atom)) is det
A browser signals it has Files open. This happens when a SWISH instance is created as well as when a SWISH instance changes state, such as closing a tab, adding a tab, bringing a tab to the foreground, etc.
  604sync_gazers(WSID, Files0) :-
  605	findall(F, subscription(WSID, gitty, F), Viewing0),
  606	sort(Files0, Files),
  607	sort(Viewing0, Viewing),
  608	(   Files == Viewing
  609	->  true
  610	;   ord_subtract(Files, Viewing, New),
  611	    add_gazing(WSID, New),
  612	    ord_subtract(Viewing, Files, Left),
  613	    del_gazing(WSID, Left)
  614	).
  615
  616add_gazing(_, []) :- !.
  617add_gazing(WSID, Files) :-
  618	inform_me_about_existing_gazers(WSID, Files),
  619	inform_existing_gazers_about_newby(WSID, Files).
  620
  621inform_me_about_existing_gazers(WSID, Files) :-
  622	findall(Gazer, files_gazer(Files, Gazer), Gazers),
  623	ignore(hub_send(WSID, json(_{type:"gazers", gazers:Gazers}))).
  624
  625files_gazer(Files, Gazer) :-
  626	member(File, Files),
  627	subscription(WSID, gitty, File),
  628	visitor_session(WSID, Session),
  629	session_user(Session, UID),
  630	public_user_data(UID, Data),
  631	Gazer = _{file:File, uid:UID, wsid:WSID}.put(Data).
  632
  633inform_existing_gazers_about_newby(WSID, Files) :-
  634	forall(member(File, Files),
  635	       signal_gazer(WSID, File)).
  636
  637signal_gazer(WSID, File) :-
  638	subscribe(WSID, gitty, File),
  639	broadcast_event(opened(File), File, WSID).
  640
  641del_gazing(_, []) :- !.
  642del_gazing(WSID, Files) :-
  643	forall(member(File, Files),
  644	       del_gazing1(WSID, File)).
  645
  646del_gazing1(WSID, File) :-
  647	broadcast_event(closed(File), File, WSID),
  648	unsubscribe(WSID, gitty, File).
 add_user_details(+Message, -Enriched) is det
Add additional information to a message. Message must contain a uid field.
  655add_user_details(Message, Enriched) :-
  656	public_user_data(Message.uid, Data),
  657	Enriched = Message.put(Data).
 public_user_data(+UID, -Public:dict) is det
True when Public provides the information we publically share about UID. This is currently the name and avatar.
  664public_user_data(UID, Public) :-
  665	visitor_data(UID, Data),
  666	(   _{name:Name, avatar:Avatar} :< Data
  667	->  Public = _{name:Name, avatar:Avatar}
  668	;   _{avatar:Avatar} :< Data
  669	->  Public = _{avatar:Avatar}
  670	;   Public = _{}
  671	).
 get_visitor_data(-Data:dict, +Options) is det
Optain data for a new visitor. Options include:
identity(+Identity)
Identity information provided by authenticate/2. Always present.
avatar(+URL)
Avatar provided by the user
nick_name(+Name)
Nick name provided by the user.

Data always contains an avatar key and optionally contains a name and email key. If the avatar is generated there is also a key avatar_generated with the value true.

bug
- This may check for avatar validity, which may take long. Possibly we should do this in a thread.
  692get_visitor_data(Data, Options) :-
  693	option(identity(Identity), Options),
  694	findall(N-V, visitor_property(Identity, Options, N, V), Pairs),
  695	dict_pairs(Data, v, Pairs).
  696
  697visitor_property(Identity, Options, name, Name) :-
  698	(   user_property(Identity, name(Name))
  699	->  true
  700	;   option(nick_name(Name), Options)
  701	).
  702visitor_property(Identity, _, email, Email) :-
  703	user_property(Identity, email(Email)).
  704visitor_property(Identity, Options, Name, Value) :-
  705	(   user_property(Identity, avatar(Avatar))
  706	->  avatar_property(Avatar, profile, Name, Value)
  707	;   user_property(Identity, email(Email)),
  708	    email_gravatar(Email, Avatar),
  709	    valid_gravatar(Avatar)
  710	->  avatar_property(Avatar, email, Name, Value)
  711	;   option(avatar(Avatar), Options)
  712	->  avatar_property(Avatar, client, Name, Value)
  713	;   noble_avatar_url(Avatar, Options),
  714	    avatar_property(Avatar, generated, Name, Value)
  715	).
  716visitor_property(_, Options, anonymous_name, Name) :-
  717	option(nick_name(Name), Options).
  718visitor_property(_, Options, anonymous_avatar, Avatar) :-
  719	option(avatar(Avatar), Options).
  720
  721
  722avatar_property(Avatar, _Source, avatar,        Avatar).
  723avatar_property(_Avatar, Source, avatar_source, Source).
  724
  725
  726		 /*******************************
  727		 *	   NOBLE AVATAR		*
  728		 *******************************/
  729
  730:- http_handler(swish('avatar/'), reply_avatar, [id(avatar), prefix]).
 reply_avatar(+Request)
HTTP handler for Noble Avatar images. Using create_avatar/2 re-creates avatars from the file name, so we can safely discard the avatar file store.
  738reply_avatar(Request) :-
  739	option(path_info(Local), Request),
  740	(   absolute_file_name(noble_avatar(Local), Path,
  741			       [ access(read),
  742				 file_errors(fail)
  743			       ])
  744	->  true
  745	;   create_avatar(Local, Path)
  746	),
  747	http_reply_file(Path, [unsafe(true)], Request).
  748
  749
  750noble_avatar_url(HREF, Options) :-
  751	option(avatar(HREF), Options), !.
  752noble_avatar_url(HREF, _Options) :-
  753	noble_avatar(_Gender, Path, true),
  754	file_base_name(Path, File),
  755	http_absolute_location(swish(avatar/File), HREF, []).
  756
  757
  758		 /*******************************
  759		 *	   BROADCASTING		*
  760		 *******************************/
Send Message to all known SWISH clients. Message is a valid JSON object, i.e., a dict or option list.
Arguments:
Channel- is either an atom or a term Channel/SubChannel, where both Channel and SubChannel are atoms.
  771chat_broadcast(Message) :-
  772	debug(chat(broadcast), 'Broadcast: ~p', [Message]),
  773	hub_broadcast(swish_chat, json(Message)).
  774
  775chat_broadcast(Message, Channel/SubChannel) :- !,
  776	must_be(atom, Channel),
  777	must_be(atom, SubChannel),
  778	debug(chat(broadcast), 'Broadcast on ~p: ~p',
  779	      [Channel/SubChannel, Message]),
  780	hub_broadcast(swish_chat, json(Message),
  781		      subscribed(Channel, SubChannel)).
  782chat_broadcast(Message, Channel) :-
  783	must_be(atom, Channel),
  784	debug(chat(broadcast), 'Broadcast on ~p: ~p', [Channel, Message]),
  785	hub_broadcast(swish_chat, json(Message),
  786		      subscribed(Channel)).
  787
  788subscribed(Channel, WSID) :-
  789	subscription(WSID, Channel, _).
  790subscribed(Channel, SubChannel, WSID) :-
  791	subscription(WSID, Channel, SubChannel).
  792
  793
  794		 /*******************************
  795		 *	     CHAT ROOM		*
  796		 *******************************/
  797
  798create_chat_room :-
  799	current_hub(swish_chat, _), !.
  800create_chat_room :-
  801	with_mutex(swish_chat, create_chat_room_sync).
  802
  803create_chat_room_sync :-
  804	current_hub(swish_chat, _), !.
  805create_chat_room_sync :-
  806	hub_create(swish_chat, Room, _{}),
  807	thread_create(swish_chat(Room), _, [alias(swish_chat)]).
  808
  809swish_chat(Room) :-
  810	(   catch(swish_chat_event(Room), E, chat_exception(E))
  811	->  true
  812	;   print_message(warning, goal_failed(swish_chat_event(Room)))
  813	),
  814	swish_chat(Room).
  815
  816chat_exception('$aborted') :- !.
  817chat_exception(E) :-
  818	print_message(warning, E).
  819
  820swish_chat_event(Room) :-
  821	thread_get_message(Room.queues.event, Message),
  822	(   handle_message(Message, Room)
  823	->  true
  824	;   print_message(warning, goal_failed(handle_message(Message, Room)))
  825	).
 handle_message(+Message, +Room)
Handle incoming messages
  831handle_message(Message, _Room) :-
  832	websocket{opcode:text} :< Message, !,
  833	atom_json_dict(Message.data, JSON, []),
  834	debug(chat(received), 'Received from ~p: ~p', [Message.client, JSON]),
  835	WSID = Message.client,
  836	setup_call_cleanup(
  837	    b_setval(wsid, WSID),
  838	    json_message(JSON, WSID),
  839	    nb_delete(wsid)).
  840handle_message(Message, _Room) :-
  841	hub{joined:WSID} :< Message, !,
  842	debug(chat(visitor), 'Joined: ~p', [WSID]).
  843handle_message(Message, _Room) :-
  844	hub{left:WSID, reason:write(Lost)} :< Message, !,
  845	(   destroy_visitor(WSID)
  846	->  debug(chat(visitor), 'Left ~p due to write error for ~p',
  847		  [WSID, Lost])
  848	;   true
  849	).
  850handle_message(Message, _Room) :-
  851	hub{left:WSID} :< Message, !,
  852	(   destroy_visitor(WSID)
  853	->  debug(chat(visitor), 'Left: ~p', [WSID])
  854	;   true
  855	).
  856handle_message(Message, _Room) :-
  857	websocket{opcode:close, client:WSID} :< Message, !,
  858	debug(chat(visitor), 'Left: ~p', [WSID]),
  859	destroy_visitor(WSID).
  860handle_message(Message, _Room) :-
  861	debug(chat(ignored), 'Ignoring chat message ~p', [Message]).
 json_message(+Message, +WSID) is det
Process a JSON message translated to a dict. The following messages are understood:
  880json_message(Dict, WSID) :-
  881	_{ type: "subscribe",
  882	   channel:ChannelS, sub_channel:SubChannelS} :< Dict, !,
  883	atom_string(Channel, ChannelS),
  884	atom_string(SubChannel, SubChannelS),
  885	subscribe(WSID, Channel, SubChannel).
  886json_message(Dict, WSID) :-
  887	_{type: "subscribe", channel:ChannelS} :< Dict, !,
  888	atom_string(Channel, ChannelS),
  889	subscribe(WSID, Channel).
  890json_message(Dict, WSID) :-
  891	_{ type: "unsubscribe",
  892	   channel:ChannelS, sub_channel:SubChannelS} :< Dict, !,
  893	atom_string(Channel, ChannelS),
  894	atom_string(SubChannel, SubChannelS),
  895	unsubscribe(WSID, Channel, SubChannel).
  896json_message(Dict, WSID) :-
  897	_{type: "unsubscribe", channel:ChannelS} :< Dict, !,
  898	atom_string(Channel, ChannelS),
  899	unsubscribe(WSID, Channel).
  900json_message(Dict, WSID) :-
  901	_{type: "unload"} :< Dict, !,	% clean close/reload
  902	sync_gazers(WSID, []),
  903	assertz(visitor_status(WSID, unload)).
  904json_message(Dict, WSID) :-
  905	_{type: "has-open-files", files:FileDicts} :< Dict, !,
  906	maplist(dict_file_name, FileDicts, Files),
  907	sync_gazers(WSID, Files).
  908json_message(Dict, WSID) :-
  909	_{type: "reloaded", file:FileS, commit:Hash} :< Dict, !,
  910	atom_string(File, FileS),
  911	event_html(reloaded(File), HTML),
  912	Message = _{ type:notify,
  913		     wsid:WSID,
  914		     html:HTML,
  915		     event:reloaded,
  916		     argv:[File,Hash]
  917		   },
  918	chat_broadcast(Message, gitty/File).
  919json_message(Dict, WSID) :-
  920	_{type: "set-nick-name", name:Name} :< Dict, !,
  921	wsid_visitor(WSID, Visitor),
  922	update_visitor_data(Visitor, _{name:Name}, 'set-nick-name').
  923json_message(Dict, WSID) :-
  924	_{type: "chat-message", docid:_} :< Dict, !,
  925	chat_add_user_id(WSID, Dict, Message),
  926	chat_relay(Message).
  927json_message(Dict, _WSID) :-
  928	debug(chat(ignored), 'Ignoring JSON message ~p', [Dict]).
  929
  930dict_file_name(Dict, File) :-
  931	atom_string(File, Dict.get(file)).
  932
  933
  934		 /*******************************
  935		 *	   CHAT MESSAGES	*
  936		 *******************************/
 chat_add_user_id(+WSID, +Message0, -Message) is det
Decorate a message with the user credentials.
  942chat_add_user_id(WSID, Dict, Message) :-
  943	visitor_session(WSID, Session, _Token),
  944	session_user(Session, Visitor),
  945	visitor_data(Visitor, UserData),
  946	User0 = u{avatar:UserData.avatar,
  947		  wsid:WSID
  948		 },
  949	(   Name = UserData.get(name)
  950	->  User1 = User0.put(name, Name)
  951	;   User1 = User0
  952	),
  953	(   http_current_session(Session, profile_id(ProfileID))
  954	->  User = User1.put(profile_id, ProfileID)
  955	;   User = User1
  956	),
  957	Message = Dict.put(user, User).
 chat_about(+DocID, +Message) is det
Distribute a chat message about DocID.
  964chat_about(DocID, Message) :-
  965	chat_relay(Message.put(docid, DocID)).
 chat_relay(+Message) is det
Store and relay a chat message.
  971chat_relay(Message) :-
  972	chat_enrich(Message, Message1),
  973	chat_send(Message1).
 chat_enrich(+Message0, -Message) is det
Add time and identifier to the chat message.
  979chat_enrich(Message0, Message) :-
  980	get_time(Now),
  981	uuid(ID),
  982	Message = Message0.put(_{time:Now, id:ID}).
 chat_send(+Message)
Relay the chat message Message. If the message has a volatile property it is broadcasted, but not stored.
  989chat_send(Message) :-
  990	atom_concat("gitty:", File, Message.docid),
  991	broadcast(swish(chat(Message))),
  992	(   Message.get(volatile) == true
  993	->  true
  994	;   chat_store(Message)
  995	),
  996	chat_broadcast(Message, gitty/File).
  997
  998
  999		 /*******************************
 1000		 *	      EVENTS		*
 1001		 *******************************/
 1002
 1003:- unlisten(swish(_)),
 1004   listen(swish(Event), chat_event(Event)).
 chat_event(+Event) is semidet
Event happened inside SWISH. Currently triggered events:
updated(+File, +From, +To)
File was updated from hash From to hash To.
profile(+ProfileID)
Session was associated with user with profile ProfileID
logout(+ProfileID)
User logged out. If the login was based on HTTP authentication ProfileID equals http.
 1018chat_event(Event) :-
 1019	broadcast_event(Event),
 1020	http_session_id(Session),
 1021	debug(event, 'Event: ~p, session ~q', [Event, Session]),
 1022	event_file(Event, File), !,
 1023	(   visitor_session(WSID, Session),
 1024	    subscription(WSID, gitty, File)
 1025	->  true
 1026	;   visitor_session(WSID, Session)
 1027	->  true
 1028	;   WSID = undefined
 1029	),
 1030	session_broadcast_event(Event, File, Session, WSID).
 1031chat_event(logout(_ProfileID)) :- !,
 1032	http_session_id(Session),
 1033	session_user(Session, User),
 1034	update_visitor_data(User, _, logout).
 1035chat_event(visitor_count(Count)) :-		% request
 1036	visitor_count(Count).
 1037
 1038:- if(current_predicate(current_profile/2)). 1039
 1040chat_event(profile(ProfileID)) :- !,
 1041	current_profile(ProfileID, Profile),
 1042	http_session_id(Session),
 1043	session_user(Session, User),
 1044	update_visitor_data(User, Profile, login).
 propagate_profile_change(+ProfileID, +Attribute, +Value)
Trap external changes to the profile.
 1050:- listen(user_profile(modified(ProfileID, Name, _Old, New)),
 1051          propagate_profile_change(ProfileID, Name, New)). 1052
 1053propagate_profile_change(ProfileID, _, _) :-
 1054	http_current_session(Session, profile_id(ProfileID)),
 1055	session_user(Session, User),
 1056	current_profile(ProfileID, Profile),
 1057	update_visitor_data(User, Profile, 'profile-edit').
 1058
 1059:- endif.
 broadcast_event(+Event) is semidet
If true, broadcast this event.
 1065broadcast_event(updated(_File, _From, _To)).
 broadcast_event(+Event, +File, +WSID) is det
Event happened that is related to File in WSID. Broadcast it to subscribed users as a notification. Always succeeds, also if the message cannot be delivered.
To be done
- Extend the structure to allow other browsers to act.
 1076broadcast_event(Event, File, WSID) :-
 1077	visitor_session(WSID, Session),
 1078	session_broadcast_event(Event, File, Session, WSID), !.
 1079broadcast_event(_, _, _).
 1080
 1081session_broadcast_event(Event, File, Session, WSID) :-
 1082	session_user(Session, UID),
 1083	event_html(Event, HTML),
 1084	Event =.. [EventName|Argv],
 1085	Message0 = _{ type:notify,
 1086		      uid:UID,
 1087		      html:HTML,
 1088		      event:EventName,
 1089		      event_argv:Argv,
 1090		      wsid:WSID
 1091		    },
 1092	add_user_details(Message0, Message),
 1093	chat_broadcast(Message, gitty/File).
Describe an event as an HTML message to be displayed in the client's notification area.
 1100event_html(Event, HTML) :-
 1101	(   phrase(event_message(Event), Tokens)
 1102	->  true
 1103	;   phrase(html('Unknown-event: ~p'-[Event]), Tokens)
 1104	),
 1105	delete(Tokens, nl(_), SingleLine),
 1106	with_output_to(string(HTML), print_html(SingleLine)).
 1107
 1108event_message(created(File)) -->
 1109	html([ 'Created ', \file(File) ]).
 1110event_message(reloaded(File)) -->
 1111	html([ 'Reloaded ', \file(File) ]).
 1112event_message(updated(File, _From, _To)) -->
 1113	html([ 'Saved ', \file(File) ]).
 1114event_message(deleted(File, _From, _To)) -->
 1115	html([ 'Deleted ', \file(File) ]).
 1116event_message(closed(File)) -->
 1117	html([ 'Closed ', \file(File) ]).
 1118event_message(opened(File)) -->
 1119	html([ 'Opened ', \file(File) ]).
 1120event_message(download(File)) -->
 1121	html([ 'Opened ', \file(File) ]).
 1122event_message(download(Store, FileOrHash, _Format)) -->
 1123	{ event_file(download(Store, FileOrHash), File)
 1124	},
 1125	html([ 'Opened ', \file(File) ]).
 1126
 1127file(File) -->
 1128	html(a(href('/p/'+File), File)).
 event_file(+Event, -File) is semidet
True when Event is associated with File.
 1134event_file(created(File, _Commit), File).
 1135event_file(updated(File, _Commit), File).
 1136event_file(deleted(File, _Commit), File).
 1137event_file(download(Store, FileOrHash, _Format), File) :-
 1138	(   is_gitty_hash(FileOrHash)
 1139	->  gitty_commit(Store, FileOrHash, Meta),
 1140	    File = Meta.name
 1141	;   File = FileOrHash
 1142	).
 1143
 1144
 1145		 /*******************************
 1146		 *	   NOTIFICATION		*
 1147		 *******************************/
 chat_to_profile(ProfileID, :HTML) is det
Send a HTML notification to users logged in using ProfileID.
 1153chat_to_profile(ProfileID, HTML) :-
 1154	(   http_current_session(Session, profile_id(ProfileID)),
 1155	    visitor_session(WSID, Session),
 1156	    html_string(HTML, String),
 1157	    hub_send(WSID, json(_{ wsid:WSID,
 1158				   type:notify,
 1159				   html:String
 1160				 })),
 1161	    debug(notify(chat), 'Notify to ~p: ~p', [ProfileID, String]),
 1162	    fail
 1163	;   true
 1164	).
 1165
 1166html_string(HTML, String) :-
 1167	phrase(html(HTML), Tokens),
 1168	delete(Tokens, nl(_), SingleLine),
 1169	with_output_to(string(String), print_html(SingleLine)).
 1170
 1171
 1172
 1173
 1174		 /*******************************
 1175		 *	       UI		*
 1176		 *******************************/
 1177
 1178:- multifile swish_config:config/2.
 notifications(+Options)//
The chat element is added to the navbar and managed by web/js/chat.js
 1185notifications(_Options) -->
 1186	{ swish_config:config(chat, true) }, !,
 1187	html(div(class(chat),
 1188		 [ div(class('chat-users'),
 1189		       ul([ class([nav, 'navbar-nav', 'pull-right']),
 1190			    id(chat)
 1191			  ], [])),
 1192		   div(class('user-count'),
 1193		       [ span(id('user-count'), '?'),
 1194			 ' users online'
 1195		       ])
 1196		 ])).
 1197notifications(_Options) -->
 1198	[].
 1199
 1200
 1201		 /*******************************
 1202		 *	      MESSAGES		*
 1203		 *******************************/
 1204
 1205:- multifile
 1206	prolog:message//1. 1207
 1208prolog:message(websocket(reconnect(Passed, Score))) -->
 1209	[ 'WebSocket: too frequent reconnect requests (~1f sec; score = ~1f)'-
 1210	  [Passed, Score] ]