1:- module(bc_comment_notify, [
2 bc_comment_notify/1 3]). 4
5:- use_module(library(assoc)). 6:- use_module(library(error)). 7:- use_module(library(docstore)). 8:- use_module(library(sort_dict)). 9
10:- use_module(bc_comment_mention). 11:- use_module(bc_mail_template). 12:- use_module(bc_data_config). 13:- use_module(bc_mail_queue). 14:- use_module(bc_string). 15:- use_module(bc_type). 16
27bc_comment_notify(CommentId):-
28 must_be(atom, CommentId),
29 debug(bc_comment,
30 'sending comment ~w notifications', [CommentId]),
31 ds_col_get(comment, CommentId, Comment),
32 ds_col_get(entry, Comment.post, Entry),
33 notify_parent(Comment, Entry),
34 notify_mentions(Comment, Entry),
35 notify_entry_author(Comment, Entry).
36
38
39notify_parent(Comment, Entry):-
40 ( get_dict(reply_to, Comment, ParentId),
41 ds_col_get(comment, ParentId, Parent),
42 get_dict(notify, Parent, true),
43 get_dict(email, Parent, Email),
44 entry_canonical_url(Entry, URL)
45 -> Data = _{
46 comment: Comment,
47 parent: Parent,
48 entry: Entry,
49 entry_url: URL },
50 bc_mail_render_template(reply, Data, Result),
51 bc_config_get(smtp_from, From),
52 bc_mail_enqueue_text(Result.body, From,
53 Result.subject, Email)
54 ; true).
55
57
58notify_entry_author(Comment, Entry):-
59 ds_col_get(user, Entry.author, Author),
60 ( Author.comment_notifications = true,
61 entry_canonical_url(Entry, URL)
62 -> Data = _{
63 entry: Entry,
64 author: Author,
65 comment: Comment,
66 entry_url: URL },
67 bc_mail_render_template(comment, Data, Result),
68 bc_config_get(smtp_from, From),
69 bc_mail_enqueue_text(Result.body, From,
70 Result.subject, Author.username)
71 ; true).
72
74
75notify_mentions(Comment, Entry):-
76 ( entry_canonical_url(Entry, URL)
77 -> entry_mentionable_authors(Comment.post, Authors),
78 assoc_to_keys(Authors, Names),
79 include(accepts_notify(Authors), Names, Accepting),
80 bc_mentions_parse(Comment.content, Accepting, Mentions),
81 maplist(extract_receiver(Authors), Mentions, Receivers),
82 maplist(mention_send(Entry, URL, Comment), Receivers)
83 ; true).
84
(Authors, Name, Receiver):-
86 get_assoc(Name, Authors, Receiver).
87
90
91mention_send(Entry, URL, Comment, Mention):-
92 debug(bc_comment,
93 'sending mention notification to ~w', [Mention.email]),
94 Data = _{
95 entry: Entry,
96 receiver: Mention,
97 comment: Comment,
98 entry_url: URL },
99 bc_mail_render_template(mention, Data, Result),
100 bc_config_get(smtp_from, From),
101 bc_mail_enqueue_text(Result.body, From,
102 Result.subject, Mention.email).
103
104accepts_notify(Authors, Name):-
105 get_assoc(Name, Authors, Data),
106 Data.notify = true.
107
109
112
113entry_mentionable_authors(EntryId, Authors):-
114 must_be(atom, EntryId),
115 ds_find(comment, post=EntryId,
116 [author, notify, email, date], Comments),
117 sort_dict(date, desc, Comments, Sorted),
118 merge_author_data(Sorted, Authors).
119
120merge_author_data(Comments, Assoc):-
121 empty_assoc(Empty),
122 merge_author_data(Comments, Empty, Assoc).
123
124merge_author_data([Comment|Comments], Acc, Assoc):-
125 ( get_dict(email, Comment, _),
126 get_dict(notify, Comment, true)
127 -> New = _{
128 comment_id: Comment.'$id',
129 name: Comment.author,
130 notify: Comment.notify,
131 email: Comment.email
132 },
133 put_assoc(Comment.author, Acc, New, Tmp),
134 merge_author_data(Comments, Tmp, Assoc)
135 ; merge_author_data(Comments, Acc, Assoc)).
136
137merge_author_data([], Assoc, Assoc).
138
142
143entry_canonical_url(Entry, URL):-
144 bc_type_canonical(Entry.type, Canonical),
145 bc_config_get(site, Site),
146 bc_string_replace(Canonical, '<slug>', Entry.slug, Path),
147 atom_concat(Site, Path, URL)