diff options
Diffstat (limited to 'src/ejabberd_config.erl')
-rw-r--r-- | src/ejabberd_config.erl | 1967 |
1 files changed, 678 insertions, 1289 deletions
diff --git a/src/ejabberd_config.erl b/src/ejabberd_config.erl index 87a918704..4463e4caa 100644 --- a/src/ejabberd_config.erl +++ b/src/ejabberd_config.erl @@ -5,7 +5,7 @@ %%% Created : 14 Dec 2002 by Alexey Shchepin <alexey@process-one.net> %%% %%% -%%% ejabberd, Copyright (C) 2002-2016 ProcessOne +%%% ejabberd, Copyright (C) 2002-2019 ProcessOne %%% %%% This program is free software; you can redistribute it and/or %%% modify it under the terms of the GNU General Public License as @@ -22,1356 +22,745 @@ %%% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA. %%% %%%---------------------------------------------------------------------- - -module(ejabberd_config). --author('alexey@process-one.net'). - --export([start/0, load_file/1, reload_file/0, read_file/1, - add_global_option/2, add_local_option/2, - get_global_option/2, get_local_option/2, - get_global_option/3, get_local_option/3, - get_option/2, get_option/3, add_option/2, has_option/1, - get_vh_by_auth_method/1, is_file_readable/1, - get_version/0, get_myhosts/0, get_mylang/0, - prepare_opt_val/4, convert_table_to_binary/5, - transform_options/1, collect_options/1, default_db/2, - convert_to_yaml/1, convert_to_yaml/2, v_db/2, - env_binary_to_list/2, opt_type/1, may_hide_data/1]). - --export([start/2]). - --include("ejabberd.hrl"). --include("logger.hrl"). --include("ejabberd_config.hrl"). --include_lib("kernel/include/file.hrl"). - --callback opt_type(atom()) -> function() | [atom()]. - -%% @type macro() = {macro_key(), macro_value()} - -%% @type macro_key() = atom(). -%% The atom must have all characters in uppercase. - -%% @type macro_value() = term(). - -start() -> - mnesia_init(), - Config = get_ejabberd_config_path(), - State0 = read_file(Config), - State1 = hosts_to_start(State0), - State2 = validate_opts(State1), - %% This start time is used by mod_last: - UnixTime = p1_time_compat:system_time(seconds), - SharedKey = case erlang:get_cookie() of - nocookie -> - p1_sha:sha(randoms:get_string()); - Cookie -> - p1_sha:sha(jlib:atom_to_binary(Cookie)) - end, - State3 = set_option({node_start, global}, UnixTime, State2), - State4 = set_option({shared_key, global}, SharedKey, State3), - set_opts(State4). - -%% When starting ejabberd for testing, we sometimes want to start a -%% subset of hosts from the one define in the config file. -%% This function override the host list read from config file by the -%% one we provide. -%% Hosts to start are defined in an ejabberd application environment -%% variable 'hosts' to make it easy to ignore some host in config -%% file. -hosts_to_start(State) -> - case application:get_env(ejabberd, hosts) of - undefined -> - %% Start all hosts as defined in config file - State; - {ok, Hosts} -> - set_hosts_in_options(Hosts, State) - end. -%% @private -%% At the moment, these functions are mainly used to setup unit tests. --spec start(Hosts :: [binary()], Opts :: [acl:acl() | local_config()]) -> ok. -start(Hosts, Opts) -> - mnesia_init(), - set_opts(set_hosts_in_options(Hosts, #state{opts = Opts})). - -mnesia_init() -> - case catch mnesia:table_info(local_config, storage_type) of - disc_copies -> - mnesia:delete_table(local_config); - _ -> - ok - end, - mnesia:create_table(local_config, - [{ram_copies, [node()]}, - {local_content, true}, - {attributes, record_info(fields, local_config)}]), - mnesia:add_table_copy(local_config, node(), ram_copies). - -%% @doc Get the filename of the ejabberd configuration file. -%% The filename can be specified with: erl -config "/path/to/ejabberd.yml". -%% It can also be specified with the environtment variable EJABBERD_CONFIG_PATH. -%% If not specified, the default value 'ejabberd.yml' is assumed. -%% @spec () -> string() -get_ejabberd_config_path() -> - case get_env_config() of - {ok, Path} -> Path; - undefined -> - case os:getenv("EJABBERD_CONFIG_PATH") of - false -> - ?CONFIG_PATH; - Path -> - Path - end - end. +%% API +-export([get_option/1]). +-export([load/0, reload/0, format_error/1, path/0]). +-export([env_binary_to_list/2]). +-export([get_myname/0, get_uri/0, get_copyright/0]). +-export([get_shared_key/0, get_node_start/0]). +-export([fsm_limit_opts/1]). +-export([codec_options/0]). +-export([version/0]). +-export([default_db/2, default_db/3, default_ram_db/2, default_ram_db/3]). +-export([beams/1, validators/1, globals/0, may_hide_data/1]). +-export([dump/0, dump/1, convert_to_yaml/1, convert_to_yaml/2]). + +%% Deprecated functions +-export([get_option/2, set_option/2]). +-export([get_version/0, get_myhosts/0]). +-export([get_mylang/0, get_lang/1]). +-deprecated([{get_option, 2}, + {set_option, 2}, + {get_version, 0}, + {get_myhosts, 0}, + {get_mylang, 0}, + {get_lang, 1}]). --spec get_env_config() -> {ok, string()} | undefined. -get_env_config() -> - %% First case: the filename can be specified with: erl -config "/path/to/ejabberd.yml". - case application:get_env(config) of - R = {ok, _Path} -> R; - undefined -> - %% Second case for embbeding ejabberd in another app, for example for Elixir: - %% config :ejabberd, - %% file: "config/ejabberd.yml" - application:get_env(ejabberd, file) +-include("logger.hrl"). +-include("ejabberd_stacktrace.hrl"). + +-type option() :: atom() | {atom(), global | binary()}. +-type error_reason() :: {merge_conflict, atom(), binary()} | + {old_config, file:filename_all(), term()} | + {write_file, file:filename_all(), term()} | + {exception, term(), term(), term()}. +-type error_return() :: {error, econf:error_reason(), term()} | + {error, error_reason()}. +-type host_config() :: #{{atom(), binary() | global} => term()}. + +-callback opt_type(atom()) -> econf:validator(). +-callback options() -> [atom() | {atom(), term()}]. +-callback globals() -> [atom()]. + +-optional_callbacks([globals/0]). + +%%%=================================================================== +%%% API +%%%=================================================================== +-spec load() -> ok | error_return(). +load() -> + load(path()). + +-spec load(file:filename_all()) -> ok | error_return(). +load(Path) -> + ConfigFile = unicode:characters_to_binary(Path), + UnixTime = erlang:monotonic_time(second), + ?INFO_MSG("Loading configuration from ~ts", [ConfigFile]), + _ = ets:new(ejabberd_options, + [named_table, public, {read_concurrency, true}]), + case load_file(ConfigFile) of + ok -> + set_shared_key(), + set_node_start(UnixTime), + ?INFO_MSG("Configuration loaded successfully", []); + Err -> + Err end. -%% @doc Read the ejabberd configuration file. -%% It also includes additional configuration files and replaces macros. -%% This function will crash if finds some error in the configuration file. -%% @spec (File::string()) -> #state{} -read_file(File) -> - read_file(File, [{replace_macros, true}, - {include_files, true}, - {include_modules_configs, true}]). - -read_file(File, Opts) -> - Terms1 = get_plain_terms_file(File, Opts), - Terms_macros = case proplists:get_bool(replace_macros, Opts) of - true -> replace_macros(Terms1); - false -> Terms1 - end, - Terms = transform_terms(Terms_macros), - State = lists:foldl(fun search_hosts/2, #state{}, Terms), - {Head, Tail} = lists:partition( - fun({host_config, _}) -> false; - ({append_host_config, _}) -> false; - (_) -> true - end, Terms), - State1 = lists:foldl(fun process_term/2, State, Head ++ Tail), - State1#state{opts = compact(State1#state.opts)}. - --spec load_file(string()) -> ok. - -load_file(File) -> - State = read_file(File), - set_opts(State). - --spec reload_file() -> ok. - -reload_file() -> - Config = get_ejabberd_config_path(), - load_file(Config). +-spec reload() -> ok | error_return(). +reload() -> + ConfigFile = path(), + ?INFO_MSG("Reloading configuration from ~ts", [ConfigFile]), + OldHosts = get_myhosts(), + case load_file(ConfigFile) of + ok -> + NewHosts = get_myhosts(), + AddHosts = NewHosts -- OldHosts, + DelHosts = OldHosts -- NewHosts, + lists:foreach( + fun(Host) -> + ejabberd_hooks:run(host_up, [Host]) + end, AddHosts), + lists:foreach( + fun(Host) -> + ejabberd_hooks:run(host_down, [Host]) + end, DelHosts), + ejabberd_hooks:run(config_reloaded, []), + delete_host_options(DelHosts), + ?INFO_MSG("Configuration reloaded successfully", []); + Err -> + ?ERROR_MSG("Configuration reload aborted: ~ts", + [format_error(Err)]), + Err + end. --spec convert_to_yaml(file:filename()) -> ok | {error, any()}. +-spec dump() -> ok | error_return(). +dump() -> + dump(stdout). -convert_to_yaml(File) -> - convert_to_yaml(File, stdout). +-spec dump(stdout | file:filename_all()) -> ok | error_return(). +dump(Output) -> + Y = get_option(yaml_config), + dump(Y, Output). --spec convert_to_yaml(file:filename(), - stdout | file:filename()) -> ok | {error, any()}. - -convert_to_yaml(File, Output) -> - State = read_file(File, [{include_files, false}]), - Opts = [{K, V} || #local_config{key = K, value = V} <- State#state.opts], - {GOpts, HOpts} = split_by_hosts(Opts), - NewOpts = GOpts ++ lists:map( - fun({Host, Opts1}) -> - {host_config, [{Host, Opts1}]} - end, HOpts), - Data = fast_yaml:encode(lists:reverse(NewOpts)), +-spec dump(term(), stdout | file:filename_all()) -> ok | error_return(). +dump(Y, Output) -> + Data = fast_yaml:encode(Y), case Output of - stdout -> - io:format("~s~n", [Data]); - FileName -> - file:write_file(FileName, Data) + stdout -> + io:format("~ts~n", [Data]); + FileName -> + try + ok = filelib:ensure_dir(FileName), + ok = file:write_file(FileName, Data) + catch _:{badmatch, {error, Reason}} -> + {error, {write_file, FileName, Reason}} + end end. -%% Some Erlang apps expects env parameters to be list and not binary. -%% For example, Mnesia is not able to start if mnesia dir is passed as a binary. -%% However, binary is most common on Elixir, so it is easy to make a setup mistake. --spec env_binary_to_list(atom(), atom()) -> {ok, any()}|undefined. -env_binary_to_list(Application, Parameter) -> - %% Application need to be loaded to allow setting parameters - application:load(Application), - case application:get_env(Application, Parameter) of - {ok, Val} when is_binary(Val) -> - BVal = binary_to_list(Val), - application:set_env(Application, Parameter, BVal), - {ok, BVal}; - Other -> - Other +-spec get_option(option(), term()) -> term(). +get_option(Opt, Default) -> + try get_option(Opt) + catch _:badarg -> Default end. -%% @doc Read an ejabberd configuration file and return the terms. -%% Input is an absolute or relative path to an ejabberd config file. -%% Returns a list of plain terms, -%% in which the options 'include_config_file' were parsed -%% and the terms in those files were included. -%% @spec(iolist()) -> [term()] -get_plain_terms_file(File, Opts) when is_binary(File) -> - get_plain_terms_file(binary_to_list(File), Opts); -get_plain_terms_file(File1, Opts) -> - File = get_absolute_path(File1), - DontStopOnError = lists:member(dont_halt_on_error, Opts), - case consult(File) of - {ok, Terms} -> - BinTerms1 = strings_to_binary(Terms), - ModInc = case proplists:get_bool(include_modules_configs, Opts) of - true -> - Files = [{filename:rootname(filename:basename(F)), F} - || F <- filelib:wildcard(ext_mod:config_dir() ++ "/*.{yml,yaml}") - ++ filelib:wildcard(ext_mod:modules_dir() ++ "/*/conf/*.{yml,yaml}")], - [proplists:get_value(F,Files) || F <- proplists:get_keys(Files)]; - _ -> - [] - end, - BinTerms = BinTerms1 ++ [{include_config_file, list_to_binary(V)} || V <- ModInc], - case proplists:get_bool(include_files, Opts) of - true -> - include_config_files(BinTerms); - false -> - BinTerms - end; - {error, enoent, Reason} -> - case DontStopOnError of - true -> - ?WARNING_MSG(Reason, []), - []; - _ -> - ?ERROR_MSG(Reason, []), - exit_or_halt(Reason) - end; - {error, Reason} -> - ?ERROR_MSG(Reason, []), - case DontStopOnError of - true -> []; - _ -> exit_or_halt(Reason) - end +-spec get_option(option()) -> term(). +get_option(Opt) when is_atom(Opt) -> + get_option({Opt, global}); +get_option({O, Host} = Opt) -> + Tab = case get_tmp_config() of + undefined -> ejabberd_options; + T -> T + end, + try ets:lookup_element(Tab, Opt, 2) + catch ?EX_RULE(error, badarg, St) when Host /= global -> + StackTrace = ?EX_STACK(St), + Val = get_option({O, global}), + ?DEBUG("Option '~ts' is not defined for virtual host '~ts'. " + "This is a bug, please report it with the following " + "stacktrace included:~n** ~ts", + [O, Host, misc:format_exception(2, error, badarg, StackTrace)]), + Val end. -consult(File) -> - case filename:extension(File) of - Ex when (Ex == ".yml") or (Ex == ".yaml") -> - case fast_yaml:decode_from_file(File, [plain_as_atom]) of - {ok, []} -> - {ok, []}; - {ok, [Document|_]} -> - {ok, parserl(Document)}; - {error, Err} -> - Msg1 = "Cannot load " ++ File ++ ": ", - Msg2 = fast_yaml:format_error(Err), - case Err of - enoent -> - {error, enoent, Msg1 ++ Msg2}; - _ -> - {error, Msg1 ++ Msg2} - end - end; - _ -> - case file:consult(File) of - {ok, Terms} -> - {ok, Terms}; - {error, enoent} -> - {error, enoent}; - {error, {LineNumber, erl_parse, _ParseMessage} = Reason} -> - {error, describe_config_problem(File, Reason, LineNumber)}; - {error, Reason} -> - case Reason of - enoent -> - {error, enoent, describe_config_problem(File, Reason)}; - _ -> - {error, describe_config_problem(File, Reason)} - end - end - end. +-spec set_option(option(), term()) -> ok. +set_option(Opt, Val) when is_atom(Opt) -> + set_option({Opt, global}, Val); +set_option(Opt, Val) -> + Tab = case get_tmp_config() of + undefined -> ejabberd_options; + T -> T + end, + ets:insert(Tab, {Opt, Val}), + ok. + +-spec get_version() -> binary(). +get_version() -> + get_option(version). -parserl(<<"> ", Term/binary>>) -> - {ok, A2, _} = erl_scan:string(binary_to_list(Term)), - {ok, A3} = erl_parse:parse_term(A2), - A3; -parserl({A, B}) -> - {parserl(A), parserl(B)}; -parserl([El|Tail]) -> - [parserl(El) | parserl(Tail)]; -parserl(Other) -> - Other. - -%% @doc Convert configuration filename to absolute path. -%% Input is an absolute or relative path to an ejabberd configuration file. -%% And returns an absolute path to the configuration file. -%% @spec (string()) -> string() -get_absolute_path(File) -> - case filename:pathtype(File) of - absolute -> - File; - relative -> - {ok, Dir} = file:get_cwd(), - filename:absname_join(Dir, File) - end. +-spec get_myhosts() -> [binary(), ...]. +get_myhosts() -> + get_option(hosts). +-spec get_myname() -> binary(). +get_myname() -> + get_option(host). -search_hosts(Term, State) -> - case Term of - {host, Host} -> - if - State#state.hosts == [] -> - set_hosts_in_options([Host], State); - true -> - ?ERROR_MSG("Can't load config file: " - "too many hosts definitions", []), - exit("too many hosts definitions") - end; - {hosts, Hosts} -> - if - State#state.hosts == [] -> - set_hosts_in_options(Hosts, State); - true -> - ?ERROR_MSG("Can't load config file: " - "too many hosts definitions", []), - exit("too many hosts definitions") - end; - _ -> - State - end. +-spec get_mylang() -> binary(). +get_mylang() -> + get_lang(global). -set_hosts_in_options(Hosts, State) -> - PrepHosts = normalize_hosts(Hosts), - NewOpts = lists:filter(fun({local_config,{hosts,global},_}) -> false; - (_) -> true - end, State#state.opts), - set_option({hosts, global}, PrepHosts, State#state{hosts = PrepHosts, opts = NewOpts}). - -normalize_hosts(Hosts) -> - normalize_hosts(Hosts,[]). -normalize_hosts([], PrepHosts) -> - lists:reverse(PrepHosts); -normalize_hosts([Host|Hosts], PrepHosts) -> - case jid:nodeprep(iolist_to_binary(Host)) of - error -> - ?ERROR_MSG("Can't load config file: " - "invalid host name [~p]", [Host]), - exit("invalid hostname"); - PrepHost -> - normalize_hosts(Hosts, [PrepHost|PrepHosts]) - end. +-spec get_lang(global | binary()) -> binary(). +get_lang(Host) -> + get_option({language, Host}). +-spec get_uri() -> binary(). +get_uri() -> + <<"http://www.process-one.net/en/ejabberd/">>. -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%%% Errors reading the config file - -describe_config_problem(Filename, Reason) -> - Text1 = lists:flatten("Problem loading ejabberd config file " ++ Filename), - Text2 = lists:flatten(" : " ++ file:format_error(Reason)), - ExitText = Text1 ++ Text2, - ExitText. - -describe_config_problem(Filename, Reason, LineNumber) -> - Text1 = lists:flatten("Problem loading ejabberd config file " ++ Filename), - Text2 = lists:flatten(" approximately in the line " - ++ file:format_error(Reason)), - ExitText = Text1 ++ Text2, - Lines = get_config_lines(Filename, LineNumber, 10, 3), - ?ERROR_MSG("The following lines from your configuration file might be" - " relevant to the error: ~n~s", [Lines]), - ExitText. - -get_config_lines(Filename, TargetNumber, PreContext, PostContext) -> - {ok, Fd} = file:open(Filename, [read]), - LNumbers = lists:seq(TargetNumber-PreContext, TargetNumber+PostContext), - NextL = io:get_line(Fd, no_prompt), - R = get_config_lines2(Fd, NextL, 1, LNumbers, []), - file:close(Fd), - R. - -get_config_lines2(_Fd, eof, _CurrLine, _LNumbers, R) -> - lists:reverse(R); -get_config_lines2(_Fd, _NewLine, _CurrLine, [], R) -> - lists:reverse(R); -get_config_lines2(Fd, Data, CurrLine, [NextWanted | LNumbers], R) when is_list(Data) -> - NextL = io:get_line(Fd, no_prompt), - if - CurrLine >= NextWanted -> - Line2 = [integer_to_list(CurrLine), ": " | Data], - get_config_lines2(Fd, NextL, CurrLine+1, LNumbers, [Line2 | R]); - true -> - get_config_lines2(Fd, NextL, CurrLine+1, [NextWanted | LNumbers], R) - end. +-spec get_copyright() -> binary(). +get_copyright() -> + <<"Copyright (c) ProcessOne">>. -%% If ejabberd isn't yet running in this node, then halt the node -exit_or_halt(ExitText) -> - case [Vsn || {ejabberd, _Desc, Vsn} <- application:which_applications()] of - [] -> - timer:sleep(1000), - halt(string:substr(ExitText, 1, 199)); - [_] -> - exit(ExitText) - end. +-spec get_shared_key() -> binary(). +get_shared_key() -> + get_option(shared_key). -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%%% Support for 'include_config_file' - -get_config_option_key(Name, Val) -> - if Name == listen -> - case Val of - {{Port, IP, Trans}, _Mod, _Opts} -> - {Port, IP, Trans}; - {{Port, Trans}, _Mod, _Opts} when Trans == tcp; Trans == udp -> - {Port, {0,0,0,0}, Trans}; - {{Port, IP}, _Mod, _Opts} -> - {Port, IP, tcp}; - {Port, _Mod, _Opts} -> - {Port, {0,0,0,0}, tcp}; - V when is_list(V) -> - lists:foldl( - fun({port, Port}, {_, IP, T}) -> - {Port, IP, T}; - ({ip, IP}, {Port, _, T}) -> - {Port, IP, T}; - ({transport, T}, {Port, IP, _}) -> - {Port, IP, T}; - (_, Res) -> - Res - end, {5222, {0,0,0,0}, tcp}, Val) - end; - is_tuple(Val) -> - element(1, Val); - true -> - Val - end. +-spec get_node_start() -> integer(). +get_node_start() -> + get_option(node_start). -maps_to_lists(IMap) -> - maps:fold(fun(Name, Map, Res) when Name == host_config orelse Name == append_host_config -> - [{Name, [{Host, maps_to_lists(SMap)} || {Host,SMap} <- maps:values(Map)]} | Res]; - (Name, Map, Res) when is_map(Map) -> - [{Name, maps:values(Map)} | Res]; - (Name, Val, Res) -> - [{Name, Val} | Res] - end, [], IMap). - -merge_configs(Terms, ResMap) -> - lists:foldl(fun({Name, Val}, Map) when is_list(Val), Name =/= auth_method -> - Old = maps:get(Name, Map, #{}), - New = lists:foldl(fun(SVal, OMap) -> - NVal = if Name == host_config orelse Name == append_host_config -> - {Host, Opts} = SVal, - {_, SubMap} = maps:get(Host, OMap, {Host, #{}}), - {Host, merge_configs(Opts, SubMap)}; - true -> - SVal - end, - maps:put(get_config_option_key(Name, SVal), NVal, OMap) - end, Old, Val), - maps:put(Name, New, Map); - ({Name, Val}, Map) -> - maps:put(Name, Val, Map) - end, ResMap, Terms). - -%% @doc Include additional configuration files in the list of terms. -%% @spec ([term()]) -> [term()] -include_config_files(Terms) -> - {FileOpts, Terms1} = - lists:mapfoldl( - fun({include_config_file, _} = T, Ts) -> - {[transform_include_option(T)], Ts}; - ({include_config_file, _, _} = T, Ts) -> - {[transform_include_option(T)], Ts}; - (T, Ts) -> - {[], [T|Ts]} - end, [], Terms), - Terms2 = lists:flatmap( - fun({File, Opts}) -> - include_config_file(File, Opts) - end, lists:flatten(FileOpts)), - - M1 = merge_configs(Terms1, #{}), - M2 = merge_configs(Terms2, M1), - maps_to_lists(M2). - -transform_include_option({include_config_file, File}) when is_list(File) -> - case is_string(File) of - true -> {File, []}; - false -> File - end; -transform_include_option({include_config_file, Filename}) -> - {Filename, []}; -transform_include_option({include_config_file, Filename, Options}) -> - {Filename, Options}. - -include_config_file(Filename, Options) -> - Included_terms = get_plain_terms_file(Filename, [{include_files, true}, dont_halt_on_error]), - Disallow = proplists:get_value(disallow, Options, []), - Included_terms2 = delete_disallowed(Disallow, Included_terms), - Allow_only = proplists:get_value(allow_only, Options, all), - keep_only_allowed(Allow_only, Included_terms2). - -%% @doc Filter from the list of terms the disallowed. -%% Returns a sublist of Terms without the ones which first element is -%% included in Disallowed. -%% @spec (Disallowed::[atom()], Terms::[term()]) -> [term()] -delete_disallowed(Disallowed, Terms) -> - lists:foldl( - fun(Dis, Ldis) -> - delete_disallowed2(Dis, Ldis) - end, - Terms, - Disallowed). - -delete_disallowed2(Disallowed, [H|T]) -> - case element(1, H) of - Disallowed -> - ?WARNING_MSG("The option '~p' is disallowed, " - "and will not be accepted", [Disallowed]), - delete_disallowed2(Disallowed, T); - _ -> - [H|delete_disallowed2(Disallowed, T)] - end; -delete_disallowed2(_, []) -> - []. - -%% @doc Keep from the list only the allowed terms. -%% Returns a sublist of Terms with only the ones which first element is -%% included in Allowed. -%% @spec (Allowed::[atom()], Terms::[term()]) -> [term()] -keep_only_allowed(all, Terms) -> - Terms; -keep_only_allowed(Allowed, Terms) -> - {As, NAs} = lists:partition( - fun(Term) -> - lists:member(element(1, Term), Allowed) - end, - Terms), - [?WARNING_MSG("This option is not allowed, " - "and will not be accepted:~n~p", [NA]) - || NA <- NAs], - As. - - -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%%% Support for Macro - -%% @doc Replace the macros with their defined values. -%% @spec (Terms::[term()]) -> [term()] -replace_macros(Terms) -> - {TermsOthers, Macros} = split_terms_macros(Terms), - replace(TermsOthers, Macros). - -%% @doc Split Terms into normal terms and macro definitions. -%% @spec (Terms) -> {Terms, Macros} -%% Terms = [term()] -%% Macros = [macro()] -split_terms_macros(Terms) -> - lists:foldl( - fun(Term, {TOs, Ms}) -> - case Term of - {define_macro, Key, Value} -> - case is_correct_macro({Key, Value}) of - true -> - {TOs, Ms++[{Key, Value}]}; - false -> - exit({macro_not_properly_defined, Term}) - end; - {define_macro, KeyVals} -> - case lists:all(fun is_correct_macro/1, KeyVals) of - true -> - {TOs, Ms ++ KeyVals}; - false -> - exit({macros_not_properly_defined, Term}) - end; - Term -> - {TOs ++ [Term], Ms} - end - end, - {[], []}, - Terms). - -is_correct_macro({Key, _Val}) -> - is_atom(Key) and is_all_uppercase(Key); -is_correct_macro(_) -> - false. - -%% @doc Recursively replace in Terms macro usages with the defined value. -%% @spec (Terms, Macros) -> Terms -%% Terms = [term()] -%% Macros = [macro()] -replace([], _) -> - []; -replace([Term|Terms], Macros) -> - [replace_term(Term, Macros) | replace(Terms, Macros)]; -replace(Term, Macros) -> - replace_term(Term, Macros). - -replace_term(Key, Macros) when is_atom(Key) -> - case is_all_uppercase(Key) of - true -> - case proplists:get_value(Key, Macros) of - undefined -> exit({undefined_macro, Key}); - Value -> Value - end; +-spec fsm_limit_opts([proplists:property()]) -> [{max_queue, pos_integer()}]. +fsm_limit_opts(Opts) -> + case lists:keyfind(max_fsm_queue, 1, Opts) of + {_, I} when is_integer(I), I>0 -> + [{max_queue, I}]; false -> - Key - end; -replace_term({use_macro, Key, Value}, Macros) -> - proplists:get_value(Key, Macros, Value); -replace_term(Term, Macros) when is_list(Term) -> - replace(Term, Macros); -replace_term(Term, Macros) when is_tuple(Term) -> - List = tuple_to_list(Term), - List2 = replace(List, Macros), - list_to_tuple(List2); -replace_term(Term, _) -> - Term. - -is_all_uppercase(Atom) -> - String = erlang:atom_to_list(Atom), - lists:all(fun(C) when C >= $a, C =< $z -> false; - (_) -> true - end, String). - -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%%% Process terms - -process_term(Term, State) -> - case Term of - {host_config, HostTerms} -> - lists:foldl( - fun({Host, Terms}, AccState) -> - lists:foldl(fun(T, S) -> - process_host_term(T, Host, S, set) - end, AccState, Terms) - end, State, HostTerms); - {append_host_config, HostTerms} -> - lists:foldl( - fun({Host, Terms}, AccState) -> - lists:foldl(fun(T, S) -> - process_host_term(T, Host, S, append) - end, AccState, Terms) - end, State, HostTerms); - _ -> - process_host_term(Term, global, State, set) + case get_option(max_fsm_queue) of + undefined -> []; + N -> [{max_queue, N}] + end end. -process_host_term(Term, Host, State, Action) -> - case Term of - {modules, Modules} when Action == set -> - set_option({modules, Host}, replace_modules(Modules), State); - {modules, Modules} when Action == append -> - append_option({modules, Host}, replace_modules(Modules), State); - {host, _} -> - State; - {hosts, _} -> - State; - {Opt, Val} when Action == set -> - set_option({rename_option(Opt), Host}, change_val(Opt, Val), State); - {Opt, Val} when Action == append -> - append_option({rename_option(Opt), Host}, change_val(Opt, Val), State); - Opt -> - ?WARNING_MSG("Ignore invalid (outdated?) option ~p", [Opt]), - State +-spec codec_options() -> [xmpp:decode_option()]. +codec_options() -> + case get_option(validate_stream) of + true -> []; + false -> [ignore_els] end. -rename_option(Option) when is_atom(Option) -> - case atom_to_list(Option) of - "odbc_" ++ T -> - NewOption = list_to_atom("sql_" ++ T), - ?WARNING_MSG("Option '~s' is obsoleted, use '~s' instead", - [Option, NewOption]), - NewOption; +%% Do not use this function in runtime: +%% It's slow and doesn't read 'version' option from the config. +%% Use ejabberd_option:version() instead. +-spec version() -> binary(). +version() -> + case application:get_env(ejabberd, custom_vsn) of + {ok, Vsn0} when is_list(Vsn0) -> + list_to_binary(Vsn0); + {ok, Vsn1} when is_binary(Vsn1) -> + Vsn1; _ -> - Option - end; -rename_option(Option) -> - Option. - -change_val(auth_method, Val) -> - prepare_opt_val(auth_method, Val, - fun(V) -> - L = if is_list(V) -> V; - true -> [V] - end, - lists:map( - fun(odbc) -> sql; - (internal) -> mnesia; - (A) when is_atom(A) -> A - end, L) - end, [mnesia]); -change_val(_Opt, Val) -> - Val. - -set_option(Opt, Val, State) -> - State#state{opts = [#local_config{key = Opt, value = Val} | - State#state.opts]}. - -append_option({Opt, Host}, Val, State) -> - GlobalVals = lists:flatmap( - fun(#local_config{key = {O, global}, value = V}) - when O == Opt -> - if is_list(V) -> V; - true -> [V] - end; - (_) -> - [] - end, State#state.opts), - NewVal = if is_list(Val) -> Val ++ GlobalVals; - true -> [Val|GlobalVals] - end, - set_option({Opt, Host}, NewVal, State). - -set_opts(State) -> - Opts = State#state.opts, - F = fun() -> - lists:foreach(fun(R) -> - mnesia:write(R) - end, Opts) - end, - case mnesia:transaction(F) of - {atomic, _} -> ok; - {aborted,{no_exists,Table}} -> - MnesiaDirectory = mnesia:system_info(directory), - ?ERROR_MSG("Error reading Mnesia database spool files:~n" - "The Mnesia database couldn't read the spool file for the table '~p'.~n" - "ejabberd needs read and write access in the directory:~n ~s~n" - "Maybe the problem is a change in the computer hostname,~n" - "or a change in the Erlang node name, which is currently:~n ~p~n" - "Check the ejabberd guide for details about changing the~n" - "computer hostname or Erlang node name.~n", - [Table, MnesiaDirectory, node()]), - exit("Error reading Mnesia database") + case application:get_key(ejabberd, vsn) of + undefined -> <<"">>; + {ok, Vsn} -> list_to_binary(Vsn) + end end. -add_global_option(Opt, Val) -> - add_option(Opt, Val). - -add_local_option(Opt, Val) -> - add_option(Opt, Val). - -add_option(Opt, Val) when is_atom(Opt) -> - add_option({Opt, global}, Val); -add_option(Opt, Val) -> - mnesia:transaction(fun() -> - mnesia:write(#local_config{key = Opt, - value = Val}) - end). - --spec prepare_opt_val(any(), any(), check_fun(), any()) -> any(). - -prepare_opt_val(Opt, Val, F, Default) -> - Call = case F of - {Mod, Fun} -> - fun() -> Mod:Fun(Val) end; - _ -> - fun() -> F(Val) end - end, - try Call() of - Res -> - Res - catch {replace_with, NewRes} -> - NewRes; - {invalid_syntax, Error} -> - ?WARNING_MSG("incorrect value '~s' of option '~s', " - "using '~s' as fallback: ~s", - [format_term(Val), - format_term(Opt), - format_term(Default), - Error]), - Default; - _:_ -> - ?WARNING_MSG("incorrect value '~s' of option '~s', " - "using '~s' as fallback", - [format_term(Val), - format_term(Opt), - format_term(Default)]), +-spec default_db(binary() | global, module()) -> atom(). +default_db(Host, Module) -> + default_db(default_db, Host, Module, mnesia). + +-spec default_db(binary() | global, module(), atom()) -> atom(). +default_db(Host, Module, Default) -> + default_db(default_db, Host, Module, Default). + +-spec default_ram_db(binary() | global, module()) -> atom(). +default_ram_db(Host, Module) -> + default_db(default_ram_db, Host, Module, mnesia). + +-spec default_ram_db(binary() | global, module(), atom()) -> atom(). +default_ram_db(Host, Module, Default) -> + default_db(default_ram_db, Host, Module, Default). + +-spec default_db(default_db | default_ram_db, binary() | global, module(), atom()) -> atom(). +default_db(Opt, Host, Mod, Default) -> + Type = get_option({Opt, Host}), + DBMod = list_to_atom(atom_to_list(Mod) ++ "_" ++ atom_to_list(Type)), + case code:ensure_loaded(DBMod) of + {module, _} -> Type; + {error, _} -> + ?WARNING_MSG("Module ~ts doesn't support database '~ts' " + "defined in option '~ts', using " + "'~ts' as fallback", [Mod, Type, Opt, Default]), Default end. --type check_fun() :: fun((any()) -> any()) | {module(), atom()}. - --spec get_global_option(any(), check_fun()) -> any(). - -get_global_option(Opt, F) -> - get_option(Opt, F, undefined). - --spec get_global_option(any(), check_fun(), any()) -> any(). - -get_global_option(Opt, F, Default) -> - get_option(Opt, F, Default). - --spec get_local_option(any(), check_fun()) -> any(). - -get_local_option(Opt, F) -> - get_option(Opt, F, undefined). - --spec get_local_option(any(), check_fun(), any()) -> any(). - -get_local_option(Opt, F, Default) -> - get_option(Opt, F, Default). - --spec get_option(any(), check_fun()) -> any(). - -get_option(Opt, F) -> - get_option(Opt, F, undefined). - --spec get_option(any(), check_fun(), any()) -> any(). - -get_option(Opt, F, Default) when is_atom(Opt) -> - get_option({Opt, global}, F, Default); -get_option(Opt, F, Default) -> - case Opt of - {O, global} when is_atom(O) -> ok; - {O, H} when is_atom(O), is_binary(H) -> ok; - _ -> ?WARNING_MSG("Option ~p has invalid (outdated?) format. " - "This is likely a bug", [Opt]) - end, - case ets:lookup(local_config, Opt) of - [#local_config{value = Val}] -> - prepare_opt_val(Opt, Val, F, Default); - _ -> - case Opt of - {Key, Host} when Host /= global -> - get_option({Key, global}, F, Default); - _ -> - Default - end - end. - --spec has_option(atom() | {atom(), global | binary()}) -> any(). -has_option(Opt) -> - get_option(Opt, fun(_) -> true end, false). - -init_module_db_table(Modules) -> - catch ets:new(module_db, [named_table, public, bag]), - %% Dirty hack for mod_pubsub - ets:insert(module_db, {mod_pubsub, mnesia}), - ets:insert(module_db, {mod_pubsub, sql}), +-spec beams(local | external | all) -> [module()]. +beams(local) -> + {ok, Mods} = application:get_key(ejabberd, modules), + Mods; +beams(external) -> + ExtMods = [Name || {Name, _Details} <- ext_mod:installed()], lists:foreach( - fun(M) -> - case re:split(atom_to_list(M), "_", [{return, list}]) of - [_] -> - ok; - Parts -> - [Suffix|T] = lists:reverse(Parts), - BareMod = string:join(lists:reverse(T), "_"), - ets:insert(module_db, {list_to_atom(BareMod), - list_to_atom(Suffix)}) - end - end, Modules). + fun(ExtMod) -> + ExtModPath = ext_mod:module_ebin_dir(ExtMod), + case lists:member(ExtModPath, code:get_path()) of + true -> ok; + false -> code:add_patha(ExtModPath) + end + end, ExtMods), + case application:get_env(ejabberd, external_beams) of + {ok, Path} -> + case lists:member(Path, code:get_path()) of + true -> ok; + false -> code:add_patha(Path) + end, + Beams = filelib:wildcard(filename:join(Path, "*\.beam")), + CustMods = [list_to_atom(filename:rootname(filename:basename(Beam))) + || Beam <- Beams], + CustMods ++ ExtMods; + _ -> + ExtMods + end; +beams(all) -> + beams(local) ++ beams(external). --spec v_db(module(), atom()) -> atom(). +-spec may_hide_data(term()) -> term(). +may_hide_data(Data) -> + case get_option(hide_sensitive_log_data) of + false -> Data; + true -> "hidden_by_ejabberd" + end. -v_db(Mod, internal) -> v_db(Mod, mnesia); -v_db(Mod, odbc) -> v_db(Mod, sql); -v_db(Mod, Type) -> - case ets:match_object(module_db, {Mod, Type}) of - [_|_] -> Type; - [] -> erlang:error(badarg) +%% Some Erlang apps expects env parameters to be list and not binary. +%% For example, Mnesia is not able to start if mnesia dir is passed as a binary. +%% However, binary is most common on Elixir, so it is easy to make a setup mistake. +-spec env_binary_to_list(atom(), atom()) -> {ok, any()} | undefined. +env_binary_to_list(Application, Parameter) -> + %% Application need to be loaded to allow setting parameters + application:load(Application), + case application:get_env(Application, Parameter) of + {ok, Val} when is_binary(Val) -> + BVal = binary_to_list(Val), + application:set_env(Application, Parameter, BVal), + {ok, BVal}; + Other -> + Other end. --spec default_db(binary(), module()) -> atom(). +-spec validators([atom()]) -> {econf:validators(), [atom()]}. +validators(Disallowed) -> + Modules = callback_modules(all), + Validators = lists:foldl( + fun(M, Vs) -> + maps:merge(Vs, validators(M, Disallowed)) + end, #{}, Modules), + Required = lists:flatmap( + fun(M) -> + [O || O <- M:options(), is_atom(O)] + end, Modules), + {Validators, Required}. + +-spec convert_to_yaml(file:filename()) -> ok | error_return(). +convert_to_yaml(File) -> + convert_to_yaml(File, stdout). -default_db(Host, Module) -> - case ejabberd_config:get_option( - {default_db, Host}, fun(T) when is_atom(T) -> T end) of - undefined -> - mnesia; - DBType -> - try - v_db(Module, DBType) - catch error:badarg -> - ?WARNING_MSG("Module '~s' doesn't support database '~s' " - "defined in option 'default_db', using " - "'mnesia' as fallback", [Module, DBType]), - mnesia - end +-spec convert_to_yaml(file:filename(), + stdout | file:filename()) -> ok | error_return(). +convert_to_yaml(File, Output) -> + case read_erlang_file(File, []) of + {ok, Y} -> + dump(Y, Output); + Err -> + Err end. -get_modules_with_options() -> - {ok, Mods} = application:get_key(ejabberd, modules), - ExtMods = [Name || {Name, _Details} <- ext_mod:installed()], - AllMods = [?MODULE|ExtMods++Mods], - init_module_db_table(AllMods), - lists:foldl( - fun(Mod, D) -> - case catch Mod:opt_type('') of - Opts when is_list(Opts) -> - lists:foldl( - fun(Opt, Acc) -> - dict:append(Opt, Mod, Acc) - end, D, Opts); - {'EXIT', {undef, _}} -> - D - end - end, dict:new(), AllMods). - -validate_opts(#state{opts = Opts} = State) -> - ModOpts = get_modules_with_options(), - NewOpts = lists:filtermap( - fun(#local_config{key = {Opt, _Host}, value = Val} = In) -> - case dict:find(Opt, ModOpts) of - {ok, [Mod|_]} -> - VFun = Mod:opt_type(Opt), - try VFun(Val) of - _ -> - true - catch {replace_with, NewVal} -> - {true, In#local_config{value = NewVal}}; - {invalid_syntax, Error} -> - ?ERROR_MSG("ignoring option '~s' with " - "invalid value: ~p: ~s", - [Opt, Val, Error]), - false; - _:_ -> - ?ERROR_MSG("ignoring option '~s' with " - "invalid value: ~p", - [Opt, Val]), - false - end; - _ -> - ?ERROR_MSG("unknown option '~s' will be likely" - " ignored", [Opt]), - true - end - end, Opts), - State#state{opts = NewOpts}. - --spec get_vh_by_auth_method(atom()) -> [binary()]. - -%% Return the list of hosts with a given auth method -get_vh_by_auth_method(AuthMethod) -> - Cfgs = mnesia:dirty_match_object(local_config, - #local_config{key = {auth_method, '_'}, - _ = '_'}), - lists:flatmap( - fun(#local_config{key = {auth_method, Host}, value = M}) -> - Methods = if not is_list(M) -> [M]; - true -> M - end, - case lists:member(AuthMethod, Methods) of - true when Host == global -> - get_myhosts(); - true -> - [Host]; +-spec format_error(error_return()) -> string(). +format_error({error, Reason, Ctx}) -> + econf:format_error(Reason, Ctx); +format_error({error, {merge_conflict, Opt, Host}}) -> + lists:flatten( + io_lib:format( + "Cannot merge value of option '~ts' defined in append_host_config " + "for virtual host ~ts: only options of type list or map are allowed " + "in append_host_config. Hint: specify the option in host_config", + [Opt, Host])); +format_error({error, {old_config, Path, Reason}}) -> + lists:flatten( + io_lib:format( + "Failed to read configuration from '~ts': ~ts~ts", + [Path, + case Reason of + {_, _, _} -> "at line "; + _ -> "" + end, file:format_error(Reason)])); +format_error({error, {write_file, Path, Reason}}) -> + lists:flatten( + io_lib:format( + "Failed to write to '~ts': ~ts", + [Path, + file:format_error(Reason)])); +format_error({error, {exception, Class, Reason, St}}) -> + lists:flatten( + io_lib:format( + "Exception occurred during configuration processing. " + "This is most likely due to faulty/incompatible validator in " + "third-party code. If you are not running any third-party " + "code, please report the bug with ejabberd configuration " + "file attached and the following stacktrace included:~n** ~ts", + [misc:format_exception(2, Class, Reason, St)])). + +%%%=================================================================== +%%% Internal functions +%%%=================================================================== +-spec path() -> binary(). +path() -> + unicode:characters_to_binary( + case get_env_config() of + {ok, Path} -> + Path; + undefined -> + case os:getenv("EJABBERD_CONFIG_PATH") of false -> - [] + "ejabberd.yml"; + Path -> + Path end - end, Cfgs). - -%% @spec (Path::string()) -> true | false -is_file_readable(Path) -> - case file:read_file_info(Path) of - {ok, FileInfo} -> - case {FileInfo#file_info.type, FileInfo#file_info.access} of - {regular, read} -> true; - {regular, read_write} -> true; - _ -> false - end; - {error, _Reason} -> - false - end. + end). -get_version() -> - case application:get_key(ejabberd, vsn) of - undefined -> ""; - {ok, Vsn} -> list_to_binary(Vsn) +-spec get_env_config() -> {ok, string()} | undefined. +get_env_config() -> + %% First case: the filename can be specified with: erl -config "/path/to/ejabberd.yml". + case application:get_env(ejabberd, config) of + R = {ok, _Path} -> R; + undefined -> + %% Second case for embbeding ejabberd in another app, for example for Elixir: + %% config :ejabberd, + %% file: "config/ejabberd.yml" + application:get_env(ejabberd, file) end. --spec get_myhosts() -> [binary()]. - -get_myhosts() -> - get_option(hosts, fun(V) -> V end). - --spec get_mylang() -> binary(). +-spec create_tmp_config() -> ok. +create_tmp_config() -> + T = ets:new(options, [private]), + put(ejabberd_options, T), + ok. -get_mylang() -> - get_option( - language, - fun iolist_to_binary/1, - <<"en">>). - -replace_module(mod_announce_odbc) -> {mod_announce, sql}; -replace_module(mod_blocking_odbc) -> {mod_blocking, sql}; -replace_module(mod_caps_odbc) -> {mod_caps, sql}; -replace_module(mod_irc_odbc) -> {mod_irc, sql}; -replace_module(mod_last_odbc) -> {mod_last, sql}; -replace_module(mod_muc_odbc) -> {mod_muc, sql}; -replace_module(mod_offline_odbc) -> {mod_offline, sql}; -replace_module(mod_privacy_odbc) -> {mod_privacy, sql}; -replace_module(mod_private_odbc) -> {mod_private, sql}; -replace_module(mod_roster_odbc) -> {mod_roster, sql}; -replace_module(mod_shared_roster_odbc) -> {mod_shared_roster, sql}; -replace_module(mod_vcard_odbc) -> {mod_vcard, sql}; -replace_module(mod_vcard_xupdate_odbc) -> {mod_vcard_xupdate, sql}; -replace_module(mod_pubsub_odbc) -> {mod_pubsub, sql}; -replace_module(Module) -> - case is_elixir_module(Module) of - true -> expand_elixir_module(Module); - false -> Module - end. +-spec get_tmp_config() -> ets:tid() | undefined. +get_tmp_config() -> + get(ejabberd_options). -replace_modules(Modules) -> - lists:map( - fun({Module, Opts}) -> - case replace_module(Module) of - {NewModule, DBType} -> - emit_deprecation_warning(Module, NewModule, DBType), - NewOpts = [{db_type, DBType} | - lists:keydelete(db_type, 1, Opts)], - {NewModule, transform_module_options(Module, NewOpts)}; - NewModule -> - if Module /= NewModule -> - emit_deprecation_warning(Module, NewModule); - true -> - ok - end, - {NewModule, transform_module_options(Module, Opts)} - end - end, Modules). - -%% Elixir module naming -%% ==================== - -%% If module name start with uppercase letter, this is an Elixir module: -is_elixir_module(Module) -> - case atom_to_list(Module) of - [H|_] when H >= 65, H =< 90 -> true; - _ ->false +-spec delete_tmp_config() -> ok. +delete_tmp_config() -> + case get_tmp_config() of + undefined -> + ok; + T -> + erase(ejabberd_options), + ets:delete(T), + ok end. -%% We assume we know this is an elixir module -expand_elixir_module(Module) -> - case atom_to_list(Module) of - %% Module name already specified as an Elixir from Erlang module name - "Elixir." ++ _ -> Module; - %% if start with uppercase letter, this is an Elixir module: Append 'Elixir.' to module name. - ModuleString -> - list_to_atom("Elixir." ++ ModuleString) - end. +-spec callback_modules(local | external | all) -> [module()]. +callback_modules(local) -> + [ejabberd_options]; +callback_modules(external) -> + lists:filter( + fun(M) -> + case code:ensure_loaded(M) of + {module, _} -> + erlang:function_exported(M, options, 0) + andalso erlang:function_exported(M, opt_type, 1); + {error, _} -> + false + end + end, beams(external)); +callback_modules(all) -> + callback_modules(local) ++ callback_modules(external). + +-spec validators(module(), [atom()]) -> econf:validators(). +validators(Mod, Disallowed) -> + maps:from_list( + lists:filtermap( + fun(O) -> + case lists:member(O, Disallowed) of + true -> false; + false -> + {true, + try {O, Mod:opt_type(O)} + catch _:_ -> + {O, ejabberd_options:opt_type(O)} + end} + end + end, proplists:get_keys(Mod:options()))). -strings_to_binary([]) -> - []; -strings_to_binary(L) when is_list(L) -> - case is_string(L) of - true -> - list_to_binary(L); - false -> - strings_to_binary1(L) - end; -strings_to_binary({A, B, C, D}) when - is_integer(A), is_integer(B), is_integer(C), is_integer(D) -> - {A, B, C ,D}; -strings_to_binary(T) when is_tuple(T) -> - list_to_tuple(strings_to_binary1(tuple_to_list(T))); -strings_to_binary(X) -> - X. - -strings_to_binary1([El|L]) -> - [strings_to_binary(El)|strings_to_binary1(L)]; -strings_to_binary1([]) -> - []; -strings_to_binary1(T) -> - T. - -is_string([C|T]) when (C >= 0) and (C =< 255) -> - is_string(T); -is_string([]) -> - true; -is_string(_) -> - false. - -binary_to_strings(B) when is_binary(B) -> - binary_to_list(B); -binary_to_strings([H|T]) -> - [binary_to_strings(H)|binary_to_strings(T)]; -binary_to_strings(T) when is_tuple(T) -> - list_to_tuple(binary_to_strings(tuple_to_list(T))); -binary_to_strings(T) -> - T. - -format_term(Bin) when is_binary(Bin) -> - io_lib:format("\"~s\"", [Bin]); -format_term(S) when is_list(S), S /= [] -> - case lists:all(fun(C) -> (C>=0) and (C=<255) end, S) of - true -> - io_lib:format("\"~s\"", [S]); - false -> - io_lib:format("~p", [binary_to_strings(S)]) - end; -format_term(T) -> - io_lib:format("~p", [binary_to_strings(T)]). - -transform_terms(Terms) -> - %% We could check all ejabberd beams, but this - %% slows down start-up procedure :( - Mods = [mod_register, - mod_last, - ejabberd_s2s, - ejabberd_listener, - ejabberd_sql_sup, - shaper, - ejabberd_s2s_out, - acl, - ejabberd_config], - collect_options(transform_terms(Mods, Terms)). - -transform_terms([Mod|Mods], Terms) -> - case catch Mod:transform_options(Terms) of - {'EXIT', _} = Err -> - ?ERROR_MSG("Failed to transform terms by ~p: ~p", [Mod, Err]), - transform_terms(Mods, Terms); - NewTerms -> - transform_terms(Mods, NewTerms) - end; -transform_terms([], NewTerms) -> - NewTerms. +read_file(File) -> + read_file(File, [replace_macros, include_files, include_modules_configs]). -transform_module_options(Module, Opts) -> - Opts1 = gen_iq_handler:transform_module_options(Opts), - try - Module:transform_module_options(Opts1) - catch error:undef -> - Opts1 +read_file(File, Opts) -> + {Opts1, Opts2} = proplists:split(Opts, [replace_macros, include_files]), + Ret = case filename:extension(File) of + Ex when Ex == <<".yml">> orelse Ex == <<".yaml">> -> + Files = case proplists:get_bool(include_modules_configs, Opts2) of + true -> ext_mod:modules_configs(); + false -> [] + end, + lists:foreach( + fun(F) -> + ?INFO_MSG("Loading third-party configuration from ~ts", [F]) + end, Files), + read_yaml_files([File|Files], lists:flatten(Opts1)); + _ -> + read_erlang_file(File, lists:flatten(Opts1)) + end, + case Ret of + {ok, Y} -> + validate(Y); + Err -> + Err end. -compact(Cfg) -> - Opts = [{K, V} || #local_config{key = K, value = V} <- Cfg], - {GOpts, HOpts} = split_by_hosts(Opts), - [#local_config{key = {O, global}, value = V} || {O, V} <- GOpts] ++ - lists:flatmap( - fun({Host, OptVal}) -> - case lists:member(OptVal, GOpts) of - true -> - []; - false -> - [#local_config{key = {Opt, Host}, value = Val} - || {Opt, Val} <- OptVal] - end - end, lists:flatten(HOpts)). - -split_by_hosts(Opts) -> - Opts1 = orddict:to_list( - lists:foldl( - fun({{Opt, Host}, Val}, D) -> - orddict:append(Host, {Opt, Val}, D) - end, orddict:new(), Opts)), - case lists:keytake(global, 1, Opts1) of - {value, {global, GlobalOpts}, HostOpts} -> - {GlobalOpts, HostOpts}; - _ -> - {[], Opts1} +read_yaml_files(Files, Opts) -> + ParseOpts = [plain_as_atom | lists:flatten(Opts)], + lists:foldl( + fun(File, {ok, Y1}) -> + case econf:parse(File, #{'_' => econf:any()}, ParseOpts) of + {ok, Y2} -> {ok, Y1 ++ Y2}; + Err -> Err + end; + (_, Err) -> + Err + end, {ok, []}, Files). + +read_erlang_file(File, _) -> + case ejabberd_old_config:read_file(File) of + {ok, Y} -> + econf:replace_macros(Y); + Err -> + Err end. -collect_options(Opts) -> - {D, InvalidOpts} = - lists:foldl( - fun({K, V}, {D, Os}) when is_list(V) -> - {orddict:append_list(K, V, D), Os}; - ({K, V}, {D, Os}) -> - {orddict:store(K, V, D), Os}; - (Opt, {D, Os}) -> - {D, [Opt|Os]} - end, {orddict:new(), []}, Opts), - InvalidOpts ++ orddict:to_list(D). - -transform_options(Opts) -> - Opts1 = lists:foldl(fun transform_options/2, [], Opts), - {HOpts, Opts2} = lists:mapfoldl( - fun({host_config, O}, Os) -> - {[O], Os}; - (O, Os) -> - {[], [O|Os]} - end, [], Opts1), - {AHOpts, Opts3} = lists:mapfoldl( - fun({append_host_config, O}, Os) -> - {[O], Os}; - (O, Os) -> - {[], [O|Os]} - end, [], Opts2), - HOpts1 = case collect_options(lists:flatten(HOpts)) of - [] -> - []; - HOs -> - [{host_config, - [{H, transform_terms(O)} || {H, O} <- HOs]}] - end, - AHOpts1 = case collect_options(lists:flatten(AHOpts)) of - [] -> - []; - AHOs -> - [{append_host_config, - [{H, transform_terms(O)} || {H, O} <- AHOs]}] - end, - HOpts1 ++ AHOpts1 ++ Opts3. - -transform_options({domain_certfile, Domain, CertFile}, Opts) -> - ?WARNING_MSG("Option 'domain_certfile' now should be defined " - "per virtual host or globally. The old format is " - "still supported but it is better to fix your config", []), - [{host_config, [{Domain, [{domain_certfile, CertFile}]}]}|Opts]; -transform_options(Opt, Opts) when Opt == override_global; - Opt == override_local; - Opt == override_acls -> - ?WARNING_MSG("Ignoring '~s' option which has no effect anymore", [Opt]), - Opts; -transform_options({host_config, Host, HOpts}, Opts) -> - {AddOpts, HOpts1} = - lists:mapfoldl( - fun({{add, Opt}, Val}, Os) -> - ?WARNING_MSG("Option 'add' is deprecated. " - "The option is still supported " - "but it is better to fix your config: " - "use 'append_host_config' instead.", []), - {[{Opt, Val}], Os}; - (O, Os) -> - {[], [O|Os]} - end, [], HOpts), - [{append_host_config, [{Host, lists:flatten(AddOpts)}]}, - {host_config, [{Host, HOpts1}]}|Opts]; -transform_options({define_macro, Macro, Val}, Opts) -> - [{define_macro, [{Macro, Val}]}|Opts]; -transform_options({include_config_file, _} = Opt, Opts) -> - [{include_config_file, [transform_include_option(Opt)]} | Opts]; -transform_options({include_config_file, _, _} = Opt, Opts) -> - [{include_config_file, [transform_include_option(Opt)]} | Opts]; -transform_options(Opt, Opts) -> - [Opt|Opts]. - --spec convert_table_to_binary(atom(), [atom()], atom(), - fun(), fun()) -> ok. - -convert_table_to_binary(Tab, Fields, Type, DetectFun, ConvertFun) -> - case is_table_still_list(Tab, DetectFun) of - true -> - ?INFO_MSG("Converting '~s' table from strings to binaries.", [Tab]), - TmpTab = list_to_atom(atom_to_list(Tab) ++ "_tmp_table"), - catch mnesia:delete_table(TmpTab), - case mnesia:create_table(TmpTab, - [{disc_only_copies, [node()]}, - {type, Type}, - {local_content, true}, - {record_name, Tab}, - {attributes, Fields}]) of - {atomic, ok} -> - mnesia:transform_table(Tab, ignore, Fields), - case mnesia:transaction( - fun() -> - mnesia:write_lock_table(TmpTab), - mnesia:foldl( - fun(R, _) -> - NewR = ConvertFun(R), - mnesia:dirty_write(TmpTab, NewR) - end, ok, Tab) - end) of - {atomic, ok} -> - mnesia:clear_table(Tab), - case mnesia:transaction( - fun() -> - mnesia:write_lock_table(Tab), - mnesia:foldl( - fun(R, _) -> - mnesia:dirty_write(R) - end, ok, TmpTab) - end) of - {atomic, ok} -> - mnesia:delete_table(TmpTab); - Err -> - report_and_stop(Tab, Err) - end; - Err -> - report_and_stop(Tab, Err) - end; - Err -> - report_and_stop(Tab, Err) - end; - false -> - ok +-spec validate(term()) -> {ok, [{atom(), term()}]} | error_return(). +validate(Y1) -> + case pre_validate(Y1) of + {ok, Y2} -> + set_loglevel(proplists:get_value(loglevel, Y2, info)), + case ejabberd_config_transformer:map_reduce(Y2) of + {ok, Y3} -> + Hosts = proplists:get_value(hosts, Y3), + Version = proplists:get_value(version, Y3, version()), + create_tmp_config(), + set_option(hosts, Hosts), + set_option(host, hd(Hosts)), + set_option(version, Version), + set_option(yaml_config, Y3), + {Validators, Required} = validators([]), + Validator = econf:options(Validators, + [{required, Required}, + unique]), + econf:validate(Validator, Y3); + Err -> + Err + end; + Err -> + Err end. -is_table_still_list(Tab, DetectFun) -> - is_table_still_list(Tab, DetectFun, mnesia:dirty_first(Tab)). - -is_table_still_list(_Tab, _DetectFun, '$end_of_table') -> - false; -is_table_still_list(Tab, DetectFun, Key) -> - Rs = mnesia:dirty_read(Tab, Key), - Res = lists:foldl(fun(_, true) -> - true; - (_, false) -> - false; - (R, _) -> - case DetectFun(R) of - '$next' -> - '$next'; - El -> - is_list(El) - end - end, '$next', Rs), - case Res of - true -> - true; - false -> - false; - '$next' -> - is_table_still_list(Tab, DetectFun, mnesia:dirty_next(Tab, Key)) +-spec pre_validate(term()) -> {ok, [{atom(), term()}]} | error_return(). +pre_validate(Y1) -> + econf:validate( + econf:and_then( + econf:options( + #{hosts => ejabberd_options:opt_type(hosts), + loglevel => ejabberd_options:opt_type(loglevel), + version => ejabberd_options:opt_type(version), + '_' => econf:any()}, + [{required, [hosts]}]), + fun econf:group_dups/1), Y1). + +-spec load_file(binary()) -> ok | error_return(). +load_file(File) -> + try + case read_file(File) of + {ok, Terms} -> + case set_host_config(Terms) of + {ok, Map} -> + T = get_tmp_config(), + Hosts = get_myhosts(), + apply_defaults(T, Hosts, Map), + case validate_modules(Hosts) of + {ok, ModOpts} -> + ets:insert(T, ModOpts), + set_option(host, hd(Hosts)), + commit(), + set_fqdn(); + Err -> + abort(Err) + end; + Err -> + abort(Err) + end; + Err -> + abort(Err) + end + catch ?EX_RULE(Class, Reason, St) -> + {error, {exception, Class, Reason, ?EX_STACK(St)}} end. -report_and_stop(Tab, Err) -> - ErrTxt = lists:flatten( - io_lib:format( - "Failed to convert '~s' table to binary: ~p", - [Tab, Err])), - ?CRITICAL_MSG(ErrTxt, []), - timer:sleep(1000), - halt(string:substr(ErrTxt, 1, 199)). - -emit_deprecation_warning(Module, NewModule, DBType) -> - ?WARNING_MSG("Module ~s is deprecated, use ~s with 'db_type: ~s'" - " instead", [Module, NewModule, DBType]). - -emit_deprecation_warning(Module, NewModule) -> - case is_elixir_module(NewModule) of - %% Do not emit deprecation warning for Elixir - true -> ok; - false -> - ?WARNING_MSG("Module ~s is deprecated, use ~s instead", - [Module, NewModule]) +-spec commit() -> ok. +commit() -> + T = get_tmp_config(), + NewOpts = ets:tab2list(T), + ets:insert(ejabberd_options, NewOpts), + delete_tmp_config(). + +-spec abort(error_return()) -> error_return(). +abort(Err) -> + delete_tmp_config(), + try ets:lookup_element(ejabberd_options, {loglevel, global}, 2) of + Level -> set_loglevel(Level) + catch _:badarg -> + ok + end, + Err. + +-spec set_host_config([{atom(), term()}]) -> {ok, host_config()} | error_return(). +set_host_config(Opts) -> + Map1 = lists:foldl( + fun({Opt, Val}, M) when Opt /= host_config, + Opt /= append_host_config -> + maps:put({Opt, global}, Val, M); + (_, M) -> + M + end, #{}, Opts), + HostOpts = proplists:get_value(host_config, Opts, []), + AppendHostOpts = proplists:get_value(append_host_config, Opts, []), + Map2 = lists:foldl( + fun({Host, Opts1}, M1) -> + lists:foldl( + fun({Opt, Val}, M2) -> + maps:put({Opt, Host}, Val, M2) + end, M1, Opts1) + end, Map1, HostOpts), + Map3 = lists:foldl( + fun(_, {error, _} = Err) -> + Err; + ({Host, Opts1}, M1) -> + lists:foldl( + fun(_, {error, _} = Err) -> + Err; + ({Opt, L1}, M2) when is_list(L1) -> + L2 = try maps:get({Opt, Host}, M2) + catch _:{badkey, _} -> + maps:get({Opt, global}, M2, []) + end, + L3 = L2 ++ L1, + maps:put({Opt, Host}, L3, M2); + ({Opt, _}, _) -> + {error, {merge_conflict, Opt, Host}} + end, M1, Opts1) + end, Map2, AppendHostOpts), + case Map3 of + {error, _} -> Map3; + _ -> {ok, Map3} end. -opt_type(hide_sensitive_log_data) -> - fun (H) when is_boolean(H) -> H end; -opt_type(hosts) -> - fun(L) when is_list(L) -> - lists:map( - fun(H) -> - iolist_to_binary(H) - end, L) - end; -opt_type(language) -> - fun iolist_to_binary/1; -opt_type(_) -> - [hide_sensitive_log_data, hosts, language]. - --spec may_hide_data(string()) -> string(); - (binary()) -> binary(). +-spec apply_defaults(ets:tid(), [binary()], host_config()) -> ok. +apply_defaults(Tab, Hosts, Map) -> + Defaults1 = defaults(), + apply_defaults(Tab, global, Map, Defaults1), + {_, Defaults2} = proplists:split(Defaults1, globals()), + lists:foreach( + fun(Host) -> + set_option(host, Host), + apply_defaults(Tab, Host, Map, Defaults2) + end, Hosts). + +-spec apply_defaults(ets:tid(), global | binary(), + host_config(), + [atom() | {atom(), term()}]) -> ok. +apply_defaults(Tab, Host, Map, Defaults) -> + lists:foreach( + fun({Opt, Default}) -> + try maps:get({Opt, Host}, Map) of + Val -> + ets:insert(Tab, {{Opt, Host}, Val}) + catch _:{badkey, _} when Host == global -> + Default1 = compute_default(Default, Host), + ets:insert(Tab, {{Opt, Host}, Default1}); + _:{badkey, _} -> + try maps:get({Opt, global}, Map) of + V -> ets:insert(Tab, {{Opt, Host}, V}) + catch _:{badkey, _} -> + Default1 = compute_default(Default, Host), + ets:insert(Tab, {{Opt, Host}, Default1}) + end + end; + (Opt) when Host == global -> + Val = maps:get({Opt, Host}, Map), + ets:insert(Tab, {{Opt, Host}, Val}); + (_) -> + ok + end, Defaults). + +-spec defaults() -> [atom() | {atom(), term()}]. +defaults() -> + lists:foldl( + fun(Mod, Acc) -> + lists:foldl( + fun({Opt, Val}, Acc1) -> + lists:keystore(Opt, 1, Acc1, {Opt, Val}); + (Opt, Acc1) -> + case lists:member(Opt, Acc1) of + true -> Acc1; + false -> [Opt|Acc1] + end + end, Acc, Mod:options()) + end, ejabberd_options:options(), callback_modules(external)). + +-spec globals() -> [atom()]. +globals() -> + lists:usort( + lists:flatmap( + fun(Mod) -> + case erlang:function_exported(Mod, globals, 0) of + true -> Mod:globals(); + false -> [] + end + end, callback_modules(all))). + +%% The module validator depends on virtual host, so we have to +%% validate modules in this separate function. +-spec validate_modules([binary()]) -> {ok, list()} | error_return(). +validate_modules(Hosts) -> + lists:foldl( + fun(Host, {ok, Acc}) -> + set_option(host, Host), + ModOpts = get_option({modules, Host}), + case gen_mod:validate(Host, ModOpts) of + {ok, ModOpts1} -> + {ok, [{{modules, Host}, ModOpts1}|Acc]}; + Err -> + Err + end; + (_, Err) -> + Err + end, {ok, []}, Hosts). + +-spec delete_host_options([binary()]) -> ok. +delete_host_options(Hosts) -> + lists:foreach( + fun(Host) -> + ets:match_delete(ejabberd_options, {{'_', Host}, '_'}) + end, Hosts). + +-spec compute_default(fun((global | binary()) -> T) | T, global | binary()) -> T. +compute_default(F, Host) when is_function(F, 1) -> + F(Host); +compute_default(Val, _) -> + Val. -may_hide_data(Data) -> - case ejabberd_config:get_option( - hide_sensitive_log_data, - fun(false) -> false; - (true) -> true - end, - false) of - false -> - Data; - true -> - "hidden_by_ejabberd" - end. +-spec set_fqdn() -> ok. +set_fqdn() -> + FQDNs = get_option(fqdn), + xmpp:set_config([{fqdn, FQDNs}]). + +-spec set_shared_key() -> ok. +set_shared_key() -> + Key = case erlang:get_cookie() of + nocookie -> + str:sha(p1_rand:get_string()); + Cookie -> + str:sha(erlang:atom_to_binary(Cookie, latin1)) + end, + set_option(shared_key, Key). + +-spec set_node_start(integer()) -> ok. +set_node_start(UnixTime) -> + set_option(node_start, UnixTime). + +-spec set_loglevel(logger:level()) -> ok. +set_loglevel(Level) -> + ejabberd_logger:set(Level). |