Introduce 'certfiles' global option

The option is supposed to replace existing options 'c2s_certfile',
's2s_certfile' and 'domain_certfile'. The option accepts a list
of file paths (optionally with wildcards "*") containing either
PEM certificates or PEM private keys. At startup, ejabberd sorts
the certificates, finds matching private keys and rebuilds full
certificates chains which can be used by fast_tls. Example:

certfiles:
  - "/etc/letsencrypt/live/example.org/*.pem"
  - "/etc/letsencrypt/live/example.com/*.pem"
This commit is contained in:
Evgeniy Khramtsov 2017-11-01 00:20:27 +03:00
parent efc4996625
commit 35b7203e01
6 changed files with 317 additions and 135 deletions

View File

@ -108,7 +108,6 @@ hosts:
## Define common macros used by listeners ## Define common macros used by listeners
## define_macro: ## define_macro:
## 'CERTFILE': "/path/to/xmpp.pem"
## 'CIPHERS': "ECDH:DH:!3DES:!aNULL:!eNULL:!MEDIUM@STRENGTH" ## 'CIPHERS': "ECDH:DH:!3DES:!aNULL:!eNULL:!MEDIUM@STRENGTH"
## 'TLSOPTS': ## 'TLSOPTS':
## - "no_sslv2" ## - "no_sslv2"
@ -130,11 +129,9 @@ listen:
module: ejabberd_c2s module: ejabberd_c2s
## ##
## If TLS is compiled in and you installed a SSL ## If TLS is compiled in and you installed a SSL
## certificate, specify the full path to the ## certificate, uncomment these lines:
## file and uncomment these lines:
## ##
## starttls: true ## starttls: true
## certfile: 'CERTFILE'
## protocol_options: 'TLSOPTS' ## protocol_options: 'TLSOPTS'
## dhfile: 'DHFILE' ## dhfile: 'DHFILE'
## ciphers: 'CIPHERS' ## ciphers: 'CIPHERS'
@ -219,7 +216,7 @@ listen:
## request_handlers: ## request_handlers:
## "": mod_http_upload ## "": mod_http_upload
## tls: true ## tls: true
## certfile: 'CERTFILE' ## certfile: "/path/to/xmpp.pem"
## protocol_options: 'TLSOPTS' ## protocol_options: 'TLSOPTS'
## dhfile: 'DHFILE' ## dhfile: 'DHFILE'
## ciphers: 'CIPHERS' ## ciphers: 'CIPHERS'
@ -228,34 +225,31 @@ listen:
## password storage (see auth_password_format option). ## password storage (see auth_password_format option).
## disable_sasl_mechanisms: "digest-md5" ## disable_sasl_mechanisms: "digest-md5"
###. ============
###' Certificates
## List all available PEM files containing certificates for your domains,
## chains of certificates or certificate keys. Full chains will be built
## automatically by ejabberd.
##
## certfiles:
## - "/etc/letsencrypt/live/example.org/*.pem"
## - "/etc/letsencrypt/live/example.com/*.pem"
###. ================== ###. ==================
###' S2S GLOBAL OPTIONS ###' S2S GLOBAL OPTIONS
## ##
## s2s_use_starttls: Enable STARTTLS for S2S connections. ## s2s_use_starttls: Enable STARTTLS for S2S connections.
## Allowed values are: false, optional or required ## Allowed values are: false, optional or required
## You must specify a certificate file. ## You must specify 'certfiles' option
## ##
## s2s_use_starttls: required ## s2s_use_starttls: required
##
## s2s_certfile: Specify a certificate file.
##
## s2s_certfile: 'CERTFILE'
## Custom OpenSSL options ## Custom OpenSSL options
## ##
## s2s_protocol_options: 'TLSOPTS' ## s2s_protocol_options: 'TLSOPTS'
##
## domain_certfile: Specify a different certificate for each served hostname.
##
## host_config:
## "example.org":
## domain_certfile: "/path/to/example_org.pem"
## "example.com":
## domain_certfile: "/path/to/example_com.pem"
## ##
## S2S whitelist or blacklist ## S2S whitelist or blacklist
## ##

View File

