1:- module(bc_data_entry, [
    2    bc_entry_actions/3,       % +Actor, +Id, -Actions
    3    bc_entry_action/4,        % +Actor, +Id, +Action, -Result
    4    bc_entry_save/3,          % +Actor, +Entry, -Id
    5    bc_entry_update/2,        % +Actor, +Entry
    6    bc_entry_remove/2,        % +Actor, +Id
    7    bc_entry_remove_trash/2,  % +Actor, +Id
    8    bc_entry_restore/2,       % +Actor, +Id
    9    bc_entry_list/3,          % +Actor, +Type, -List
   10    bc_trash_list/2,          % +Actor, -List
   11    bc_purge_trash/1,         % +Actor
   12    bc_entry/3,               % +Actor, +Id, -Entry
   13    bc_entry_info/3,          % +Actor, +Id, -Entry
   14    bc_export_all/1           % +Directory
   15]).

Handles entry data */

   19:- use_module(library(debug)).   20:- use_module(library(sort_dict)).   21:- use_module(library(docstore)).   22:- use_module(library(md/md_parse)).   23:- use_module(library(http/json)).   24
   25:- use_module(bc_access).   26:- use_module(bc_search).   27:- use_module(bc_entry).   28:- use_module(bc_files).   29:- use_module(bc_user).   30:- use_module(bc_action).
 bc_entry_actions(+Actor, +Id, -Actions) is det
List of available actions for the actor.
   36bc_entry_actions(Actor, Id, Actions):-
   37    bc_available_actions(Actor, Id, Actions).
 bc_entry_action(+Actor, +Id, +Action, -Result) is det
Executes the given action on the entry.
   43bc_entry_action(Actor, Id, Action, Result):-
   44    can_execute(Actor, Action, Id),
   45    bc_execute(Actor, Action, Id, Result).
   46
   47can_execute(Actor, Action, Id):-
   48    bc_execute_access_id(Actor, Action, Id), !.
   49
   50can_execute(_, _, _):-
   51    throw(error(no_access)).
 bc_entry_save(+Actor, +Entry, -Id) is det
Saves and formats the new entry.
   57bc_entry_save(Actor, Entry, Id):-
   58    can_create(Actor, Entry),
   59    entry_format(Entry, Formatted),
   60    ds_insert(Formatted, Id),
   61    bc_index(Id),
   62    debug(bc_data_entry, 'saved entry ~p', [Id]).
   63
   64can_create(Actor, Entry):-
   65    bc_valid_slug(Entry.slug),
   66    bc_slug_unique(Entry.slug),
   67    bc_user_exists(Entry.author),
   68    create_access(Actor, Entry).
   69
   70create_access(Actor, Entry):-
   71    bc_create_access_type(Actor, Entry.type), !.
   72
   73create_access(_, _):-
   74    throw(error(no_access)).
 bc_entry_update(+Actor, +Entry) is det
