35
36:- module(chat_store,
37 [ chat_store/1, 38 chat_messages/3 39 ]). 40:- use_module(library(settings)). 41:- use_module(library(filesex)). 42:- use_module(library(option)). 43:- use_module(library(sha)). 44:- use_module(library(apply)). 45:- use_module(library(http/http_dispatch)). 46:- use_module(library(http/http_parameters)). 47:- use_module(library(http/http_json)). 48
49:- http_handler(swish(chat/messages), chat_messages, [ id(chat_messages) ]). 50:- http_handler(swish(chat/status), chat_status, [ id(chat_status) ]). 51
52:- setting(directory, callable, data(chat),
53 'The directory for storing chat messages.').
58:- multifile
59 swish_config:chat_count_about/2. 60
61:- listen(http(pre_server_start),
62 open_chatstore). 63
64:- dynamic storage_dir/1. 65:- volatile storage_dir/1. 66
67open_chatstore :-
68 storage_dir(_),
69 !.
70open_chatstore :-
71 with_mutex(chat_store, open_chatstore_guarded).
72
73open_chatstore_guarded :-
74 storage_dir(_),
75 !.
76open_chatstore_guarded :-
77 setting(directory, Spec),
78 absolute_file_name(Spec, Dir,
79 [ file_type(directory),
80 access(write),
81 file_errors(fail)
82 ]), !,
83 asserta(storage_dir(Dir)).
84open_chatstore_guarded :-
85 setting(directory, Spec),
86 absolute_file_name(Spec, Dir,
87 [ solutions(all)
88 ]),
89 \+ exists_directory(Dir),
90 catch(make_directory(Dir),
91 error(permission_error(create, directory, Dir), _),
92 fail), !,
93 asserta(storage_dir(Dir)).
99chat_dir_file(DocID, Path, File) :-
100 open_chatstore,
101 sha_hash(DocID, Bin, []),
102 hash_atom(Bin, Hash),
103 sub_atom(Hash, 0, 2, _, D1),
104 sub_atom(Hash, 2, 2, _, D2),
105 sub_atom(Hash, 4, _, 0, Name),
106 storage_dir(Dir),
107 atomic_list_concat([Dir, D1, D2], /, Path),
108 atomic_list_concat([Path, Name], /, File).
115existing_chat_file(DocID, File) :-
116 chat_dir_file(DocID, _, File),
117 exists_file(File).
126chat_store(Message) :-
127 chat{docid:DocIDS} :< Message,
128 atom_string(DocID, DocIDS),
129 chat_dir_file(DocID, Dir, File),
130 ( del_dict(create, Message, false, Message1)
131 -> exists_file(File)
132 ; Message1 = Message
133 ),
134 !,
135 make_directory_path(Dir),
136 strip_chat(Message1, Message2),
137 with_mutex(chat_store,
138 ( setup_call_cleanup(
139 open(File, append, Out, [encoding(utf8)]),
140 format(Out, '~q.~n', [Message2]),
141 close(Out)),
142 increment_message_count(DocID)
143 )).
144chat_store(_).
151strip_chat(Message0, Message) :-
152 strip_chat_user(Message0.get(user), User),
153 !,
154 Message = Message0.put(user, User).
155strip_chat(Message, Message).
156
157strip_chat_user(User0, User) :-
158 del_dict(wsid, User0, _, User),
159 !.
160strip_chat_user(User, User).
172chat_messages(DocID, Messages, Options) :-
173 ( existing_chat_file(DocID, File)
174 -> read_messages(File, Messages0, Options),
175 filter_old(Messages0, Messages, Options)
176 ; Messages = []
177 ).
178
179read_messages(File, Messages, Options) :-
180 setup_call_cleanup(
181 open(File, read, In, [encoding(utf8)]),
182 read_messages_from_stream(In, Messages, Options),
183 close(In)).
184
185read_messages_from_stream(In, Messages, Options) :-
186 option(max(Max), Options, 25),
187 integer(Max),
188 seek(In, 0, eof, _Pos),
189 backskip_lines(In, Max),
190 !,
191 read_terms(In, Messages).
192read_messages_from_stream(In, Messages, _Options) :-
193 seek(In, 0, bof, _NewPos),
194 read_terms(In, Messages).
195
196read_terms(In, Terms) :-
197 read_term(In, H, []),
198 ( H == end_of_file
199 -> Terms = []
200 ; Terms = [H|T],
201 read_terms(In, T)
202 ).
203
204backskip_lines(Stream, Lines) :-
205 byte_count(Stream, Here),
206 between(10, 20, X),
207 Start is max(0, Here-(1<<X)),
208 seek(Stream, Start, bof, _NewPos),
209 skip(Stream, 0'\n),
210 line_starts(Stream, Here, Starts),
211 reverse(Starts, RStarts),
212 nth1(Lines, RStarts, LStart),
213 !,
214 seek(Stream, LStart, bof, _).
215
216line_starts(Stream, To, Starts) :-
217 byte_count(Stream, Here),
218 ( Here >= To
219 -> Starts = []
220 ; Starts = [Here|T],
221 skip(Stream, 0'\n),
222 line_starts(Stream, To, T)
223 ).
224
225filter_old(Messages0, Messages, Options) :-
226 option(after(After), Options),
227 After > 0,
228 !,
229 include(after(After), Messages0, Messages).
230filter_old(Messages, Messages, _).
231
232after(After, Message) :-
233 is_dict(Message),
234 Message.get(time) > After.
241:- dynamic message_count/2. 242:- volatile message_count/2. 243
244chat_message_count(DocID, Count) :-
245 message_count(DocID, Count),
246 !.
247chat_message_count(DocID, Count) :-
248 count_messages(DocID, Count),
249 asserta(message_count(DocID, Count)).
250
251count_messages(DocID, Count) :-
252 ( existing_chat_file(DocID, File)
253 -> setup_call_cleanup(
254 open(File, read, In, [encoding(iso_latin_1)]),
255 ( skip(In, 256),
256 line_count(In, Line)
257 ),
258 close(In)),
259 Count is Line - 1
260 ; Count = 0
261 ).
262
263increment_message_count(DocID) :-
264 clause(message_count(DocID, Count0), _, CRef),
265 !,
266 Count is Count0+1,
267 asserta(message_count(DocID, Count)),
268 erase(CRef).
269increment_message_count(_).
275swish_config:chat_count_about(DocID, Count) :-
276 chat_message_count(DocID, Count).
277
278
279
287chat_messages(Request) :-
288 http_parameters(Request,
289 [ docid(DocID, []),
290 max(Max, [nonneg, optional(true)]),
291 after(After, [number, optional(true)])
292 ]),
293 include(ground, [max(Max), after(After)], Options),
294 chat_messages(DocID, Messages, Options),
295 reply_json_dict(Messages).
301chat_status(Request) :-
302 http_parameters(Request,
303 [ docid(DocID, []),
304 max(Max, [nonneg, optional(true)]),
305 after(After, [number, optional(true)])
306 ]),
307 include(ground, [max(Max), after(After)], Options),
308 chat_message_count(DocID, Total),
309 ( Options == []
310 -> Count = Total
311 ; chat_messages(DocID, Messages, Options),
312 length(Messages, Count)
313 ),
314 reply_json_dict(
315 json{docid: DocID,
316 total: Total,
317 count: Count
318 })
Store chat messages
*/