Skip to content

Commit

Permalink
Added predicates for data export
Browse files Browse the repository at this point in the history
  • Loading branch information
rla committed Dec 12, 2022
1 parent e658963 commit 0a8b79f
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 3 deletions.
2 changes: 1 addition & 1 deletion pack.pl
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name('blog_core').
version('1.5.3').
version('1.6.3').
title('Blog/CMS framework').
author('Raivo Laanemets', 'https://rlaanemets.com/').
home('http://blog-core.net/').
Expand Down
13 changes: 12 additions & 1 deletion prolog/bc/bc_data_comment.pl
Original file line number Diff line number Diff line change
@@ -1,14 +1,16 @@
:- module(bc_data_comment, [
bc_comment_tree/2, % +EntryId, -Comments
bc_comment_save/3, % +EntryId, +Comment, -Id
bc_comment_remove/3 % +Actor, +EntryId, +Id
bc_comment_remove/3, % +Actor, +EntryId, +Id
bc_export_comments/1 % +Filename
]).

/** <module> Handles post comments */

:- use_module(library(sort_dict)).
:- use_module(library(docstore)).
:- use_module(library(debug)).
:- use_module(library(http/json)).

:- use_module(bc_mail).
:- use_module(bc_entry).
Expand Down Expand Up @@ -97,3 +99,12 @@

remove_access(_, _):-
throw(error(no_access)).

% Exports all comments to the given file.

bc_export_comments(File):-
ds_all(comment, Comments),
setup_call_cleanup(
open(File, write, Stream, [encoding('utf8')]),
json_write(Stream, Comments),
close(Stream)).
45 changes: 44 additions & 1 deletion prolog/bc/bc_data_entry.pl
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,8 @@
bc_trash_list/2, % +Actor, -List
bc_purge_trash/1, % +Actor
bc_entry/3, % +Actor, +Id, -Entry
bc_entry_info/3 % +Actor, +Id, -Entry
bc_entry_info/3, % +Actor, +Id, -Entry
bc_export_all/1 % +Directory
]).

/** <module> Handles entry data */
Expand All @@ -19,6 +20,7 @@
:- use_module(library(sort_dict)).
:- use_module(library(docstore)).
:- use_module(library(md/md_parse)).
:- use_module(library(http/json)).

:- use_module(bc_access).
:- use_module(bc_search).
Expand Down Expand Up @@ -304,3 +306,44 @@
ds_find(comment, post=Id, [post], List),
length(List, Count),
put_dict(_{ comments: Count }, EntryIn, EntryOut).

% Exports all entries to the directory.

bc_export_all(Directory):-
( exists_directory(Directory)
-> export_all_to_directory(Directory)
; throw(error(no_directory(Directory)))).

export_all_to_directory(Directory):-
ds_all(entry, Entries),
maplist(export_entry(Directory), Entries).

% Exports entry to the given directory.

export_entry(Directory, Entry):-
export_entry_meta(Directory, Entry),
export_entry_content(Directory, Entry).

% Exports entry Markdown content.

export_entry_content(Directory, Entry):-
atomic_list_concat([Directory, /, Entry.slug, '.md'], MdFile),
setup_call_cleanup(
open(MdFile, write, Stream, [encoding('utf8')]),
write(Stream, Entry.content),
close(Stream)).

% Exports entry metadata.

export_entry_meta(Directory, Entry):-
dict_pairs(Entry, Tag, Pairs),
exclude(key_is_non_meta, Pairs, MetaPairs),
dict_pairs(Meta, Tag, MetaPairs),
atomic_list_concat([Directory, /, Entry.slug, '.json'], MetaFile),
setup_call_cleanup(
open(MetaFile, write, Stream, [encoding('utf8')]),
json_write(Stream, Meta),
close(Stream)).

key_is_non_meta(content-_).
key_is_non_meta(html-_).

0 comments on commit 0a8b79f

Please sign in to comment.