View source with raw comments or as raw
   1:- module(conf_authenticate, []).
   2:- use_module(library(http/http_wrapper), []).
   3:- use_module(library(http/http_authenticate)).
   4:- use_module(user(user_db)).
   5
   6/** <module> Protect entire server
   7
   8This  config  file  protects  the  entire    server   using  basic  HTTP
   9authentication. This may be combined with configuring HTTPS as described
  10in https.pl.
  11
  12ClioPatria will not force login if  no   users  are yet defined. In this
  13case you will be redirected to the `create admin user page'.  If youn do
  14not want that, delete the second clause.
  15
  16@tbd	If you use this login mechanism, you cannot logout.  Maybe we
  17	should implement http://stackoverflow.com/questions/233507
  18*/
  19
  20:- multifile
  21	http:request_expansion/2.
  22
  23http:request_expansion(Request, Request) :-
  24	memberchk(authorization(Text), Request), !,
  25	(   http_authorization_data(Text, basic(User, Password)),
  26	    validate_password(User, Password)
  27	->  true
  28	;   throw(http_reply(authorise(basic, 'ClioPatria')))
  29	).
  30http:request_expansion(Request, Request) :-
  31	\+ current_user(_), !.			% allow if no users are defined
  32http:request_expansion(Request, Request) :-
  33	throw(http_reply(authorise(basic, 'ClioPatria'))).