35
36:- module(swish_plugin_user_profile,
37 [
38 ]). 39:- use_module(library(option)). 40:- use_module(library(user_profile)). 41:- use_module(library(http/http_dispatch)). 42:- use_module(library(http/http_session)). 43:- use_module(library(http/http_wrapper)). 44:- use_module(library(http/html_write)). 45:- use_module(library(http/http_json)). 46:- use_module(library(apply)). 47:- use_module(library(error)). 48:- use_module(library(lists)). 49:- use_module(library(debug)). 50:- use_module(library(broadcast)). 51:- use_module(library(pairs)). 52
53:- use_module('../config', []). 54:- use_module(login). 55:- use_module('../authenticate'). 56:- use_module('../bootstrap'). 57:- use_module('../form'). 58:- use_module('../avatar').
100:- http_handler(swish(user_profile), user_profile, [id(user_profile)]). 101:- http_handler(swish(save_profile), save_profile, []). 102:- http_handler(swish(update_profile), update_profile, []). 103:- http_handler(swish(delete_profile), delete_profile, []). 104
105
106:- multifile
107 swish_config:user_info/3,
108 swish_config:reply_logged_in/1, 109 swish_config:reply_logged_out/1, 110 swish_config:user_profile/2, 111 user_profile:attribute/3,
112 user_profile:attribute_mapping/3. 113
114
115
132swish_config:reply_logged_in(Options) :-
133 option(user_info(Info), Options),
134 known_profile(Info, ProfileID),
135 !,
136 option(profile_id(ProfileID), Options, _),
137 associate_profile(ProfileID),
138 ( option(reply(html), Options, html)
139 -> reply_html_page(
140 title('Logged in'),
141 [ h4('Welcome back'),
142 p(\last_login(ProfileID)),
143 \login_continue_button
144 ])
145 ; true
146 ).
147swish_config:reply_logged_in(Options) :-
148 option(user_info(Info), Options),
149 create_profile(Info, Info.get(identity_provider), ProfileID),
150 !,
151 option(profile_id(ProfileID), Options, _),
152 http_open_session(_SessionID, []),
153 associate_profile(ProfileID),
154 update_last_login(ProfileID),
155 ( option(reply(html), Options, html)
156 -> reply_html_page(
157 title('Logged in'),
158 [ h4('Welcome'),
159 p([ 'You appear to be a new user. You may inspect, update \c
160 and delete your profile using the drop-down menu associated \c
161 with the login/logout widget.'
162 ]),
163 \login_continue_button
164 ])
165 ; true
166 ).
173known_profile(Info, ProfileID) :-
174 IdProvider = Info.get(identity_provider),
175 profile_default(IdProvider, Info, external_identity(ID)),
176 profile_property(ProfileID, external_identity(ID)),
177 profile_property(ProfileID, identity_provider(IdProvider)),
178 !.
186associate_profile(ProfileID) :-
187 http_session_assert(profile_id(ProfileID)),
188 broadcast(swish(profile(ProfileID))).
198:- listen(http_session(begin(_SessionID, _Peer)),
199 init_session_profile). 200
201init_session_profile :-
202 http_current_request(Request),
203 authenticate(Request, Identity),
204 known_profile(Request, Identity, ProfileID),
205 associate_profile(ProfileID).
206
207known_profile(_Request, Identity, ProfileID) :-
208 known_profile(Identity, ProfileID),
209 !.
210known_profile(Request, Identity, ProfileID) :-
211 local == Identity.get(identity_provider),
212 swish_config:user_info(Request, local, UserInfo),
213 create_profile(UserInfo, local, ProfileID).
220swish_config:reply_logged_out(Options) :-
221 http_in_session(_),
222 !,
223 forall(http_session_retract(profile_id(ProfileID)),
224 broadcast(swish(logout(ProfileID)))),
225 reply_logged_out_page(Options).
226swish_config:reply_logged_out(_) :-
227 broadcast(swish(logout(-))). 228
229:- listen(swish(logout(http)), cancel_session_profile). 230
231cancel_session_profile :-
232 ( http_in_session(_)
233 -> forall(http_session_retract(profile_id(ProfileID)),
234 broadcast(swish(logout(ProfileID))))
235 ; true
236 ).
242create_profile(UserInfo, IdProvider, ProfileID) :-
243 user_profile_values(UserInfo, IdProvider, Defaults),
244 profile_create(ProfileID, Defaults).
245
246user_profile_values(UserInfo, IdProvider, Defaults) :-
247 findall(Default,
248 profile_default(IdProvider, UserInfo, Default),
249 Defaults0),
250 add_gravatar(Defaults0, Defaults).
251
252profile_default(IdProvider, UserInfo, Default) :-
253 ( nonvar(Default)
254 -> functor(Default, Name, 1)
255 ; true
256 ),
257 user_profile:attribute(Name, _, _),
258 user_profile:attribute_mapping(Name, IdProvider, UName),
259 catch(profile_canonical_value(Name, UserInfo.get(UName), Value),
260 error(type_error(_,_),_),
261 fail),
262 Default =.. [Name,Value].
263profile_default(local, UserInfo, email_verified(true)) :-
264 _ = UserInfo.get(email). 265
266add_gravatar(Defaults0, Defaults) :-
267 \+ memberchk(avatar(_), Defaults0),
268 memberchk(email(Email), Defaults0),
269 email_gravatar(Email, Avatar0),
270 valid_gravatar(Avatar0),
271 catch(profile_canonical_value(avatar, Avatar0, Avatar),
272 error(type_error(_,_),_),
273 fail),
274 !,
275 Defaults = [avatar(Avatar)|Defaults0].
276add_gravatar(Defaults, Defaults).
283last_login(User) -->
284 { profile_property(User, last_login(TimeStamp)),
285 profile_property(User, last_peer(Peer)),
286 format_time(string(Time), '%+', TimeStamp),
287 update_last_login(User)
288 },
289 !,
290 html('Last login: ~w from ~w'-[Time, Peer]).
291last_login(User) -->
292 { update_last_login(User) }.
293
294update_last_login(User) :-
295 http_current_request(Request),
296 http_peer(Request, Peer),
297 get_time(Now),
298 NowInt is round(Now),
299 set_profile(User, last_peer(Peer)),
300 set_profile(User, last_login(NowInt)).
307swish_config:user_profile(_Request, Profile) :-
308 http_in_session(_SessionID),
309 http_session_data(profile_id(User)),
310 current_profile(User, Profile0),
311 Profile = Profile0.put(profile_id, User).
312
313
314
323user_profile(_Request) :-
324 http_in_session(_SessionID),
325 http_session_data(profile_id(User)), !,
326 current_profile(User, Profile),
327 findall(Field, user_profile:attribute(Field, _, _), Fields),
328 convlist(bt_field(Profile), Fields, FieldWidgets),
329 buttons(Buttons),
330 append(FieldWidgets, Buttons, Widgets),
331 reply_html_page(
332 title('User profile'),
333 \bt_form(Widgets,
334 [ class('form-horizontal'),
335 label_columns(sm-3)
336 ])).
337user_profile(_Request) :-
338 reply_html_page(
339 title('User profile'),
340 [ p('You must be logged in to view your profile'),
341 \bt_form([ button_group(
342 [ button(cancel, button,
343 [ type(danger),
344 data([dismiss(modal)])
345 ])
346 ], [])
347 ],
348 [ class('form-horizontal'),
349 label_columns(sm-3)
350 ])
351 ]).
352
353
354bt_field(Profile, Name, Field) :-
355 user_profile:attribute(Name, Type, AOptions),
356 !,
357 \+ option(hidden(true), AOptions),
358 bt_field(Profile, Name, Type, AOptions, Field).
359
360bt_field(Profile, Name, Type, AOptions, select(Name, Values, Options)) :-
361 Type = oneof(Values),
362 !,
363 phrase(( (value_opt(Profile, Type, Name) -> [] ; []),
364 (access_opt(AOptions) -> [] ; [])
365 ), Options).
366bt_field(Profile, Name, Type, AOptions, input(Name, IType, Options)) :-
367 input_type(Type, IType),
368 phrase(( (value_opt(Profile, Type, Name) -> [] ; []),
369 (access_opt(AOptions) -> [] ; []),
370 (data_type_opt(Type) -> [] ; [])
371 ), Options).
372
373input_type(boolean, checkbox) :-
374 !.
375input_type(_, text).
376
377value_opt(Profile, Type, Name) -->
378 { Value0 = Profile.get(Name),
379 display_value(Type, Value0, Value)
380 },
381 [ value(Value) ].
382access_opt(AOptions) -->
383 { option(access(ro), AOptions) },
384 [ disabled(true) ].
385data_type_opt(_Type) --> 386 [].
387
388display_value(time_stamp(Format), Stamp, Value) :-
389 !,
390 format_time(string(Value), Format, Stamp).
391display_value(_, Value0, Value) :-
392 atomic(Value0),
393 !,
394 Value = Value0.
395display_value(_, Value0, Value) :-
396 format(string(Value), '~w', [Value0]).
397
398buttons(
399 [ button_group(
400 [ button(done, button,
401 [ type(primary),
402 data([dismiss(modal)])
403 ]),
404 button(save, submit,
405 [ type(success),
406 label('Save profile'),
407 data([action(SaveHREF)])
408 ]),
409 button(reset, submit,
410 [ type(warning),
411 label('Reset profile'),
412 data([action(UpdateHREF), form_data(false)])
413 ]),
414 button(delete, submit,
415 [ type(danger),
416 label('Delete profile'),
417 data([action(DeleteHREF), form_data(false)])
418 ])
419 ],
420 [
421 ])
422 ]) :-
423 http_link_to_id(save_profile, [], SaveHREF),
424 http_link_to_id(update_profile, [], UpdateHREF),
425 http_link_to_id(delete_profile, [], DeleteHREF).
426
427
428
438save_profile(Request) :-
439 http_read_json_dict(Request, Dict),
440 debug(profile(update), 'Got ~p', [Dict]),
441 http_in_session(_SessionID),
442 http_session_data(profile_id(User)),
443 dict_pairs(Dict, _, Pairs),
444 maplist(validate_term, Pairs, VPairs, Validate),
445 catch(validate_form(Dict, Validate), E, true),
446 ( var(E)
447 -> dict_pairs(VDict, _, VPairs),
448 save_profile(User, VDict),
449 current_profile(User, Profile),
450 reply_json_dict(_{status:success, profile:Profile})
451 ; message_to_string(E, Msg),
452 Error = _{code:form_error, data:Msg},
453 reply_json_dict(_{status:error, error:Error})
454 ).
455
456validate_term(Name-_, Name-Value,
457 field(Name, Value, [strip,default("")|Options])) :-
458 user_profile:attribute(Name, Type, FieldOptions),
459 ( ( option(access(ro), FieldOptions)
460 ; option(hidden(true), FieldOptions)
461 )
462 -> permission_error(modify, profile, Name)
463 ; true
464 ),
465 type_options(Type, Options).
466
467type_options(Type, [Type]).
473save_profile(User, Dict) :-
474 dict_pairs(Dict, _, Pairs),
475 maplist(save_profile_field(User), Pairs).
476
477save_profile_field(User, Name-Value) :-
478 ( Term =.. [Name,Old],
479 profile_property(User, Term)
480 -> true
481 ; Old = ""
482 ),
483 update_profile_field(User, Name, Old, Value).
484
485update_profile_field(User, Name, Old, "") :-
486 !,
487 profile_remove(User, Name),
488 broadcast(user_profile(modified(User, Name, Old, ""))).
489update_profile_field(User, Name, Old, New0) :-
490 profile_canonical_value(Name, New0, New),
491 ( Old == New
492 -> true
493 ; set_profile(User, Name=New),
494 broadcast(user_profile(modified(User, Name, Old, New)))
495 ).
502update_profile(Request) :-
503 swish_config:user_info(Request, Server, UserInfo),
504 http_in_session(_SessionID),
505 http_session_data(profile_id(User)),
506 user_profile_values(UserInfo, Server, ServerInfo),
507 dict_pairs(ServerInfo, _, Pairs),
508 maplist(update_profile_field(User), Pairs),
509 current_profile(User, Profile),
510 reply_json_dict(_{status:success, profile:Profile}).
511
512update_profile_field(User, Name-Value) :-
513 set_profile(User, Name=Value).
519delete_profile(_Request) :-
520 http_in_session(SessionID),
521 http_session_data(profile_id(User)),
522 http_close_session(SessionID), 523 profile_remove(User),
524 reply_json_dict(true).
525
526
527 530
531:- listen(identity_property(Identity, Property),
532 from_profile(Identity, Property)). 533
534from_profile(Identity, Property) :-
535 profile_property(Identity.get(profile_id), Property).
541profile_name(ProfileID, Name) :-
542 user_field(Field),
543 Term =.. [Field, Name],
544 profile_property(ProfileID, Term),
545 !.
546
547user_field(name).
548user_field(given_name).
549user_field(nick_name).
550user_field(family_name).
551
552
553 556
557:- multifile
558 swish_search:typeahead/4.
575swish_search:typeahead(user, Query, User, _Options) :-
576 current_profile(ProfileID, Attributes),
577 Keys = [name,given_name,family_name,email],
578 pairs_keys_values(Pairs, Keys, _),
579 dict_pairs(Profile, _, Pairs),
580 Profile >:< Attributes,
581 profile_match_query(Query, Pairs, Key),
582 user_dict(ProfileID, Key, Attributes, User).
583
584profile_match_query(Query, Pairs, Key) :-
585 member(Key-Value, Pairs),
586 text(Value),
587 sub_atom_icasechk(Value, 0, Query),
588 !.
589
590text(Value) :-
591 string(Value),
592 !.
593text(Value) :-
594 atom(Value).
595
596user_dict(ProfileID, SearchKey, Attributes, Dict) :-
597 findall(Key-Value,
598 user_search_property(ProfileID,SearchKey,Attributes,Key,Value),
599 Pairs),
600 dict_pairs(Dict, user, Pairs).
601
602user_search_property(ProfileID, _, _, id, ProfileID).
603user_search_property(ProfileID, _, _, name, Name) :-
604 profile_name(ProfileID, Name).
605user_search_property(_, email, Attrs, email, Attrs.get(email)).
606user_search_property(_, Search, Attrs, hit, hit{key:Search,
607 value:Attrs.get(Search)}).
608user_search_property(_, _, Attrs, avatar, Attrs.get(avatar))
User profile configuration
Complementary to authentication, this module configures the maintenance of user profiles.
There are several places where we need interaction with the user profile:
email
for the new user and start a process to verify this.*/