1:- module(bc_data_comment, [
    2    bc_comment_tree/2,      % +EntryId, -Comments
    3    bc_comment_save/3,      % +EntryId, +Comment, -Id
    4    bc_comment_remove/3,    % +Actor, +EntryId, +Id
    5    bc_export_comments/1    % +Filename
    6]).

Handles post comments */

   10:- use_module(library(sort_dict)).   11:- use_module(library(docstore)).   12:- use_module(library(debug)).   13:- use_module(library(http/json)).   14
   15:- use_module(bc_mail).   16:- use_module(bc_entry).   17:- use_module(bc_comment).   18:- use_module(bc_access).   19:- use_module(bc_type).   20:- use_module(bc_data_config).   21:- use_module(bc_comment_question).   22:- use_module(bc_comment_format).   23:- use_module(bc_comment_tree).   24:- use_module(bc_comment_notify).
 bc_comment_tree(+EntryId, -Tree) is det
Retrieves the tree of comments for the post.
   30bc_comment_tree(EntryId, Tree):-
   31    bc_entry_exists(EntryId),
   32    ds_find(comment, post=EntryId, Comments),
   33    sort_dict(date, desc, Comments, Sorted),
   34    bc_build_comment_tree(Sorted, Tree),
   35    debug(bc_data, 'retrieved comment tree for ~p', [EntryId]).
 bc_comment_save(+EntryId, +Comment, -Id) is det
Saves a new comment.
   41bc_comment_save(EntryId, Comment, Id):-
   42    can_create(EntryId, Comment),
   43    comment_save(EntryId, Comment, Id),
   44    bc_comment_notify(Id),
   45    debug(bc_data, 'saved comment ~p', [Id]).
   46
   47can_create(EntryId, Comment):-
   48    bc_entry_exists(EntryId),
   49    comments_allowed(EntryId),
   50    (   get_dict(reply_to, Comment, To)
   51    ->  bc_comment_exists(EntryId, To)
   52    ;   true),
   53    correct_answer(Comment).
   54
   55comments_allowed(EntryId):-
   56    bc_entry_commenting(EntryId, true),
   57    bc_entry_type(EntryId, Type),
   58    bc_type(Type, _, _, _, true), !.
   59
   60comments_allowed(_):-
   61    throw(error(no_comments_allowed)).
   62
   63correct_answer(Comment):-
   64    bc_answer_ok(Comment.question, Comment.answer), !.
   65
   66correct_answer(_):-
   67    throw(error(incorrect_answer)).
   68
   69% Attaches comment timestamp,
   70% formats comment content and
   71% saves into docstore.
   72
   73comment_save(EntryId, Comment, CommentId):-
   74    bc_format_comment(Comment.content, Formatted),
   75    get_time(Time),
   76    Ts is floor(Time),
   77    put_dict(_{
   78        date: Ts,
   79        post: EntryId,
   80        html: Formatted }, Comment, Processed),
   81    ds_insert(Processed, CommentId).
 bc_comment_remove(+Actor, +EntryId, +Id) is det
Removes the given comment. Requires update access on the entry.
   88bc_comment_remove(Actor, EntryId, Id):-
   89    can_remove(Actor, EntryId, Id),
   90    bc_comment_remove(Id),
   91    debug(bc_data, 'removed comment ~p', [Id]).
   92
   93can_remove(Actor, EntryId, Id):-
   94    bc_comment_exists(EntryId, Id),
   95    remove_access(Actor, EntryId).
   96
   97remove_access(Actor, EntryId):-
   98    bc_update_access_id(Actor, EntryId), !.
   99
  100remove_access(_, _):-
  101    throw(error(no_access)).
  102
  103% Exports all comments to the given file.
  104
  105bc_export_comments(File):-
  106    ds_all(comment, Comments),
  107    setup_call_cleanup(
  108        open(File, write, Stream, [encoding('utf8')]),
  109        json_write(Stream, Comments),
  110        close(Stream))