1:- module(bc_api_entry, []).
5:- use_module(library(arouter)). 6:- use_module(library(dict_schema)). 7
8:- use_module(bc_view). 9:- use_module(bc_api_io). 10:- use_module(bc_api_auth). 11:- use_module(bc_api_actor). 12:- use_module(bc_data_entry). 13
15
16:- route_post(api/entry,
17 bc_auth, entry_save). 18
19entry_save:-
20 bc_read_by_schema(bc_entry, Post),
21 bc_actor(Actor),
22 bc_entry_save(Actor, Post, Id),
23 bc_view_purge_cache,
24 bc_reply_success(Id).
25
27
28:- route_put(api/entry/Id,
29 bc_auth, entry_update(Id)). 30
31entry_update(Id):-
32 bc_read_by_schema(bc_entry, Entry),
33 put_dict('$id', Entry, Id, Update),
34 bc_actor(Actor),
35 bc_entry_update(Actor, Update),
36 bc_view_purge_cache,
37 bc_reply_success(Id).
38
40
41:- route_del(api/entry/Id,
42 bc_auth, entry_remove(Id)). 43
44entry_remove(Id):-
45 bc_actor(Actor),
46 bc_entry_remove(Actor, Id),
47 bc_view_purge_cache,
48 bc_reply_success(Id).
49
51
52:- route_get(api/entries/Type,
53 bc_auth, entry_list(Type)). 54
55entry_list(Type):-
56 bc_actor(Actor),
57 bc_entry_list(Actor, Type, List),
58 bc_reply_success(List).
59
61
62:- route_get(api/trash,
63 bc_auth, trash_list). 64
65trash_list:-
66 bc_actor(Actor),
67 bc_trash_list(Actor, List),
68 bc_reply_success(List).
69
71
72:- route_put(api/restore/Id,
73 bc_auth, entry_restore(Id)). 74
75entry_restore(Id):-
76 bc_actor(Actor),
77 bc_entry_restore(Actor, Id),
78 bc_reply_success(Id).
79
81
82:- route_del(api/trash/Id,
83 bc_auth, entry_remove_trash(Id)). 84
85entry_remove_trash(Id):-
86 bc_actor(Actor),
87 bc_entry_remove_trash(Actor, Id),
88 bc_reply_success(Id).
89
91
92:- route_del(api/trash,
93 bc_auth, purge_trash). 94
95purge_trash:-
96 bc_actor(Actor),
97 bc_purge_trash(Actor),
98 bc_reply_success([]).
99
101
102:- route_get(api/entry/Id,
103 bc_auth, entry_get(Id)). 104
105entry_get(Id):-
106 bc_actor(Actor),
107 bc_entry(Actor, Id, Entry),
108 bc_reply_success(Entry).
109
111
112:- route_get(api/entry/Id/info,
113 bc_auth, entry_get_info(Id)). 114
115entry_get_info(Id):-
116 bc_actor(Actor),
117 bc_entry_info(Actor, Id, Entry),
118 bc_reply_success(Entry).
119
121
122:- route_put(api/action/Id/Action,
123 bc_auth, entry_run_action(Id, Action)). 124
125entry_run_action(Id, Action):-
126 bc_actor(Actor),
127 bc_entry_action(Actor, Id, Action, Result),
128 bc_reply_success(Result).
129
132
133:- route_get(api/actions/Id,
134 bc_auth, entry_actions(Id)). 135
136entry_actions(Id):-
137 bc_actor(Actor),
138 bc_entry_actions(Actor, Id, Actions),
139 bc_reply_success(Actions).
140
143
144:- register_schema(bc_entry, _{
145 type: dict,
146 tag: entry,
147 keys: _{
148 author: _{ type: atom, min_length: 36, max_length: 36 },
149 title: _{ type: string, min_length: 1 },
150 slug: _{ type: atom, min_length: 1 },
151 tags: _{ type: list, items: atom },
152 date_published: _{ type: integer, min: 0 },
153 date_updated: _{ type: integer, min: 0 },
154 commenting: bool,
155 published: bool,
156 content: string,
157 content_type: _{ type: enum, values: [markdown, raw] },
158 description: string,
159 type: _{ type: atom, min_length: 1, max_length: 100 },
160 language: _{ type: string, min_length: 2, max_length: 10 }
161 }
162}).
HTTP handlers for managing posts */