Updates the given entry. Reformats HTML.
   80bc_entry_update(Actor, Entry):-
   81    ds_id(Entry, Id),
   82    can_update(Actor, Entry),
   83    bc_entry_slug(Id, OldSlug),
   84    entry_format(Entry, OldSlug, Formatted),
   85    ds_update(Formatted),
   86    bc_index(Id),
   87    rename_directory(OldSlug, Entry.slug),
   88    debug(bc_data_entry, 'updated entry ~p', [Id]).
   89
   90can_update(Actor, Entry):-
   91    ds_id(Entry, Id),
   92    bc_entry_exists(Id),
   93    bc_valid_slug(Entry.slug),
   94    bc_slug_unique(Entry.slug, Id),
   95    bc_user_exists(Entry.author),
   96    update_access(Actor, Entry).
   97
   98update_access(Actor, Entry):-
   99    ds_id(Entry, Id),
  100    update_type_access(Actor, Entry),
  101    update_author_access(Actor, Entry),
  102    bc_update_access_id(Actor, Id),
  103    bc_entry_published(Id, Published),
  104    (   Entry.published = Published
  105    ->  true
  106    ;   bc_publish_access_id(Actor, Id)), !.
  107
  108update_access(_, _):-
  109    throw(error(no_access)).
  110
  111% Checks if the entry
  112% type can be updated.
  113
  114update_type_access(Actor, _):-
  115    Actor.type = admin, !.
  116
  117update_type_access(_, Entry):-
  118    ds_id(Entry, Id),
  119    bc_entry_type(Id, Entry.type), !.
  120
  121update_type_access(_, _):-
  122    throw(error(no_access)).
  123
  124% Checks if the entry
  125% author can be updated.
  126
  127update_author_access(Actor, _):-
  128    Actor.type = admin, !.
  129
  130update_author_access(_, Entry):-
  131    ds_id(Entry, Id),
  132    bc_entry_author(Id, Entry.author), !.
  133
  134update_author_access(_, _):-
  135    throw(error(no_access)).
  136
  137% Renames entry files directory
  138% when the entry slug changes.
  139
  140rename_directory(Slug, Slug):- !.
  141
  142rename_directory(Old, New):-
  143    atomic_list_concat([public, '/', Old], From),
  144    atomic_list_concat([public, '/', New], To),
  145    (   exists_directory(From)
  146    ->  rename_file(From, To)
  147    ;   true).
  148
  149% Formats entry HTML contents based on
  150% the entries content type.
  151
  152entry_format(EntryIn, OldSlug, EntryOut):-
  153    links_rewrite(EntryIn.content,
  154        EntryIn.slug, OldSlug, Content),
  155    Rewritten = EntryIn.put(content, Content),
  156    entry_format(Rewritten, EntryOut).
  157
  158% Replaces slug in links in the content.
  159
  160links_rewrite(ContentIn, NewSlug, OldSlug, ContentOut):-
  161    atomic_list_concat(['/', OldSlug, '/'], OldLink),
  162    atomic_list_concat(['/', NewSlug, '/'], NewLink),
  163    atomic_list_concat(Tokens, OldLink, ContentIn),
  164    atomic_list_concat(Tokens, NewLink, ContentAtom),
  165    atom_string(ContentAtom, ContentOut).
  166
  167entry_format(EntryIn, EntryOut):-
  168    Content = EntryIn.content,
  169    ContentType = EntryIn.content_type,
  170    (   ContentType = markdown
  171    ->  md_html_string(Content, Html)
  172    ;   Html = Content),
  173    put_dict(_{ html: Html }, EntryIn, EntryOut).
 bc_entry_remove(+Actor, +Id) is det
Removes the given entry and its comments.
  179bc_entry_remove(Actor, Id):-
  180    can_remove(Actor, Id),
  181    ds_move(entry, Id, trash),
  182    debug(bc_data_entry, 'moved to trash: ~p', [Id]).
 bc_entry_remove_trash(+Actor, +Id) is det
Removes entry from trash.
  188bc_entry_remove_trash(Actor, Id):-
  189    can_remove(Actor, Id),
  190    bc_entry_slug(Id, Slug),
  191    ds_col_remove(trash, Id),
  192    ds_col_remove_cond(comment, post=Id),
  193    bc_index_remove(Id),
  194    remove_files(Slug),
  195    debug(bc_data_entry, 'removed entry ~p', [Id]).
 bc_entry_restore(+Actor, +Id) is det
Restores the given entry from trash. Require remove permission.
  202bc_entry_restore(Actor, Id):-
  203    can_remove(Actor, Id),
  204    ds_move(trash, Id, entry).
  205
  206can_remove(Actor, Id):-
  207    bc_entry_exists(Id),
  208    remove_access(Actor, Id).
  209
  210remove_access(Actor, Id):-
  211    bc_remove_access_id(Actor, Id), !.
  212
  213remove_access(_, _):-
  214    throw(error(no_access)).
  215
  216% Removes entry files.
  217
  218remove_files(Slug):-
  219    atomic_list_concat([public, '/', Slug], Directory),
  220    (   exists_directory(Directory)
  221    ->  remove_directory(Directory)
  222    ;   true).
 bc_entry_list(+Actor, +Type, -List) is det
Retrieves the list of entries of certain type. Does not include contents and HTML. Sorts by date_updated desc.
  230bc_entry_list(Actor, Type, Sorted):-
  231    ds_find(entry, type=Type, [slug, type, date_published,
  232        date_updated, commenting, published,
  233        title, author, tags], Entries),
  234    include(bc_read_access_entry(Actor), Entries, Filtered),
  235    maplist(attach_comment_count, Filtered, List),
  236    sort_dict(date_updated, desc, List, Sorted),
  237    debug(bc_data_entry, 'retrieved entry list', []).
 bc_trash_list(+Actor, -List) is det
Retrieves the list of entries in trash. Does not include contents and HTML. Sorts by date_updated desc. Only includes these that the user has access to.
  246bc_trash_list(Actor, Sorted):-
  247    ds_all(trash, [slug, type, date_published,
  248        date_updated, commenting, published,
  249        title, author, tags], Entries),
  250    include(bc_remove_access_entry(Actor), Entries, Filtered),
  251    maplist(attach_comment_count, Filtered, List),
  252    sort_dict(date_updated, desc, List, Sorted),
  253    debug(bc_data_entry, 'retrieved trash list', []).
 bc_purge_trash(Actor) is det
Removes all entries from trash that the actor has access to.
  260bc_purge_trash(Actor):-
  261    ds_all(trash, [type, author], Entries),
  262    include(bc_remove_access_entry(Actor), Entries, Filtered),
  263    maplist(ds_id, Filtered, Ids),
  264    maplist(bc_entry_remove_trash(Actor), Ids),
  265    debug(bc_data_entry, 'purged trash', []).
 bc_entry(+Actor, +Id, -Entry) is det
Retrieves a single entry by its Id.
  271bc_entry(Actor, Id, WithCount):-
  272    can_view(Actor, Id),
  273    ds_col_get(entry, Id, [slug, type, date_published, date_updated,
  274        commenting, published, title, author,
  275        content, description, content_type, tags, language], Entry), !,
  276    attach_comment_count(Entry, WithCount),
  277    debug(bc_data_entry, 'retrieved entry ~p', [Id]).
 bc_entry_info(+Actor, +Id, -Entry) is det
Retrieves a single entry by its Id. Does not include the content field.
  284bc_entry_info(Actor, Id, WithCount):-
  285    can_view(Actor, Id),
  286    ds_col_get(entry, Id, [slug, type, date_published, date_updated,
  287        commenting, published, title, author,
  288        description, content_type, tags, language], Entry), !,
  289    attach_comment_count(Entry, WithCount),
  290    debug(bc_data_entry, 'retrieved entry ~p info', [Id]).
  291
  292can_view(Actor, Id):-
  293    bc_entry_exists(Id),
  294    view_access(Actor, Id).
  295
  296view_access(Actor, Id):-
  297    bc_read_access_id(Actor, Id), !.
  298
  299view_access(_, _):-
  300    throw(error(no_access)).
  301
  302% Attaches comment count to the entry.
  303
  304attach_comment_count(EntryIn, EntryOut):-
  305    ds_id(EntryIn, Id),
  306    ds_find(comment, post=Id, [post], List),
  307    length(List, Count),
  308    put_dict(_{ comments: Count }, EntryIn, EntryOut).
  309
  310% Exports all entries to the directory.
  311
  312bc_export_all(Directory):-
  313    (   exists_directory(Directory)
  314    ->  export_all_to_directory(Directory)
  315    ;   throw(error(no_directory(Directory)))).
  316
  317export_all_to_directory(Directory):-
  318    ds_all(entry, Entries),
  319    maplist(export_entry(Directory), Entries).
  320
  321% Exports entry to the given directory.
  322
  323export_entry(Directory, Entry):-
  324    export_entry_meta(Directory, Entry),
  325    export_entry_content(Directory, Entry).
  326
  327% Exports entry Markdown content.
  328
  329export_entry_content(Directory, Entry):-
  330    atomic_list_concat([Directory, /, Entry.slug, '.md'], MdFile),
  331    setup_call_cleanup(
  332        open(MdFile, write, Stream, [encoding('utf8')]),
  333        write(Stream, Entry.content),
  334        close(Stream)).
  335
  336% Exports entry metadata.    
  337
  338export_entry_meta(Directory, Entry):-
  339    dict_pairs(Entry, Tag, Pairs),
  340    exclude(key_is_non_meta, Pairs, MetaPairs),
  341    dict_pairs(Meta, Tag, MetaPairs),
  342    atomic_list_concat([Directory, /, Entry.slug, '.json'], MetaFile),
  343    setup_call_cleanup(
  344        open(MetaFile, write, Stream, [encoding('utf8')]),
  345        json_write(Stream, Meta),
  346        close(Stream)).
  347
  348key_is_non_meta(content-_).
  349key_is_non_meta(html-_)