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]).
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
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 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 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')
Hook session management to use Redis
This module acts as a plugin for library(http/http_session), storing session information on a Redis server. This has several consequences:
The library is activated by loading it in addition to library(http/http_session) and using http_set_session_options/1 to configure the Redis database as below. The redis_server/2 predicate from library(redis) can be used to specify the parameters for the redis server such as host, port or authentication.
Redis key usage
All Redis keys reside under a prefix specified by the option
redis_prefix(Prefix)
, which defaults to'swipl:http:session'
. Here we find: