View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2020, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(http_redis_plugin, []).   36:- use_module(library(http/http_session)).   37:- autoload(library(apply), [maplist/3]).   38:- autoload(library(error), [must_be/2]).   39:- autoload(library(lists), [member/2]).   40:- autoload(library(redis), [redis/3]).   41:- autoload(library(broadcast), [broadcast/1]).   42:- use_module(library(debug), [debug/3]).   43
   44/** <module> Hook session management to use Redis
   45
   46This module acts as  a   plugin  for library(http/http_session), storing
   47session information on a Redis server. This has several consequences:
   48
   49  - The Prolog server may be restarted without loosing session data.
   50    This is notably useful when long session timeouts are used.
   51  - Multiple Prolog servers can act as a cluster while session
   52    management is used.
   53  - Associating Prolog data with sessions is relatively slow.  The
   54    assert/retract is replaced by managing a Redis list.  Data in
   55    this list is matched sequentially, where each term needs to be
   56    parsed before it can be matched.
   57  - Associated data is currently limited to __ground terms__.
   58
   59The   library   is   activated   by   loading    it   in   addition   to
   60library(http/http_session)  and  using    http_set_session_options/1  to
   61configure the Redis database as below. The redis_server/2 predicate from
   62library(redis) can be used  to  specify   the  parameters  for the redis
   63server  such as host, port or authentication.
   64
   65```
   66:- http_set_session_options(
   67       [ redis_db(default),
   68         redis_prefix('swipl:http:session')
   69       ]).
   70```
   71
   72## Redis key usage
   73
   74All  Redis  keys  reside  under  a    prefix  specified  by  the  option
   75redis_prefix(Prefix), which defaults to  `'swipl:http:session'`. Here we
   76find:
   77
   78  - An ordered set at <prefix>:expire that contains the session ids,
   79    ordered by the time the session expires.  Session enumeration and
   80    garbage collection is based on this set.
   81  - A hash at <prefix>:session:<id> which contains the _peer_ address,
   82    the _last used_ time and optionally session specific settings.
   83  - If there is session _data_, a list at <prefix>:data:<id> of Prolog
   84    terms, represented as strings that contain the session data.
   85*/
   86
   87:- multifile
   88    http_session:hooked/0,
   89    http_session:hook/1,
   90    http_session:session_option/2.   91
   92http_session:session_option(redis_db, atom).
   93http_session:session_option(redis_prefix, atom).
   94
   95http_session:hooked :-
   96    http_session:session_setting(redis_db(_)).
   97
   98%http_session:hook(assert_session(SessionID, Peer)).
   99%http_session:hook(set_session_option(SessionId, Setting)).
  100%http_session:hook(get_session_option(SessionId, Setting)).
  101%http_session:hook(active_session(SessionID, Peer, LastUsed)).
  102%http_session:hook(set_last_used(SessionID, Now, TimeOut)).
  103%http_session:hook(asserta(session_data(SessionId, Data))).
  104%http_session:hook(assertz(session_data(SessionId, Data))).
  105%http_session:hook(retract(session_data(SessionId, Data))).
  106%http_session:hook(retractall(session_data(SessionId, Data))).
  107%http_session:hook(session_data(SessionId, Data)).
  108%http_session:hook(current_session(SessionID, Data)).
  109%http_session:hook(close_session(?SessionID)).
  110%http_session:hook(gc_sessions).
  111
  112http_session:hook(assert_session(SessionID, Peer)) :-
  113    session_db(SessionID, DB, Key),
  114    http_session:session_setting(timeout(Timeout)),
  115    peer_string(Peer, PeerS),
  116    get_time(Now),
  117    redis(DB, hset(Key,
  118                   peer, PeerS,
  119                   last_used, Now)),
  120    expire(SessionID, Timeout).
  121http_session:hook(set_session_option(SessionID, Setting)) :-
  122    session_db(SessionID, DB, Key),
  123    Setting =.. [Name,Value],
  124    redis(DB, hset(Key, Name, Value as prolog)),
  125    (   Setting = timeout(Timeout)
  126    ->  expire(SessionID, Timeout)
  127    ;   true
  128    ).
  129http_session:hook(get_session_option(SessionID, Setting)) :-
  130    session_db(SessionID, DB, Key),
  131    Setting =.. [Name,Value],
  132    redis(DB, hget(Key, Name), Value).
  133http_session:hook(active_session(SessionID, Peer, LastUsed)) :-
  134    session_db(SessionID, DB, Key),
  135    redis(DB, hget(Key, peer), PeerS),
  136    peer_string(Peer, PeerS),
  137    redis(DB, hget(Key, last_used), LastUsed as number).
  138http_session:hook(set_last_used(SessionID, Now, Timeout)) :-
  139    session_db(SessionID, DB, Key),
  140    redis(DB, hset(Key,
  141                   last_used, Now)),
  142    Expire is Now+Timeout,
  143    expire(SessionID, Expire).
  144http_session:hook(asserta(session_data(SessionID, Data))) :-
  145    must_be(ground, Data),
  146    session_data_db(SessionID, DB, Key),
  147    redis(DB, lpush(Key, Data as prolog)).
  148http_session:hook(assertz(session_data(SessionID, Data))) :-
  149    must_be(ground, Data),
  150    session_data_db(SessionID, DB, Key),
  151    redis(DB, rpush(Key, Data as prolog)).
  152http_session:hook(retract(session_data(SessionID, Data))) :-
  153    session_data_db(SessionID, DB, Key),
  154    redis_get_list(DB, Key, 10, List),
  155    member(Data, List),
  156    redis(DB, lrem(Key, 1, Data as prolog)).
  157http_session:hook(retractall(session_data(SessionID, Data))) :-
  158    forall(http_session:hook(retract(session_data(SessionID, Data))),
  159           true).
  160http_session:hook(session_data(SessionID, Data)) :-
  161    session_data_db(SessionID, DB, Key),
  162    redis_get_list(DB, Key, 10, List),
  163    member(Data, List).
  164http_session:hook(current_session(SessionID, Data)) :-
  165    session_db(SessionID, DB, Key),
  166    redis(DB, hget(Key, last_used), Time as number),
  167    get_time(Now),
  168    Idle is Now - Time,
  169    (   http_session:session_setting(SessionID, timeout(TMO)),
  170        TMO > 0
  171    ->  Idle =< TMO
  172    ;   true
  173    ),
  174    (   Data = peer(Peer),
  175        redis(DB, hget(Key, peer), PeerS),
  176        peer_string(Peer, PeerS)
  177    ;   Data = idle(Idle)
  178    ;   non_reserved_property(Data),
  179        http_session:hook(session_data(SessionID, Data))
  180    ).
  181http_session:hook(close_session(SessionID)) :-
  182    gc_session(SessionID).
  183http_session:hook(gc_sessions) :-
  184    gc_sessions.
  185
  186non_reserved_property(P) :-
  187    var(P),
  188    !.
  189non_reserved_property(peer(_)) :- !, fail.
  190non_reserved_property(idle(_)) :- !, fail.
  191non_reserved_property(_).
  192
  193
  194		 /*******************************
  195		 *      SCHEDULE TIMEOUT	*
  196		 *******************************/
  197
  198expire(SessionID, Timeout) :-
  199    get_time(Now),
  200    Time is Now+Timeout,
  201    session_expire_db(DB, Key),
  202    redis(DB, zadd(Key, Time, SessionID)).
  203
  204gc_sessions :-
  205    session_expire_db(DB, Key),
  206    get_time(Now),
  207    redis(DB, zrangebyscore(Key, "-inf", Now), TimedOut as atom),
  208    forall(member(SessionID, TimedOut),
  209           gc_session(SessionID)).
  210
  211gc_session(SessionID) :-
  212    debug(http_session(gc), 'GC session ~p', [SessionID]),
  213    session_db(SessionID, DB, SessionKey),
  214    session_expire_db(DB, TMOKey),
  215    redis(DB, zrem(TMOKey, SessionID)),
  216    redis(DB, hget(SessionKey, peer), PeerS),
  217    peer_string(Peer, PeerS),
  218    broadcast(http_session(end(SessionID, Peer))),
  219    redis(DB, del(SessionKey)),
  220    session_data_db(SessionID, DB, DataKey),
  221    redis(DB, del(DataKey)).
  222
  223
  224		 /*******************************
  225		  *
  226		 *             UTIL		*
  227		 *******************************/
  228
  229peer_string(ip(A,B,C,D), String) :-
  230    nonvar(String),
  231    !,
  232    split_string(String, ".", "", List),
  233    maplist(number_string, [A,B,C,D], List).
  234peer_string(ip(A,B,C,D), String) :-
  235    atomics_to_string([A,B,C,D], ".", String).
  236
  237session_db(SessionID, DB, Key) :-
  238    nonvar(SessionID),
  239    !,
  240    http_session:session_setting(redis_db(DB)),
  241    key_prefix(Prefix),
  242    atomics_to_string([Prefix,session,SessionID], :, Key).
  243session_db(SessionID, DB, Key) :-
  244    session_expire_db(DB, TMOKey),
  245    redis_zscan(DB, TMOKey, Pairs, []),
  246    member(SessionIDS-_Timeout, Pairs),
  247    atom_string(SessionID, SessionIDS),
  248    key_prefix(Prefix),
  249    atomics_to_string([Prefix,session,SessionID], :, Key).
  250
  251session_expire_db(DB, Key) :-
  252    http_session:session_setting(redis_db(DB)),
  253    key_prefix(Prefix),
  254    atomics_to_string([Prefix,expire], :, Key).
  255
  256session_data_db(SessionID, DB, Key) :-
  257    http_session:session_setting(redis_db(DB)),
  258    key_prefix(Prefix),
  259    atomics_to_string([Prefix,data,SessionID], :, Key).
  260
  261key_prefix(Prefix) :-
  262    http_session:session_setting(redis_prefix(Prefix)),
  263    !.
  264key_prefix('swipl:http:sessions')