View source with raw comments or as raw
   1:- module(conf_https_only, []).
   2:- use_module(library(option)).
   3:- use_module(library(http/thread_httpd)).
   4:- use_module(library(http/http_dispatch)).
   5:- use_module(cliopatria(cliopatria)).
   6
   7/** <module> Configure the HTTPS server
   8
   9To enable HTTPS, create a directory =http= inside the =|config-enabled|=
  10directory of the application and add the following files:
  11
  12    $ =|server-cert.pem|= :
  13      Contains the server certificate.  Passed as certificate_file(File)
  14      to the ssl_context/3 predicate. This file may be omitted, in
  15      which case the =|server-key.pem|= is also passed using the
  16      key_file(+File) option.
  17    $ =|server-key.pem|= :
  18      Contains the private key for the server.  Passed as key_file(File)
  19      option of ssl_context/3.
  20    $ =|passwd|= :
  21      Needs to hold the password if the private key is protected
  22      with a password.  Passed using the password(Password) option
  23      of ssl_context/3.
  24
  25@see	http://www.swi-prolog.org/pldoc/doc_for?object=ssl_context/3 for
  26	a description of these files.
  27*/
  28
  29% uncomment the following to add a server that redirects requests from a
  30% plain HTTP port to the HTTPS port. This configuration assumes there is
  31% no reverse proxy between the public   network and ClioPatria. If there
  32% is, this redirect as well as HTTPS   handling is typically done by the
  33% proxy server.
  34
  35% :- initialization cp_after_load(plain_http_server).
  36
  37plain_http_server :-
  38	plain_http_server([port(5020)]).
  39
  40plain_http_server(Options) :-
  41	option(port(Port), Options),
  42	http_server_property(Port, goal(redirect_to_https)), !.
  43plain_http_server(Options) :-
  44	http_server(redirect_to_https,
  45		    Options).
  46
  47redirect_to_https(Request) :-
  48	option(host(Host), Request),
  49	option(request_uri(ReqURI), Request),
  50	http_server_property(Port, scheme(https)),
  51	format(string(URL), 'https://~w:~w~w', [Host, Port, ReqURI]),
  52	http_redirect(see_other, URL, Request).