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,
85 SSL0,
86 M:[ close_parent(true)
87 | SSLOptions
88 ]),
89 ( http:ssl_server_create_hook(SSL0, SSL, Options1)
90 -> true
91 ; SSL = SSL0
92 ),
93 atom_concat('httpsd', Port, Queue),
94 Options = [ queue(Queue),
95 tcp_socket(Socket),
96 ssl_instance(SSL)
97 | Options1
98 ].
104add_secure_ciphers(SSLOptions0, SSLOptions) :-
105 ( option(cipher_list(_), SSLOptions0)
106 -> SSLOptions = SSLOptions0
107 ; ssl_secure_ciphers(Ciphers),
108 SSLOptions = [cipher_list(Ciphers)|SSLOptions0]
109 ).
117disable_sslv3(SSLOptions0, SSLOptions) :-
118 ( option(min_protocol_version(_), SSLOptions0)
119 ; option(disable_ssl_methods(_), SSLOptions0)
120 ),
121 !,
122 SSLOptions = SSLOptions0.
123disable_sslv3(SSLOptions0,
124 [ disable_ssl_methods([sslv3,sslv23]), 125 min_protocol_version(tlsv1) 126 | SSLOptions0
127 ]).
128
129
130make_socket(_Port, Socket, Options) :-
131 option(tcp_socket(Socket), Options),
132 !.
133make_socket(Port, Socket, _Options) :-
134 tcp_socket(Socket),
135 tcp_setopt(Socket, reuseaddr),
136 tcp_bind(Socket, Port),
137 tcp_listen(Socket, 5).
144thread_httpd:accept_hook(Goal, Options) :-
145 memberchk(ssl_instance(SSL), Options),
146 !,
147 memberchk(queue(Queue), Options),
148 memberchk(tcp_socket(Socket), Options),
149 tcp_accept(Socket, Client, Peer),
150 debug(http(connection), 'New HTTPS connection from ~p', [Peer]),
151 http_enough_workers(Queue, accept, Peer),
152 thread_send_message(Queue, ssl_client(SSL, Client, Goal, Peer)).
175thread_httpd:open_client_hook(ssl_client(SSL0, Client, Goal, Peer),
176 Goal, In, Out,
177 [peer(Peer), protocol(https)],
178 Options) :-
179 ( http:ssl_server_open_client_hook(SSL0, SSL, Options)
180 -> true
181 ; SSL = SSL0
182 ),
183 option(timeout(TMO), Options, 60),
184 tcp_open_socket(Client, Read, Write),
185 set_stream(Read, timeout(TMO)),
186 set_stream(Write, timeout(TMO)),
187 catch(ssl_negotiate(SSL, Read, Write, In, Out),
188 E,
189 ssl_failed(Read, Write, E)).
190
191ssl_failed(Read, Write, E) :-
192 close(Write, [force(true)]),
193 close(Read, [force(true)]),
194 throw(E).
195
196
197
208http:http_protocol_hook(https, Parts, PlainStreamPair, StreamPair, Options) :-
209 ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options).
210http:http_protocol_hook(wss, Parts, PlainStreamPair, StreamPair, Options) :-
211 ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options).
212
213ssl_protocol_hook(Parts, PlainStreamPair, StreamPair, Options) :-
214 memberchk(host(Host), Parts),
215 ssl_context(client, SSL, [ host(Host),
216 close_parent(true)
217 | Options
218 ]),
219 stream_pair(PlainStreamPair, PlainIn, PlainOut),
220 221 ssl_negotiate(SSL, PlainIn, PlainOut, In, Out),
222 stream_pair(StreamPair, In, Out).
230http:open_options(Parts, Options) :-
231 memberchk(scheme(S), Parts),
232 ssl_scheme(S),
233 Options = [cacert_file(system(root_certificates))].
234
235ssl_scheme(https).
236ssl_scheme(wss).
245http:http_connection_over_proxy(proxy(ProxyHost, ProxyPort), Parts,
246 Host:Port, StreamPair, Options, Options) :-
247 memberchk(scheme(https), Parts),
248 !,
249 tcp_connect(ProxyHost:ProxyPort, StreamPair, [bypass_proxy(true)]),
250 catch(negotiate_http_connect(StreamPair, Host:Port),
251 Error,
252 ( close(StreamPair, [force(true)]),
253 throw(Error)
254 )).
255
256negotiate_http_connect(StreamPair, Address):-
257 format(StreamPair, 'CONNECT ~w HTTP/1.1\r\n\r\n', [Address]),
258 flush_output(StreamPair),
259 http_read_reply_header(StreamPair, Header),
260 memberchk(status(_, Status, Message), Header),
261 ( Status == ok
262 -> true
263 ; throw(error(proxy_rejection(Message), _))
264 )
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. */