1:- module(bc_data, [
2 bc_data_open/1, 3 bc_data_close/0
4]). 5
6:- use_module(library(docstore)). 7:- use_module(library(debug)). 8
9:- use_module(bc_data_config). 10:- use_module(bc_data_user). 11:- use_module(bc_migrate). 12:- use_module(bc_search). 13:- use_module(bc_type). 14:- use_module(bc_role). 15
17
18:- bc_register_role(admin, 'Admin', true). 19:- bc_register_role(author, 'Author', true). 20:- bc_register_role(anon, 'Anonymous', false). 21
23
24:- bc_register_type(post, 'Post', 'Posts', [
25 admin(create, read_any, update_any, remove_any, publish_any, files),
26 author(create, read_any, update_own, remove_own, publish_own, files)
27], true). 28
29:- bc_register_type(page, 'Page', 'Pages', [
30 admin(create, read_any, update_any, remove_any, publish_any, files),
31 author(create, read_any, update_own, remove_own, publish_own, files)
32], false). 33
34:- bc_register_type(block, 'Block', 'Blocks', [
35 admin(create, read_any, update_any, remove_any, publish_any, files),
36 author(create, read_any, update_own, remove_own, publish_own, files)
37], false). 38
39:- dynamic(opened/0).
46bc_data_open(File):-
47 ds_open(File),
48 bc_init,
49 bc_index_all,
50 asserta(opened),
51 debug(bc_data, 'opened docstore file ~p', [File]).
57bc_data_close:-
58 ds_close,
59 bc_index_remove,
60 retractall(opened),
61 debug(bc_data, 'closed docstore file', []).
62
65
66bc_init:-
67 bc_migrate(
68 bc_initial_config,
69 'Inserts the initial config',
70 bc_initial_config),
71 bc_migrate(
72 bc_initial_user,
73 'Inserts the initial user',
74 bc_initial_user),
75 bc_migrate(
76 bc_add_language,
77 'Adds language to posts',
78 bc_add_language),
79 bc_migrate(
80 bc_smtp_settings,
81 'Adds SMTP settings',
82 bc_smtp_settings),
83 bc_migrate(
84 bc_remove_files,
85 'Removes files key from users',
86 bc_remove_files),
87 bc_migrate(
88 bc_smtp_security,
89 'Adds smtp_security configuration parameter',
90 bc_smtp_security),
91 bc_migrate(
92 bc_smtp_from,
93 'Adds smtp_from configuration parameter',
94 bc_smtp_from),
95 bc_migrate(
96 bc_comment_notifications,
97 'Adds option for users to receive comment notifications',
98 bc_comment_notifications),
99 bc_migrate(
100 bc_site,
101 'Adds option for setting site',
102 bc_site).
103
105
106bc_initial_config:-
107 bc_config_set(title, 'Untitled site').
108
109bc_smtp_settings:-
110 bc_config_set(smtp_enabled, false),
111 bc_config_set(smtp_host, 'localhost'),
112 bc_config_set(smtp_user, 'user'),
113 bc_config_set(smtp_password, 'password'),
114 bc_config_set(smtp_auth, 'login').
115
116bc_smtp_security:-
117 bc_config_set(smtp_security, 'none').
118
119bc_smtp_from:-
120 bc_config_set(smtp_from, 'admin@example.com').
121
:-
123 ds_col_add_key(user, comment_notifications, true).
124
125bc_site:-
126 bc_config_set(site, 'http://example.com').
127
129
130bc_initial_user:-
131 bc_user_save_initial(user{
132 fullname: 'Admin',
133 username: 'admin@example.com',
134 password: 'admin',
135 type: admin,
136 link: ""
137 }).
138
141
142bc_add_language:-
143 ds_col_add_key(entry, language, en),
144 bc_config_set(default_language, en).
145
146bc_remove_files:-
147 ds_col_remove_key(user, files).
148
151
152ds_snapshot_sleep(86400).
153
154start_ds_snapshot:-
155 debug(bc_data, 'started Docstore snapshot thread', []),
156 ds_snapshot_sleep(Sleep),
157 sleep(Sleep),
158 ds_snapshot_loop.
159
163
164ds_snapshot_loop:-
165 debug(bc_data, 'taking Docstore snapshot', []),
166 ds_snapshot_iteration,
167 ds_snapshot_sleep(Sleep),
168 sleep(Sleep),
169 ds_snapshot_loop.
170
171ds_snapshot_iteration:-
172 \+ opened, !.
173
174ds_snapshot_iteration:-
175 ( catch(ds_snapshot, E, true)
176 -> ( var(E)
177 -> true
178 ; format(user_error, 'Docstore snapshot call threw error: ~w~n', [E]))
179 ; writeln(user_error, 'Docstore snapshot call failed')).
180
181:- thread_create(start_ds_snapshot, _, []).