35
36:- module(swish_notify,
37 [ follow/3, 38 notify/2 39 ]). 40:- use_module(library(settings)). 41:- use_module(library(persistency)). 42:- use_module(library(broadcast)). 43:- use_module(library(lists)). 44:- use_module(library(readutil)). 45:- use_module(library(debug)). 46:- use_module(library(error)). 47:- use_module(library(apply)). 48:- use_module(library(http/html_write)). 49:- use_module(library(http/http_session)). 50:- use_module(library(http/http_dispatch)). 51:- use_module(library(http/http_parameters)). 52:- use_module(library(http/http_json)). 53
54:- use_module(library(user_profile)). 55
56:- use_module(email). 57:- use_module('../bootstrap'). 58:- use_module('../storage'). 59:- use_module('../chat').
76:- setting(database, callable, data('notify.db'),
77 "Database holding notifications"). 78:- setting(queue, callable, data('notify-queue.db'),
79 "File holding queued messages"). 80:- setting(daily, compound, 04:00,
81 "Time at which to send daily messages"). 82
83:- meta_predicate try(0). 84
85 88
89:- persistent
90 follower(docid:atom,
91 profile:atom,
92 options:list(oneof([update,chat]))). 93
94notify_open_db :-
95 db_attached(_),
96 !.
97notify_open_db :-
98 setting(database, Spec),
99 absolute_file_name(Spec, Path, [access(write)]),
100 db_attach(Path, [sync(close)]).
108queue_event(Profile, DocID, Action) :-
109 queue_event(Profile, DocID, Action, new).
110queue_event(Profile, DocID, Action, Status) :-
111 queue_file(Path),
112 with_mutex(swish_notify,
113 queue_event_sync(Path, Profile, DocID, Action, Status)),
114 start_mail_scheduler.
115
116queue_event_sync(Path, Profile, DocID, Action, Status) :-
117 setup_call_cleanup(
118 open(Path, append, Out, [encoding(utf8)]),
119 format(Out, '~q.~n', [notify(Profile, DocID, Action, Status)]),
120 close(Out)).
121
122queue_file(Path) :-
123 setting(queue, Spec),
124 absolute_file_name(Spec, Path, [access(write)]).
130send_queued_mails :-
131 queue_file(Path),
132 exists_file(Path), !,
133 atom_concat(Path, '.sending', Tmp),
134 with_mutex(swish_notify, rename_file(Path, Tmp)),
135 read_file_to_terms(Tmp, Terms, [encoding(utf8)]),
136 forall(member(Term, Terms),
137 send_queued(Term)),
138 delete_file(Tmp).
139send_queued_mails.
140
141send_queued(notify(Profile, DocID, Action, Status)) :-
142 profile_property(Profile, email(Email)),
143 profile_property(Profile, email_notifications(When)),
144 When \== never, !,
145 ( catch(send_notification_mail(Profile, DocID, Email, Action),
146 Error, true)
147 -> ( var(Error)
148 -> true
149 ; update_status(Status, Error, NewStatus)
150 -> queue_event(Profile, Action, NewStatus)
151 ; true
152 )
153 ; update_status(Status, failed, NewStatus)
154 -> queue_event(Profile, DocID, Action, NewStatus)
155 ; true
156 ).
157
158update_status(new, Status, retry(3, Status)).
159update_status(retry(Count0, _), Status, retry(Count, Status)) :-
160 Count0 > 0,
161 Count is Count0 - 1.
167:- dynamic mail_scheduler_running/0. 168
169start_mail_scheduler :-
170 mail_scheduler_running,
171 !.
172start_mail_scheduler :-
173 catch(thread_create(mail_main, _,
174 [ alias(mail_scheduler),
175 detached(true),
176 at_exit(retractall(mail_scheduler_running))
177 ]),
178 error(permission_error(create, thread, mail_scheduler), _),
179 true).
185mail_main :-
186 asserta(mail_scheduler_running),
187 repeat,
188 next_send_queue_time(T),
189 get_time(Now),
190 Sleep is T-Now,
191 sleep(Sleep),
192 thread_create(send_queued_mails, _,
193 [ detached(true),
194 alias(send_queued_mails)
195 ]),
196 fail.
197
198next_send_queue_time(T) :-
199 get_time(Now),
200 stamp_date_time(Now, date(Y,M,D0,H0,_M,_S,Off,TZ,DST), local),
201 setting(daily, HH:MM),
202 ( H0 @< HH
203 -> D = D0
204 ; D is D0+1
205 ),
206 date_time_stamp(date(Y,M,D,HH,MM,0,Off,TZ,DST), T).
213follow(DocID, ProfileID, Flags) :-
214 to_atom(DocID, DocIDA),
215 to_atom(ProfileID, ProfileIDA),
216 maplist(to_atom, Flags, Options),
217 notify_open_db,
218 ( follower(DocIDA, ProfileIDA, OldOptions)
219 -> ( OldOptions == Options
220 -> true
221 ; retractall_follower(DocIDA, ProfileIDA, _),
222 ( Options \== []
223 -> assert_follower(DocIDA, ProfileIDA, Options)
224 ; true
225 )
226 )
227 ; Options \== []
228 -> assert_follower(DocIDA, ProfileIDA, Options)
229 ; true
230 ).
231
232nofollow(DocID, ProfileID, Flags) :-
233 to_atom(DocID, DocIDA),
234 to_atom(ProfileID, ProfileIDA),
235 maplist(to_atom, Flags, Options),
236 ( follower(DocIDA, ProfileIDA, OldOptions)
237 -> subtract(OldOptions, Options, NewOptions),
238 follow(DocID, ProfileID, NewOptions)
239 ; true
240 ).
260notify(DocID, Action) :-
261 to_atom(DocID, DocIDA),
262 try(notify_in_chat(DocIDA, Action)),
263 notify_open_db,
264 forall(follower(DocIDA, Profile, Options),
265 notify_user(Profile, DocIDA, Action, Options)).
266
267to_atom(Text, Atom) :-
268 atom_string(Atom, Text).
275notify_user(Profile, _, Action, _Options) :- 276 event_generator(Action, Profile),
277 debug(notify(self), 'Notification to self ~p', [Profile]),
278 \+ debugging(notify_self),
279 !.
280notify_user(Profile, DocID, Action, Options) :-
281 try(notify_online(Profile, Action, Options)),
282 try(notify_by_mail(Profile, DocID, Action, Options)).
283
284try(Goal) :-
285 catch(Goal, Error, print_message(error, Error)),
286 !.
287try(_0Goal) :-
288 debug(notify(fail), 'Failed: ~p', [_0Goal]).
289
290
291 294
295:- unlisten(swish(_)),
296 listen(swish(Event), notify_event(Event)). 297
299notify_event(follow(DocID, ProfileID, Options)) :-
300 follow(DocID, ProfileID, Options).
302notify_event(updated(File, Commit)) :-
303 storage_meta_data(Commit.get(previous), OldCommit),
304 ( atom_concat('gitty:', OldCommit.name, DocID)
305 -> notify(DocID, updated(Commit))
306 ; atom_concat('gitty:', File, DocID),
307 notify(DocID, forked(OldCommit, Commit))
308 ).
309notify_event(deleted(File, Commit)) :-
310 atom_concat('gitty:', File, DocID),
311 notify(DocID, deleted(Commit)).
312notify_event(created(File, Commit)) :-
313 atom_concat('gitty:', File, DocID),
314 notify(DocID, created(Commit)).
316notify_event(chat(Message)) :-
317 notify(Message.docid, chat(Message)).
323event_generator(updated(Commit), Commit.get(profile_id)).
324event_generator(deleted(Commit), Commit.get(profile_id)).
325event_generator(forked(_, Commit), Commit.get(profile_id)).
326
327
328 331
332notify_online(ProfileID, Action, _Options) :-
333 chat_to_profile(ProfileID, \short_notice(Action)).
334
335short_notice(updated(Commit)) -->
336 html([\committer(Commit), ' updated ', \file_name(Commit)]).
337short_notice(deleted(Commit)) -->
338 html([\committer(Commit), ' deleted ', \file_name(Commit)]).
339short_notice(forked(OldCommit, Commit)) -->
340 html([\committer(Commit), ' forked ', \file_name(OldCommit),
341 ' into ', \file_name(Commit)
342 ]).
343short_notice(chat(Message)) -->
344 html([\chat_user(Message), " chatted about ", \chat_file(Message)]).
345
346file_name(Commit) -->
347 { http_link_to_id(web_storage, path_postfix(Commit.name), HREF) },
348 html(a(href(HREF), Commit.name)).
349
350
351
357:- html_meta(html_string(html, -)). 358
359notify_in_chat(_, chat(_)) :-
360 !.
361notify_in_chat(DocID, Action) :-
362 html_string(\chat_notice(Action, Payload), HTML),
363 action_user(Action, User),
364 Message0 = _{ type:"chat-message",
365 class:"update",
366 html:HTML,
367 user:User,
368 create:false
369 },
370 ( Payload == []
371 -> Message = Message0
372 ; Message = Message0.put(payload, Payload)
373 ),
374 chat_about(DocID, Message).
375
376
377html_string(HTML, String) :-
378 phrase(html(HTML), Tokens),
379 delete(Tokens, nl(_), SingleLine),
380 with_output_to(string(String), print_html(SingleLine)).
381
382
383chat_notice(updated(Commit), [_{type:update, name:Name,
384 commit:CommitHash, previous:PrevCommit}]) -->
385 { _{name:Name, commit:CommitHash, previous:PrevCommit} :< Commit },
386 html([b('Saved'), ' new version: ', \commit_message_summary(Commit)]).
387chat_notice(deleted(Commit), []) -->
388 html([b('Deleted'), ': ', \commit_message_summary(Commit)]).
389chat_notice(forked(_OldCommit, Commit), []) -->
390 html([b('Forked'), ' into ', \file_name(Commit), ': ',
391 \commit_message_summary(Commit)
392 ]).
393chat_notice(created(Commit), []) -->
394 html([b('Created'), ' ', \file_name(Commit), ': ',
395 \commit_message_summary(Commit)
396 ]).
397
398commit_message_summary(Commit) -->
399 { Message = Commit.get(commit_message) }, !,
400 html(span(class(['commit-message']), Message)).
401commit_message_summary(_Commit) -->
402 html(span(class(['no-commit-message']), 'no message')).
409action_user(Action, User) :-
410 action_commit(Action, Commit),
411 findall(Name-Value, commit_user_property(Commit, Name, Value), Pairs),
412 dict_pairs(User, u, Pairs).
413
414action_commit(forked(_From, Commit), Commit) :-
415 !.
416action_commit(Action, Commit) :-
417 arg(1, Action, Commit).
418
419commit_user_property(Commit, Name, Value) :-
420 Profile = Commit.get(profile_id),
421 !,
422 profile_user_property(Profile, Commit, Name, Value).
423commit_user_property(Commit, name, Name) :-
424 Name = Commit.get(author).
425commit_user_property(Commit, avatar, Avatar) :-
426 Avatar = Commit.get(avatar).
427
428profile_user_property(ProfileID, _, profile_id, ProfileID).
429profile_user_property(_, Commit, name, Commit.get(author)).
430profile_user_property(ProfileID, Commit, avatar, Avatar) :-
431 ( profile_property(ProfileID, avatar(Avatar))
432 -> true
433 ; Avatar = Commit.get(avatar)
434 ).
435
436
437 440
447
448notify_by_mail(Profile, DocID, Action, Options) :-
449 profile_property(Profile, email(Email)),
450 profile_property(Profile, email_notifications(When)),
451 When \== never,
452 must_notify(Action, Options),
453 ( When == immediate
454 -> debug(notify(email), 'Sending notification mail to ~p', [Profile]),
455 send_notification_mail(Profile, DocID, Email, Action)
456 ; debug(notify(email), 'Queing notification mail to ~p', [Profile]),
457 queue_event(Profile, DocID, Action)
458 ).
459
460must_notify(chat(Message), Options) :- !,
461 memberchk(chat, Options),
462 \+ Message.get(class) == "update".
463must_notify(_, Options) :-
464 memberchk(update, Options).
465
470
471send_notification_mail(Profile, DocID, Email, Action) :-
472 phrase(subject(Action), Codes),
473 string_codes(Subject, Codes),
474 smtp_send_html(Email, \mail_message(Profile, DocID, Action),
475 [ subject(Subject)
476 ]).
477
478subject(Action) -->
479 subject_action(Action).
480
481subject_action(updated(Commit)) -->
482 txt_commit_file(Commit), " updated by ", txt_committer(Commit).
483subject_action(deleted(Commit)) -->
484 txt_commit_file(Commit), " deleted by ", txt_committer(Commit).
485subject_action(forked(_, Commit)) -->
486 txt_commit_file(Commit), " forked by ", txt_committer(Commit).
487subject_action(chat(Message)) -->
488 txt_chat_user(Message), " chatted about ", txt_chat_file(Message).
489
490
491 494
495style -->
496 email_style,
497 notify_style.
498
499notify_style -->
500 html({|html||
501<style>
502 .block {margin-left: 2em;}
503p.commit-message,
504p.chat {color: darkgreen;}
505p.nocommit-message {color: orange;}
506pre.query {}
507div.query {margin-top:2em; border-top: 1px solid #888;}
508div.query-title {font-size: 80%; color: #888;}
509div.nofollow {margin-top:2em; border-top: 1px solid #888;
510 font-size: 80%; color: #888; }
511</style>
512 |}).
513
514
515
516
517
523mail_message(ProfileID, DocID, Action) -->
524 dear(ProfileID),
525 notification(Action),
526 unsubscribe_options(ProfileID, DocID, Action),
527 signature,
528 style.
529
530notification(updated(Commit)) -->
531 html(p(['The file ', \global_commit_file(Commit),
532 ' has been updated by ', \committer(Commit), '.'])),
533 commit_message(Commit).
534notification(forked(OldCommit, Commit)) -->
535 html(p(['The file ', \global_commit_file(OldCommit),
536 ' has been forked into ', \global_commit_file(Commit), ' by ',
537 \committer(Commit), '.'])),
538 commit_message(Commit).
539notification(deleted(Commit)) -->
540 html(p(['The file ', \global_commit_file(Commit),
541 ' has been deleted by ', \committer(Commit), '.'])),
542 commit_message(Commit).
543notification(chat(Message)) -->
544 html(p([\chat_user(Message), " chatted about ", \chat_file(Message)])),
545 chat_message(Message).
546
547global_commit_file(Commit) -->
548 global_gitty_link(Commit.name).
549
550global_gitty_link(File) -->
551 { public_url(web_storage, path_postfix(File), HREF, []) },
552 html(a(href(HREF), File)).
553
554committer(Commit) -->
555 { ProfileID = Commit.get(profile_id) }, !,
556 profile_name(ProfileID).
557committer(Commit) -->
558 html(Commit.get(owner)).
559
560commit_message(Commit) -->
561 { Message = Commit.get(commit_message) }, !,
562 html(p(class(['commit-message', block]), Message)).
563commit_message(_Commit) -->
564 html(p(class(['no-commit-message', block]), 'No message')).
565
566chat_file(Message) -->
567 global_docid_link(Message.docid).
568
569global_docid_link(DocID) -->
570 { string_concat("gitty:", File, DocID)
571 },
572 global_gitty_link(File).
573
574chat_user(Message) -->
575 { User = Message.get(user).get(name) },
576 !,
577 html(User).
578chat_user(_Message) -->
579 html("Someone").
580
581chat_message(Message) -->
582 (chat_text(Message) -> [] ; []),
583 (chat_payloads(Message.get(payload)) -> [] ; []).
584
585chat_text(Message) -->
586 html(p(class([chat,block]), Message.get(text))).
587
588chat_payloads([]) --> [].
589chat_payloads([H|T]) --> chat_payload(H), chat_payloads(T).
590
591chat_payload(PayLoad) -->
592 { atom_string(Type, PayLoad.get(type)) },
593 chat_payload(Type, PayLoad),
594 !.
595chat_payload(_) --> [].
596
597chat_payload(query, PayLoad) -->
598 html(div(class(query),
599 [ div(class('query-title'), 'Query'),
600 pre(class([query, block]), PayLoad.get(query))
601 ])).
602chat_payload(about, PayLoad) -->
603 html(div(class(about),
604 [ 'About file ', \global_docid_link(PayLoad.get(docid)) ])).
605chat_payload(Type, _) -->
606 html(p(['Unknown payload of type ~q'-[Type]])).
607
608
609 612
613unsubscribe_options(ProfileID, DocID, _) -->
614 html(div(class(nofollow),
615 [ 'Stop following ',
616 \nofollow_link(ProfileID, DocID, [chat]), '||',
617 \nofollow_link(ProfileID, DocID, [update]), '||',
618 \nofollow_link(ProfileID, DocID, [chat,update]),
619 ' about this document'
620 ])).
621
622nofollow_link(ProfileID, DocID, What) -->
623 email_action_link(\nofollow_link_label(What),
624 nofollow_page(ProfileID, DocID, What),
625 nofollow(ProfileID, DocID, What),
626 []).
627
628nofollow_link_label([chat]) --> html(chats).
629nofollow_link_label([update]) --> html(updates).
630nofollow_link_label([chat, update]) --> html('all notifications').
631
632nofollow_done([chat]) --> html(chat).
633nofollow_done([update]) --> html(update).
634nofollow_done([chat, update]) --> html('any notifications').
635
636nofollow_page(ProfileID, DocID, What, _Request) :-
637 reply_html_page(
638 email_confirmation,
639 title('SWISH -- Stopped following'),
640 [ \email_style,
641 \dear(ProfileID),
642 p(['You will no longer receive ', \nofollow_done(What),
643 'notifications about ', \docid_link(DocID), '. ',
644 'You can reactivate following this document using the \c
645 File/Follow ... menu in SWISH. You can specify whether \c
646 and when you like to receive email notifications from your \c
647 profile page.'
648 ]),
649 \signature
650 ]).
651
652docid_link(DocID) -->
653 { atom_concat('gitty:', File, DocID),
654 http_link_to_id(web_storage, path_postfix(File), HREF)
655 },
656 !,
657 html(a(href(HREF), File)).
658docid_link(DocID) -->
659 html(DocID).
660
661
662 665
666txt_commit_file(Commit) -->
667 write(Commit.name).
668
669txt_committer(Commit) -->
670 { ProfileID = Commit.get(profile_id) }, !,
671 txt_profile_name(ProfileID).
672txt_committer(Commit) -->
673 write(Commit.get(owner)), !.
674
675
676
677 680
681txt_profile_name(ProfileID) -->
682 { profile_property(ProfileID, name(Name)) },
683 write(Name).
684
685
686 689
690txt_chat_user(Message) -->
691 { User = Message.get(user).get(name) },
692 !,
693 write(User).
694txt_chat_user(_Message) -->
695 "Someone".
696
697txt_chat_file(Message) -->
698 { string_concat("gitty:", File, Message.docid) },
699 !,
700 write(File).
701
702
703 706
707write(Term, Head, Tail) :-
708 format(codes(Head, Tail), '~w', [Term]).
709
710
711 714
715:- http_handler(swish(follow/options), follow_file_options,
716 [ id(follow_file_options) ]). 717:- http_handler(swish(follow/save), save_follow_file,
718 [ id(save_follow_file) ]).
724follow_file_options(Request) :-
725 http_parameters(Request,
726 [ docid(DocID, [atom])
727 ]),
728 http_in_session(_SessionID),
729 http_session_data(profile_id(ProfileID)), !,
730 ( profile_property(ProfileID, email_notifications(When))
731 -> true
732 ; existence_error(profile_property, email_notifications)
733 ),
734
735 ( follower(DocID, ProfileID, Follow)
736 -> true
737 ; Follow = []
738 ),
739
740 follow_file_widgets(DocID, When, Follow, Widgets),
741
742 reply_html_page(
743 title('Follow file options'),
744 \bt_form(Widgets,
745 [ class('form-horizontal'),
746 label_columns(sm-3)
747 ])).
748follow_file_options(_Request) :-
749 reply_html_page(
750 title('Follow file options'),
751 [ p('You must be logged in to follow a file'),
752 \bt_form([ button_group(
753 [ button(cancel, button,
754 [ type(danger),
755 data([dismiss(modal)])
756 ])
757 ], [])
758 ],
759 [ class('form-horizontal'),
760 label_columns(sm-3)
761 ])
762 ]).
763
764:- multifile
765 user_profile:attribute/3. 766
767follow_file_widgets(DocID, When, Follow,
768 [ hidden(docid, DocID),
769 checkboxes(follow, [update,chat], [value(Follow)]),
770 select(email_notifications, NotificationOptions, [value(When)])
771 | Buttons
772 ]) :-
773 user_profile:attribute(email_notifications, oneof(NotificationOptions), _),
774 buttons(Buttons).
775
776buttons(
777 [ button_group(
778 [ button(save, submit,
779 [ type(primary),
780 data([action(SaveHREF)])
781 ]),
782 button(cancel, button,
783 [ type(danger),
784 data([dismiss(modal)])
785 ])
786 ],
787 [
788 ])
789 ]) :-
790 http_link_to_id(save_follow_file, [], SaveHREF).
796save_follow_file(Request) :-
797 http_read_json_dict(Request, Dict),
798 debug(profile(update), 'Got ~p', [Dict]),
799 http_in_session(_SessionID),
800 http_session_data(profile_id(ProfileID)),
801 debug(notify(options), 'Set follow options to ~p', [Dict]),
802 set_profile(ProfileID, email_notifications=Dict.get(email_notifications)),
803 follow(Dict.get(docid), ProfileID, Dict.get(follow)),
804 reply_json_dict(_{status:success})
SWISH notifications
This module keeps track of which users wish to track which notifications and sending the notifications to the user. If the target user is online we will notify using an avatar. Otherwise we send an email.
A user has the following options to control notifications:
*/