View source with raw comments or as raw
   1:- module(conf_https, []).
   2:- use_module(library(settings)).
   3:- use_module(library(http/http_ssl_plugin)).
   4:- use_module(library(http/thread_httpd)).
   5:- use_module(library(http/http_dispatch)).
   6
   7/** <module> Provide HTTPS
   8
   9This plugin module makes the server available under https (aka http over
  10SSL).  The default port for HTTPS usage is 443.
  11
  12@see etc/README.txt for creating SSL certificates
  13*/
  14
  15:- setting(https:port, integer, 1443,
  16	   'Port to use for https connections').
  17
  18:- set_setting_default(http:public_host,   localhost).
  19:- set_setting_default(http:public_port,   setting(https:port)).
  20:- set_setting_default(http:public_scheme, https).
  21
  22start_https :-
  23	setting(https:port, Port),
  24	http_server(http_dispatch,
  25		    [ port(Port),
  26		      ssl([ host('localhost'),
  27                            cacert_file('etc/demoCA/cacert.pem'),
  28			    certificate_file('etc/server/server-cert.pem'),
  29			    key_file('etc/server/server-key.pem'),
  30			    password('apenoot1')
  31                          ])
  32                    ]).
  33
  34:- initialization
  35	start_https.