View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2017, VU University Amsterdam
    7			 CWI Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(chat_store,
   37          [ chat_store/1,               % +Message
   38            chat_messages/3             % +DocID, -Messages, +Options
   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.').

Store chat messages

*/

   58:- multifile
   59    swish_config:chat_count_about/2.	% +DocID, -Count
   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)).
 chat_dir_file(+DocID, -Path, -File)
True when Path/File is the place to store char messages about DocID.
   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).
 existing_chat_file(+DocID, -File) is semidet
True when File is the path of the file holding chat messages from DocID.
  115existing_chat_file(DocID, File) :-
  116    chat_dir_file(DocID, _, File),
  117    exists_file(File).
 chat_store(+Message:dict) is det
Add a chat message to the chat store. If Message.create == false, the message is only stored if the chat is already active. This is used to only insert messages about changes to the file if there is an ongoing chat so we know to which version chat messages refer.
  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(_).
 strip_chat(_Message0, -Message) is det
Remove stuff from a chat message that is useless to store permanently, such as the wsid (WebSocket id).
  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).
 chat_messages(+DocID, -Messages:list, +Options) is det
Get messages associated with DocID. Options include
max(+Max)
Maximum number of messages to retrieve. Default is 25.
after(+TimeStamp)
Only get messages after TimeStamp
  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.
 chat_message_count(+DocID, -Count) is det
Count the number of message stored for DocID. This is the same as the number of lines.
  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(_).
 swish_config:chat_count_about(+DocID, -Count)
True when Count is the number of messages about DocID
  275swish_config:chat_count_about(DocID, Count) :-
  276    chat_message_count(DocID, Count).
  277
  278
  279		 /*******************************
  280		 *              HTTP		*
  281		 *******************************/
 chat_messages(+Request)
HTTP handler that returns chat messages for a document
  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).
 chat_status(+Request)
HTTP handler that returns chat status for document
  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            })