35
36:- module(http_ssl_plugin, []). 37:- use_module(library(ssl)). 38:- use_module(library(socket)). 39:- use_module(library(debug)). 40:- use_module(library(option)). 41:- use_module(library(http/thread_httpd)). 42:- use_module(library(http/http_header)).
55:- multifile
56 thread_httpd:make_socket_hook/3,
57 thread_httpd:accept_hook/2,
58 thread_httpd:open_client_hook/6,
59 http:http_protocol_hook/5,
60 http:open_options/2,
61 http:http_connection_over_proxy/6,
62 http:ssl_server_create_hook/3,
63 http:ssl_server_open_client_hook/3. 64
65
66
78thread_httpd:make_socket_hook(Port, M:Options0, Options) :-
79 select(ssl(SSLOptions0), Options0, Options1),
80 !,
81 add_secure_ciphers(SSLOptions0, SSLOptions1),
82 disable_sslv3(SSLOptions1, SSLOptions),
83 make_socket(Port, Socket, Options1),
84 ssl_context(server, SSL0, M:SSLOptions),
85 ( http:ssl_server_create_hook(SSL0, SSL, Options1)
86 -> true
87 ; SSL = SSL0
88 ),
89 atom_concat('httpsd', Port, Queue),
90 Options = [ queue(Queue),
91 tcp_socket(Socket),
92 ssl_instance(SSL)
93 | Options1
94 ].
100add_secure_ciphers(SSLOptions0, SSLOptions) :-
101 ( option(cipher_list(_), SSLOptions0)
102 -> SSLOptions = SSLOptions0
103 ; ssl_secure_ciphers(Ciphers),
104 SSLOptions = [cipher_list(Ciphers)|SSLOptions0]
105 ).
113disable_sslv3(SSLOptions0, SSLOptions) :-
114 ( option(min_protocol_version(_), SSLOptions0)
115 ; option(disable_ssl_methods(_), SSLOptions0)
116 ),
117 !,
118 SSLOptions = SSLOptions0.
119disable_sslv3(SSLOptions0,
120 [ disable_ssl_methods([sslv3,sslv23]), 121 min_protocol_version(tlsv1) 122 | SSLOptions0
123 ]).
124
125
126make_socket(_Port, Socket, Options) :-
127 option(tcp_socket(Socket), Options),
128 !.
129make_socket(Port, Socket, _Options) :-
130 tcp_socket(Socket),
131 tcp_setopt(Socket, reuseaddr),
132 tcp_bind(Socket, Port),
133 tcp_listen(Socket, 5).
140thread_httpd:accept_hook(Goal, Options) :-
141 memberchk(ssl_instance(SSL), Options),
142 !,
143 memberchk(queue(Queue), Options),
144 memberchk(tcp_socket(Socket), Options),
145 tcp_accept(Socket, Client, Peer),
146 debug(http(connection), 'New HTTPS connection from ~p', [Peer]),
147 http_enough_workers(Queue, accept, Peer),
148 thread_send_message(Queue, ssl_client(SSL, Client, Goal, Peer)).
171thread_httpd:open_client_hook(ssl_client(SSL0, Client, Goal, Peer),
172 Goal, In, Out,
173 [peer(Peer), protocol(https)],
174 Options) :-
175 ( http:ssl_server_open_client_hook(SSL0, SSL1, Options)
176 -> true
177 ; SSL1 = SSL0
178 ),
179 option(timeout(TMO), Options, 60),
180 tcp_open_socket(Client, Read, Write),
181 set_stream(Read, timeout(TMO)),
182 set_stream(Write, timeout(TMO)),
183 ssl_set_options(SSL1, SSL, [close_parent(true)]),
184 catch(ssl_negotiate(SSL, Read, Write, In, Out),
185 E,
186 ssl_failed(Read, Write, E)).
187
188ssl_failed(Read, Write, E) :-
189 close(Write, [force(true)]),
190 close(Read, [force(true)]),
191 throw(E).
192
193
194
205http:http_protocol_hook(https, Parts, PlainStreamPair, StreamPair, Options) :-
206 ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options).
207http:http_protocol_hook(wss, Parts, PlainStreamPair, StreamPair, Options) :-
208 ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options).
209
210ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options) :-
211 memberchk(host(Host), Parts),
212 ssl_context(client, SSL, [ host(Host),
213 close_parent(true)
214 | Options
215 ]),
216 stream_pair(PlainStreamPair, PlainIn, PlainOut),
217 218 ssl_negotiate(SSL, PlainIn, PlainOut, In, Out),
219 stream_pair(StreamPair, In, Out).
227http:open_options(Parts, Options) :-
228 memberchk(scheme(S), Parts),
229 ssl_scheme(S),
230 Options = [cacert_file(system(root_certificates))].
231
232ssl_scheme(https).
233ssl_scheme(wss).
242http:http_connection_over_proxy(proxy(ProxyHost, ProxyPort), Parts,
243 Host:Port, StreamPair, Options, Options) :-
244 memberchk(scheme(https), Parts),
245 !,
246 tcp_connect(ProxyHost:ProxyPort, StreamPair, [bypass_proxy(true)]),
247 catch(negotiate_http_connect(StreamPair, Host:Port),
248 Error,
249 ( close(StreamPair, [force(true)]),
250 throw(Error)
251 )).
252
253negotiate_http_connect(StreamPair, Address):-
254 format(StreamPair, 'CONNECT ~w HTTP/1.1\r\n\r\n', [Address]),
255 flush_output(StreamPair),
256 http_read_reply_header(StreamPair, Header),
257 memberchk(status(_, Status, Message), Header),
258 ( Status == ok
259 -> true
260 ; throw(error(proxy_rejection(Message), _))
261 )
SSL plugin for HTTP libraries
This module can be loaded next to
library(thread_httpd)
andlibrary(http_open)
to provide secure HTTP (HTTPS) services and client access.An example secure server using self-signed certificates can be found in the <plbase>/
doc/packages/examples/ssl/https.pl
, where <plbase> is the SWI-Prolog installation directory. */