@ -30,6 +30,7 @@
{jiffy, ".*", {git, "https://github.com/davisp/jiffy", {tag, "0.14.8"}}}, {jiffy, ".*", {git, "https://github.com/davisp/jiffy", {tag, "0.14.8"}}},
{p1_oauth2, ".*", {git, "https://github.com/processone/p1_oauth2", {tag, "0.6.2"}}}, {p1_oauth2, ".*", {git, "https://github.com/processone/p1_oauth2", {tag, "0.6.2"}}},
{luerl, ".*", {git, "https://github.com/rvirding/luerl", {tag, "v0.2"}}}, {luerl, ".*", {git, "https://github.com/rvirding/luerl", {tag, "v0.2"}}},
{fs, ".*", {git, "https://github.com/synrc/fs.git", {tag, "2.12.0"}}},
{if_var_true, stun, {stun, ".*", {git, "https://github.com/processone/stun", {tag, "1.0.15"}}}}, {if_var_true, stun, {stun, ".*", {git, "https://github.com/processone/stun", {tag, "1.0.15"}}}},
{if_var_true, sip, {esip, ".*", {git, "https://github.com/processone/esip", {tag, "1.0.16"}}}}, {if_var_true, sip, {esip, ".*", {git, "https://github.com/processone/esip", {tag, "1.0.16"}}}},
{if_var_true, mysql, {p1_mysql, ".*", {git, "https://github.com/processone/p1_mysql", {if_var_true, mysql, {p1_mysql, ".*", {git, "https://github.com/processone/p1_mysql",

View File

@ -302,10 +302,7 @@ tls_options(#{lserver := LServer, tls_options := DefaultOpts,
TLSOpts1 = case {Encrypted, proplists:get_value(certfile, DefaultOpts)} of TLSOpts1 = case {Encrypted, proplists:get_value(certfile, DefaultOpts)} of
{true, CertFile} when CertFile /= undefined -> DefaultOpts; {true, CertFile} when CertFile /= undefined -> DefaultOpts;
{_, _} -> {_, _} ->
case ejabberd_config:get_option( case get_certfile(LServer) of
{domain_certfile, LServer},
ejabberd_config:get_option(
{c2s_certfile, LServer})) of
undefined -> DefaultOpts; undefined -> DefaultOpts;
CertFile -> lists:keystore(certfile, 1, DefaultOpts, CertFile -> lists:keystore(certfile, 1, DefaultOpts,
{certfile, CertFile}) {certfile, CertFile})
@ -928,6 +925,17 @@ format_reason(_, {shutdown, _}) ->
format_reason(_, _) -> format_reason(_, _) ->
<<"internal server error">>. <<"internal server error">>.
-spec get_certfile(binary()) -> file:filename_all().
get_certfile(LServer) ->
case ejabberd_pkix:get_certfile(LServer) of
{ok, CertFile} ->
CertFile;
error ->
ejabberd_config:get_option(
{domain_certfile, LServer},
ejabberd_config:get_option({c2s_certfile, LServer}))
end.
transform_listen_option(Opt, Opts) -> transform_listen_option(Opt, Opts) ->
[Opt|Opts]. [Opt|Opts].
@ -941,7 +949,11 @@ transform_listen_option(Opt, Opts) ->
(resource_conflict) -> fun((resource_conflict()) -> resource_conflict()); (resource_conflict) -> fun((resource_conflict()) -> resource_conflict());
(disable_sasl_mechanisms) -> fun((binary() | [binary()]) -> [binary()]); (disable_sasl_mechanisms) -> fun((binary() | [binary()]) -> [binary()]);
(atom()) -> [atom()]. (atom()) -> [atom()].
opt_type(c2s_certfile) -> fun misc:try_read_file/1; opt_type(c2s_certfile = Opt) ->
fun(File) ->
?WARNING_MSG("option '~s' is deprecated, use 'certfiles' instead", [Opt]),
misc:try_read_file(File)
end;
opt_type(c2s_ciphers) -> fun iolist_to_binary/1; opt_type(c2s_ciphers) -> fun iolist_to_binary/1;
opt_type(c2s_dhfile) -> fun misc:try_read_file/1; opt_type(c2s_dhfile) -> fun misc:try_read_file/1;
opt_type(c2s_cafile) -> fun misc:try_read_file/1; opt_type(c2s_cafile) -> fun misc:try_read_file/1;

View File

@ -1417,8 +1417,11 @@ opt_type(cache_life_time) ->
(infinity) -> infinity; (infinity) -> infinity;
(unlimited) -> infinity (unlimited) -> infinity
end; end;
opt_type(domain_certfile) -> opt_type(domain_certfile = Opt) ->
fun misc:try_read_file/1; fun(File) ->
?WARNING_MSG("option '~s' is deprecated, use 'certfiles' instead", [Opt]),
misc:try_read_file(File)
end;
opt_type(shared_key) -> opt_type(shared_key) ->
fun iolist_to_binary/1; fun iolist_to_binary/1;
opt_type(node_start) -> opt_type(node_start) ->

View File

@ -27,7 +27,8 @@
%% API %% API
-export([start_link/0, add_certfile/1, format_error/1, opt_type/1, -export([start_link/0, add_certfile/1, format_error/1, opt_type/1,
get_certfile/1, try_certfile/1, route_registered/1]). get_certfile/1, try_certfile/1, route_registered/1,
config_reloaded/0]).
%% gen_server callbacks %% gen_server callbacks
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
terminate/2, code_change/3]). terminate/2, code_change/3]).
@ -37,9 +38,11 @@
-include("jid.hrl"). -include("jid.hrl").
-record(state, {validate = true :: boolean(), -record(state, {validate = true :: boolean(),
certs = #{}}). paths = [] :: [file:filename()],
-record(cert_state, {domains = [] :: [binary()]}). certs = #{} :: map(),
keys = [] :: [public_key:private_key()]}).
-type state() :: #state{}.
-type cert() :: #'OTPCertificate'{}. -type cert() :: #'OTPCertificate'{}.
-type priv_key() :: public_key:private_key(). -type priv_key() :: public_key:private_key().
-type pub_key() :: #'RSAPublicKey'{} | {integer(), #'Dss-Parms'{}} | #'ECPoint'{}. -type pub_key() :: #'RSAPublicKey'{} | {integer(), #'Dss-Parms'{}} | #'ECPoint'{}.
@ -62,8 +65,8 @@ add_certfile(Path) ->
-spec try_certfile(filename:filename()) -> binary(). -spec try_certfile(filename:filename()) -> binary().
try_certfile(Path0) -> try_certfile(Path0) ->
Path = prep_path(Path0), Path = prep_path(Path0),
case mk_cert_state(Path, false) of case load_certfile(Path) of
{ok, _} -> Path; {ok, _, _} -> Path;
{error, _} -> erlang:error(badarg) {error, _} -> erlang:error(badarg)
end. end.
@ -78,14 +81,14 @@ format_error(not_pem) ->
format_error(not_der) -> format_error(not_der) ->
"failed to decode from DER format"; "failed to decode from DER format";
format_error(encrypted) -> format_error(encrypted) ->
"encrypted certificate found in the chain"; "encrypted certificate";
format_error({bad_cert, cert_expired}) -> format_error({bad_cert, cert_expired}) ->
"certificate is no longer valid as its expiration date has passed"; "certificate is no longer valid as its expiration date has passed";
format_error({bad_cert, invalid_issuer}) -> format_error({bad_cert, invalid_issuer}) ->
"certificate issuer name does not match the name of the " "certificate issuer name does not match the name of the "
"issuer certificate in the chain"; "issuer certificate";
format_error({bad_cert, invalid_signature}) -> format_error({bad_cert, invalid_signature}) ->
"certificate was not signed by its issuer certificate in the chain"; "certificate was not signed by its issuer certificate";
format_error({bad_cert, name_not_permitted}) -> format_error({bad_cert, name_not_permitted}) ->
"invalid Subject Alternative Name extension"; "invalid Subject Alternative Name extension";
format_error({bad_cert, missing_basic_constraint}) -> format_error({bad_cert, missing_basic_constraint}) ->
@ -95,7 +98,7 @@ format_error({bad_cert, invalid_key_usage}) ->
"certificate key is used in an invalid way according " "certificate key is used in an invalid way according "
"to the key-usage extension"; "to the key-usage extension";
format_error({bad_cert, selfsigned_peer}) -> format_error({bad_cert, selfsigned_peer}) ->
"self-signed certificate in the chain"; "self-signed certificate";
format_error({bad_cert, unknown_sig_algo}) -> format_error({bad_cert, unknown_sig_algo}) ->
"certificate is signed using unknown algorithm"; "certificate is signed using unknown algorithm";
format_error({bad_cert, unknown_ca}) -> format_error({bad_cert, unknown_ca}) ->
@ -139,18 +142,29 @@ get_certfile(Domain) ->
start_link() -> start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [], []). gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
config_reloaded() ->
gen_server:cast(?MODULE, config_reloaded).
opt_type(ca_path) -> opt_type(ca_path) ->
fun(Path) -> iolist_to_binary(Path) end; fun(Path) -> iolist_to_binary(Path) end;
opt_type(certfiles) ->
fun(CertList) ->
[binary_to_list(Path) || Path <- CertList]
end;
opt_type(_) -> opt_type(_) ->
[ca_path]. [ca_path, certfiles].
%%%=================================================================== %%%===================================================================
%%% gen_server callbacks %%% gen_server callbacks
%%%=================================================================== %%%===================================================================
init([]) -> init([]) ->
application:load(fs),
application:set_env(fs, backwards_compatible, false),
ejabberd:start_app(fs),
process_flag(trap_exit, true), process_flag(trap_exit, true),
ets:new(?MODULE, [named_table, public, bag]), ets:new(?MODULE, [named_table, public, bag]),
ejabberd_hooks:add(route_registered, ?MODULE, route_registered, 50), ejabberd_hooks:add(route_registered, ?MODULE, route_registered, 50),
ejabberd_hooks:add(config_reloaded, ?MODULE, config_reloaded, 30),
Validate = case os:type() of Validate = case os:type() of
{win32, _} -> false; {win32, _} -> false;
_ -> _ ->
@ -162,34 +176,74 @@ init([]) ->
true -> ok true -> ok
end, end,
State = #state{validate = Validate}, State = #state{validate = Validate},
{ok, add_certfiles(State)}. case filelib:ensure_dir(filename:join(certs_dir(), "foo")) of
ok ->
clean_dir(certs_dir()),
case add_certfiles(State) of
{ok, State1} ->
{ok, State1};
{error, Why} ->
{stop, Why}
end;
{error, Why} ->
?CRITICAL_MSG("Failed to create directory ~s: ~s",
[certs_dir(), file:format_error(Why)]),
{stop, Why}
end.
handle_call({add_certfile, Path}, _, State) -> handle_call({add_certfile, Path}, _, State) ->
{Result, NewState} = add_certfile(Path, State), {Result, NewState} = add_certfile(Path, State),
{reply, Result, NewState}; {reply, Result, NewState};
handle_call({route_registered, Host}, _, State) -> handle_call({route_registered, Host}, _, State) ->
NewState = add_certfiles(Host, State), case add_certfiles(Host, State) of
case get_certfile(Host) of {ok, NewState} ->
{ok, _} -> ok; case get_certfile(Host) of
error -> {ok, _} -> ok;
?WARNING_MSG("No certificate found matching '~s': strictly " error ->
"configured clients or servers will reject " ?WARNING_MSG("No certificate found matching '~s': strictly "
"connections with this host", [Host]) "configured clients or servers will reject "
end, "connections with this host", [Host])
{reply, ok, NewState}; end,
{reply, ok, NewState};
{error, _} ->
{reply, ok, State}
end;
handle_call(_Request, _From, State) -> handle_call(_Request, _From, State) ->
Reply = ok, Reply = ok,
{reply, Reply, State}. {reply, Reply, State}.
handle_cast(config_reloaded, State) ->
State1 = State#state{paths = [], certs = #{}, keys = []},
case add_certfiles(State1) of
{ok, State2} ->
{noreply, State2};
{error, _} ->
{noreply, State}
end;
handle_cast(_Msg, State) -> handle_cast(_Msg, State) ->
{noreply, State}. {noreply, State}.
handle_info({_, {fs, file_event}, {File, Events}}, State) ->
?DEBUG("got FS events for ~s: ~p", [File, Events]),
Path = iolist_to_binary(File),
case lists:member(modified, Events) of
true ->
case lists:member(Path, State#state.paths) of
true ->
handle_cast(config_reloaded, State);
false ->
{noreply, State}
end;
false ->
{noreply, State}
end;
handle_info(_Info, State) -> handle_info(_Info, State) ->
?WARNING_MSG("unexpected info: ~p", [_Info]), ?WARNING_MSG("unexpected info: ~p", [_Info]),
{noreply, State}. {noreply, State}.
terminate(_Reason, _State) -> terminate(_Reason, _State) ->
ejabberd_hooks:delete(route_registered, ?MODULE, route_registered, 50). ejabberd_hooks:delete(route_registered, ?MODULE, route_registered, 50),
ejabberd_hooks:delete(config_reloaded, ?MODULE, config_reloaded, 30).
code_change(_OldVsn, State, _Extra) -> code_change(_OldVsn, State, _Extra) ->
{ok, State}. {ok, State}.
@ -197,73 +251,150 @@ code_change(_OldVsn, State, _Extra) ->
%%%=================================================================== %%%===================================================================
%%% Internal functions %%% Internal functions
%%%=================================================================== %%%===================================================================
-spec certfiles_from_config_options() -> [atom()].
certfiles_from_config_options() ->
[c2s_certfile, s2s_certfile, domain_certfile].
-spec get_certfiles_from_config_options(state()) -> [binary()].
get_certfiles_from_config_options(State) ->
Global = case ejabberd_config:get_option(certfiles) of
undefined ->
[];
Paths ->
lists:flatmap(fun filelib:wildcard/1, Paths)
end,
Local = lists:flatmap(
fun(OptHost) ->
case ejabberd_config:get_option(OptHost) of
undefined -> [];
Path -> [Path]
end
end, [{Opt, Host}
|| Opt <- certfiles_from_config_options(),
Host <- ejabberd_config:get_myhosts()]),
[iolist_to_binary(P) || P <- lists:usort(Local ++ Global)].
-spec add_certfiles(state()) -> {ok, state()} | {error, bad_cert()}.
add_certfiles(State) -> add_certfiles(State) ->
lists:foldl( Paths = get_certfiles_from_config_options(State),
fun(Host, AccState) -> State1 = lists:foldl(
add_certfiles(Host, AccState) fun(Path, Acc) ->
end, State, ejabberd_config:get_myhosts()). {_, NewAcc} = add_certfile(Path, Acc),
NewAcc
end, State, Paths),
case build_chain_and_check(State1) of
ok -> {ok, State1};
{error, _} = Err -> Err
end.
-spec add_certfiles(binary(), state()) -> {ok, state()} | {error, bad_cert()}.
add_certfiles(Host, State) -> add_certfiles(Host, State) ->
lists:foldl( State1 = lists:foldl(
fun(Opt, AccState) -> fun(Opt, AccState) ->
case ejabberd_config:get_option({Opt, Host}) of case ejabberd_config:get_option({Opt, Host}) of
undefined -> AccState; undefined -> AccState;
Path -> Path ->
{_, NewAccState} = add_certfile(Path, AccState), {_, NewAccState} = add_certfile(Path, AccState),
NewAccState NewAccState
end end
end, State, [c2s_certfile, s2s_certfile, domain_certfile]). end, State, certfiles_from_config_options()),
if State /= State1 ->
case build_chain_and_check(State1) of
ok -> {ok, State1};
{error, _} = Err -> Err
end;
true ->
{ok, State}
end.
-spec add_certfile(file:filename_all(), state()) -> {ok, state()} |
{{error, cert_error()}, state()}.
add_certfile(Path, State) -> add_certfile(Path, State) ->
case maps:get(Path, State#state.certs, undefined) of case lists:member(Path, State#state.paths) of
#cert_state{} -> true ->
{ok, State}; {ok, State};
undefined -> false ->
case mk_cert_state(Path, State#state.validate) of case load_certfile(Path) of
{error, Reason} -> {ok, Certs, Keys} ->
{{error, Reason}, State}; NewCerts = lists:foldl(
{ok, CertState} -> fun(Cert, Acc) ->
NewCerts = maps:put(Path, CertState, State#state.certs), maps:put(Cert, Path, Acc)
lists:foreach( end, State#state.certs, Certs),
fun(Domain) -> {ok, State#state{paths = [Path|State#state.paths],
ets:insert(?MODULE, {Domain, Path}) certs = NewCerts,
end, CertState#cert_state.domains), keys = Keys ++ State#state.keys}};
{ok, State#state{certs = NewCerts}} {error, Why} = Err ->
?ERROR_MSG("failed to read certificate from ~s: ~s",
[Path, format_error(Why)]),
{Err, State}
end end
end. end.
mk_cert_state(Path, Validate) -> -spec build_chain_and_check(state()) -> ok | {error, bad_cert()}.
case check_certfile(Path, Validate) of build_chain_and_check(State) ->
{ok, Ds} -> ?DEBUG("Rebuilding certificate chains from ~s",
{ok, #cert_state{domains = Ds}}; [str:join(State#state.paths, <<", ">>)]),
{invalid, Ds, {bad_cert, _} = Why} -> CertPaths = get_cert_paths(maps:keys(State#state.certs)),
?WARNING_MSG("certificate from ~s is invalid: ~s", case match_cert_keys(CertPaths, State#state.keys) of
[Path, format_error(Why)]), {ok, Chains} ->
{ok, #cert_state{domains = Ds}}; CertFilesWithDomains = store_certs(Chains, []),
{error, Why} = Err -> ets:delete_all_objects(?MODULE),
?ERROR_MSG("failed to read certificate from ~s: ~s", lists:foreach(
fun({Path, Domain}) ->
ets:insert(?MODULE, {Domain, Path})
end, CertFilesWithDomains),
Errors = validate(CertPaths, State#state.validate),
subscribe(State),
lists:foreach(
fun({Cert, Why}) ->
Path = maps:get(Cert, State#state.certs),
?ERROR_MSG("Failed to validate certificate from ~s: ~s",
[Path, format_error(Why)])
end, Errors);
{error, Cert, Why} ->
Path = maps:get(Cert, State#state.certs),
?ERROR_MSG("Failed to build certificate chain for ~s: ~s",
[Path, format_error(Why)]), [Path, format_error(Why)]),
Err {error, Why}
end. end.
-spec check_certfile(filename:filename(), boolean()) -spec store_certs([{[cert()], priv_key()}],
-> {ok, [binary()]} | {invalid, [binary()], bad_cert()} | [{binary(), binary()}]) -> [{binary(), binary()}].
{error, cert_error() | file:posix()}. store_certs([{Certs, Key}|Chains], Acc) ->
check_certfile(Path, Validate) -> CertPEMs = public_key:pem_encode(
lists:map(
fun(Cert) ->
Type = element(1, Cert),
DER = public_key:pkix_encode(Type, Cert, otp),
{'Certificate', DER, not_encrypted}
end, Certs)),
KeyPEM = public_key:pem_encode(
[{element(1, Key),
public_key:der_encode(element(1, Key), Key),
not_encrypted}]),
PEMs = <<CertPEMs/binary, KeyPEM/binary>>,
Cert = hd(Certs),
Domains = xmpp_stream_pkix:get_cert_domains(Cert),
FileName = filename:join(certs_dir(), str:sha(PEMs)),
case file:write_file(FileName, PEMs) of
ok ->
file:change_mode(FileName, 8#600),
NewAcc = [{FileName, Domain} || Domain <- Domains] ++ Acc,
store_certs(Chains, NewAcc);
{error, Why} ->
?ERROR_MSG("Failed to write to ~s: ~s",
[FileName, file:format_error(Why)]),
store_certs(Chains, [])
end;
store_certs([], Acc) ->
Acc.
-spec load_certfile(file:filename_all()) -> {ok, [cert()], [priv_key()]} |
{error, cert_error() | file:posix()}.
load_certfile(Path) ->
try try
{ok, Data} = file:read_file(Path), {ok, Data} = file:read_file(Path),
{ok, Certs, PrivKeys} = pem_decode(Data), pem_decode(Data)
CertPaths = get_cert_paths(Certs),
Domains = get_domains(CertPaths),
case match_cert_keys(CertPaths, PrivKeys) of
{ok, _} ->
case validate(CertPaths, Validate) of
ok -> {ok, Domains};
{error, Why} -> {invalid, Domains, Why}
end;
{error, Why} ->
{invalid, Domains, Why}
end
catch _:{badmatch, {error, _} = Err} -> catch _:{badmatch, {error, _} = Err} ->
Err Err
end. end.
@ -281,7 +412,7 @@ pem_decode(Data) ->
fun(#'OTPCertificate'{}) -> true; fun(#'OTPCertificate'{}) -> true;
(_) -> false (_) -> false
end, Objects) of end, Objects) of
{[], _} -> {[], []} ->
{error, not_cert}; {error, not_cert};
{Certs, PrivKeys} -> {Certs, PrivKeys} ->
{ok, Certs, PrivKeys} {ok, Certs, PrivKeys}
@ -331,41 +462,44 @@ decode_certs(PemEntries) ->
{error, not_der} {error, not_der}
end. end.
-spec validate([{path, [cert()]}], boolean()) -> ok | {error, bad_cert()}. -spec validate([{path, [cert()]}], boolean()) -> [{cert(), bad_cert()}].
validate([{path, Path}|Paths], true) -> validate(Paths, true) ->
case validate_path(Path) of lists:flatmap(
ok -> fun({path, Path}) ->
validate(Paths, true); case validate_path(Path) of
Err -> ok ->
Err [];
end; {error, Cert, Reason} ->
[{Cert, Reason}]
end
end, Paths);
validate(_, _) -> validate(_, _) ->
ok. ok.
-spec validate_path([cert()]) -> ok | {error, bad_cert()}. -spec validate_path([cert()]) -> ok | {error, cert(), bad_cert()}.
validate_path([Cert|_] = Certs) -> validate_path([Cert|_] = Certs) ->
case find_local_issuer(Cert) of case find_local_issuer(Cert) of
{ok, IssuerCert} -> {ok, IssuerCert} ->
try public_key:pkix_path_validation(IssuerCert, Certs, []) of try public_key:pkix_path_validation(IssuerCert, Certs, []) of
{ok, _} -> {ok, _} ->
ok; ok;
Err -> {error, Reason} ->
Err {error, Cert, Reason}
catch error:function_clause -> catch error:function_clause ->
case erlang:get_stacktrace() of case erlang:get_stacktrace() of
[{public_key, pkix_sign_types, _, _}|_] -> [{public_key, pkix_sign_types, _, _}|_] ->
{error, {bad_cert, unknown_sig_algo}}; {error, Cert, {bad_cert, unknown_sig_algo}};
ST -> ST ->
%% Bug in public_key application %% Bug in public_key application
erlang:raise(error, function_clause, ST) erlang:raise(error, function_clause, ST)
end end
end; end;
{error, _} = Err -> {error, Reason} ->
case public_key:pkix_is_self_signed(Cert) of case public_key:pkix_is_self_signed(Cert) of
true -> true ->
{error, {bad_cert, selfsigned_peer}}; {error, Cert, {bad_cert, selfsigned_peer}};
false -> false ->
Err {error, Cert, Reason}
end end
end. end.
@ -373,6 +507,25 @@ validate_path([Cert|_] = Certs) ->
ca_dir() -> ca_dir() ->
ejabberd_config:get_option(ca_path, "/etc/ssl/certs"). ejabberd_config:get_option(ca_path, "/etc/ssl/certs").
-spec certs_dir() -> string().
certs_dir() ->
MnesiaDir = mnesia:system_info(directory),
filename:join(MnesiaDir, "certs").
-spec clean_dir(file:filename_all()) -> ok.
clean_dir(Dir) ->
?DEBUG("Cleaning directory ~s", [Dir]),
Files = filelib:wildcard(filename:join(Dir, "*")),
lists:foreach(
fun(Path) ->
case filelib:is_file(Path) of
true ->
file:delete(Path);
false ->
ok
end
end, Files).
-spec check_ca_dir() -> ok. -spec check_ca_dir() -> ok.
check_ca_dir() -> check_ca_dir() ->
case filelib:wildcard(filename:join(ca_dir(), "*.0")) of case filelib:wildcard(filename:join(ca_dir(), "*.0")) of
@ -424,13 +577,13 @@ match_cert_keys(CertPaths, PrivKeys) ->
-spec match_cert_keys([{path, [cert()]}], [{pub_key(), priv_key()}], -spec match_cert_keys([{path, [cert()]}], [{pub_key(), priv_key()}],
[{cert(), priv_key()}]) [{cert(), priv_key()}])
-> {ok, [{cert(), priv_key()}]} | {error, {bad_cert, missing_priv_key}}. -> {ok, [{[cert()], priv_key()}]} | {error, cert(), {bad_cert, missing_priv_key}}.
match_cert_keys([{path, Certs}|CertPaths], KeyPairs, Result) -> match_cert_keys([{path, Certs}|CertPaths], KeyPairs, Result) ->
[Cert|_] = RevCerts = lists:reverse(Certs), [Cert|_] = RevCerts = lists:reverse(Certs),
PubKey = pubkey_from_cert(Cert), PubKey = pubkey_from_cert(Cert),
case lists:keyfind(PubKey, 1, KeyPairs) of case lists:keyfind(PubKey, 1, KeyPairs) of
false -> false ->
{error, {bad_cert, missing_priv_key}}; {error, Cert, {bad_cert, missing_priv_key}};
{_, PrivKey} -> {_, PrivKey} ->
match_cert_keys(CertPaths, KeyPairs, [{RevCerts, PrivKey}|Result]) match_cert_keys(CertPaths, KeyPairs, [{RevCerts, PrivKey}|Result])
end; end;
@ -465,15 +618,6 @@ pubkey_from_privkey(#'DSAPrivateKey'{p = P, q = Q, g = G, y = Y}) ->
pubkey_from_privkey(#'ECPrivateKey'{publicKey = Key}) -> pubkey_from_privkey(#'ECPrivateKey'{publicKey = Key}) ->
#'ECPoint'{point = Key}. #'ECPoint'{point = Key}.
-spec get_domains([{path, [cert()]}]) -> [binary()].
get_domains(CertPaths) ->
lists:usort(
lists:flatmap(
fun({path, Certs}) ->
Cert = lists:last(Certs),
xmpp_stream_pkix:get_cert_domains(Cert)
end, CertPaths)).
-spec get_cert_paths([cert()]) -> [{path, [cert()]}]. -spec get_cert_paths([cert()]) -> [{path, [cert()]}].
get_cert_paths(Certs) -> get_cert_paths(Certs) ->
G = digraph:new([acyclic]), G = digraph:new([acyclic]),
@ -533,3 +677,18 @@ short_name_hash(IssuerID) ->
short_name_hash(_) -> short_name_hash(_) ->
"". "".
-endif. -endif.
-spec subscribe(state()) -> ok.
subscribe(State) ->
lists:foreach(
fun(Path) ->
Dir = filename:dirname(Path),
Name = list_to_atom(integer_to_list(erlang:phash2(Dir))),
case fs:start_link(Name, Dir) of
{ok, _} ->
?DEBUG("Subscribed to FS events from ~s", [Dir]),
fs:subscribe(Name);
{error, _} ->
ok
end
end, State#state.paths).

View File

@ -198,13 +198,11 @@ dirty_get_connections() ->
-spec tls_options(binary(), [proplists:property()]) -> [proplists:property()]. -spec tls_options(binary(), [proplists:property()]) -> [proplists:property()].
tls_options(LServer, DefaultOpts) -> tls_options(LServer, DefaultOpts) ->
TLSOpts1 = case ejabberd_config:get_option( TLSOpts1 = case get_certfile(LServer) of
{domain_certfile, LServer},
ejabberd_config:get_option(
{s2s_certfile, LServer})) of
undefined -> DefaultOpts; undefined -> DefaultOpts;
CertFile -> lists:keystore(certfile, 1, DefaultOpts, CertFile ->
{certfile, CertFile}) lists:keystore(certfile, 1, DefaultOpts,
{certfile, CertFile})
end, end,
TLSOpts2 = case ejabberd_config:get_option( TLSOpts2 = case ejabberd_config:get_option(
{s2s_ciphers, LServer}) of {s2s_ciphers, LServer}) of
@ -269,6 +267,17 @@ queue_type(LServer) ->
{s2s_queue_type, LServer}, {s2s_queue_type, LServer},
ejabberd_config:default_queue_type(LServer)). ejabberd_config:default_queue_type(LServer)).
-spec get_certfile(binary()) -> file:filename_all().
get_certfile(LServer) ->
case ejabberd_pkix:get_certfile(LServer) of
{ok, CertFile} ->
CertFile;
error ->
ejabberd_config:get_option(
{domain_certfile, LServer},
ejabberd_config:get_option({s2s_certfile, LServer}))
end.
%%==================================================================== %%====================================================================
%% gen_server callbacks %% gen_server callbacks
%%==================================================================== %%====================================================================
@ -711,7 +720,11 @@ opt_type(route_subdomains) ->
end; end;
opt_type(s2s_access) -> opt_type(s2s_access) ->
fun acl:access_rules_validator/1; fun acl:access_rules_validator/1;
opt_type(s2s_certfile) -> fun misc:try_read_file/1; opt_type(s2s_certfile = Opt) ->
fun(File) ->
?WARNING_MSG("option '~s' is deprecated, use 'certfiles' instead", [Opt]),
misc:try_read_file(File)
end;
opt_type(s2s_ciphers) -> fun iolist_to_binary/1; opt_type(s2s_ciphers) -> fun iolist_to_binary/1;
opt_type(s2s_dhfile) -> fun misc:try_read_file/1; opt_type(s2s_dhfile) -> fun misc:try_read_file/1;
opt_type(s2s_cafile) -> fun misc:try_read_file/1; opt_type(s2s_cafile) -> fun misc:try_read_file/1;