1:- module(bc_comment, [
2 bc_comment_exists/2, 3 bc_comment_remove/1 4]). 5
6:- use_module(library(docstore)). 7
9
(EntryId, Id):-
11 ds_col_get(comment, Id, [post], Comment),
12 Comment.post = EntryId, !.
13
14bc_comment_exists(_, _):-
15 throw(error(comment_not_exists)).
16
19
(Id):-
21 ds_find(comment, reply_to=Id, [author], Replies),
22 comment_remove_list(Replies),
23 ds_col_remove(comment, Id).
24
([Comment|Comments]):-
26 bc_comment_remove(Comment.'$id'),
27 comment_remove_list(Comments).
28
29comment_remove_list([])