when Ctx == [listen, module];
Ctx == [listen, request_handlers] ->
Mods = ejabberd_config:beams(all),
- format("~s: unknown ~s: ~s. Did you mean ~s?",
+ format("~ts: unknown ~ts: ~ts. Did you mean ~ts?",
[yconf:format_ctx(Ctx),
format_module_type(Ctx),
format_module(Mod),
_ -> false
end
end, ejabberd_config:beams(all)),
- format("~s: unknown ~s: ~s. Did you mean ~s?",
+ format("~ts: unknown ~ts: ~ts. Did you mean ~ts?",
[yconf:format_ctx(Ctx),
format_module_type(Ctx),
format_module(Mod),
Slogan = yconf:format_ctx(Ctx),
case lists:member(Mod, ejabberd_config:beams(local)) of
true ->
- format("~s: '~s' is not a ~s",
+ format("~ts: '~ts' is not a ~ts",
[Slogan, format_module(Mod), Type]);
false ->
case lists:member(Mod, ejabberd_config:beams(external)) of
true ->
- format("~s: third-party ~s '~s' doesn't export "
- "function ~s/~B. If it's really a ~s, "
+ format("~ts: third-party ~ts '~ts' doesn't export "
+ "function ~ts/~B. If it's really a ~ts, "
"consider to upgrade it",
[Slogan, Type, format_module(Mod),F, A, Type]);
false ->
- format("~s: '~s' doesn't match any known ~s",
+ format("~ts: '~ts' doesn't match any known ~ts",
[Slogan, format_module(Mod), Type])
end
end;
format_error({unknown_option, [], _} = Why, Ctx) ->
- format("~s. There are no available options",
+ format("~ts. There are no available options",
[yconf:format_error(Why, Ctx)]);
format_error({unknown_option, Known, Opt} = Why, Ctx) ->
- format("~s. Did you mean ~s? ~s",
+ format("~ts. Did you mean ~ts? ~ts",
[yconf:format_error(Why, Ctx),
misc:best_match(Opt, Known),
format_known("Available options", Known)]);
format_error({bad_enum, Known, Bad} = Why, Ctx) ->
- format("~s. Did you mean ~s? ~s",
+ format("~ts. Did you mean ~ts? ~ts",
[yconf:format_error(Why, Ctx),
misc:best_match(Bad, Known),
format_known("Possible values", Known)]);
yconf:format_ctx(Ctx) ++ ": " ++ [string:to_lower(H)|T].
format_error({bad_db_type, _, Atom}) ->
- format("unsupported database: ~s", [Atom]);
+ format("unsupported database: ~ts", [Atom]);
format_error({bad_lang, Lang}) ->
- format("Invalid language tag: ~s", [Lang]);
+ format("Invalid language tag: ~ts", [Lang]);
format_error({bad_pem, Why, Path}) ->
- format("Failed to read PEM file '~s': ~s",
+ format("Failed to read PEM file '~ts': ~ts",
[Path, pkix:format_error(Why)]);
format_error({bad_cert, Why, Path}) ->
format_error({bad_pem, Why, Path});
format_error({bad_jwt_key, Path}) ->
- format("No valid JWT key found in file: ~s", [Path]);
+ format("No valid JWT key found in file: ~ts", [Path]);
format_error({bad_jid, Bad}) ->
- format("Invalid XMPP address: ~s", [Bad]);
+ format("Invalid XMPP address: ~ts", [Bad]);
format_error({bad_user, Bad}) ->
- format("Invalid user part: ~s", [Bad]);
+ format("Invalid user part: ~ts", [Bad]);
format_error({bad_domain, Bad}) ->
- format("Invalid domain: ~s", [Bad]);
+ format("Invalid domain: ~ts", [Bad]);
format_error({bad_resource, Bad}) ->
- format("Invalid resource part: ~s", [Bad]);
+ format("Invalid resource part: ~ts", [Bad]);
format_error({bad_ldap_filter, Bad}) ->
- format("Invalid LDAP filter: ~s", [Bad]);
+ format("Invalid LDAP filter: ~ts", [Bad]);
format_error({bad_sip_uri, Bad}) ->
- format("Invalid SIP URI: ~s", [Bad]);
+ format("Invalid SIP URI: ~ts", [Bad]);
format_error({route_conflict, R}) ->
- format("Failed to reuse route '~s' because it's "
+ format("Failed to reuse route '~ts' because it's "
"already registered on a virtual host",
[R]);
format_error({listener_dup, AddrPort}) ->
- format("Overlapping listeners found at ~s",
+ format("Overlapping listeners found at ~ts",
[format_addr_port(AddrPort)]);
format_error({listener_conflict, AddrPort1, AddrPort2}) ->
- format("Overlapping listeners found at ~s and ~s",
+ format("Overlapping listeners found at ~ts and ~ts",
[format_addr_port(AddrPort1),
format_addr_port(AddrPort2)]);
format_error({invalid_syntax, Reason}) ->
- format("~s", [Reason]);
+ format("~ts", [Reason]);
format_error({missing_module_dep, Mod, DepMod}) ->
- format("module ~s depends on module ~s, "
+ format("module ~ts depends on module ~ts, "
"which is not found in the config",
[Mod, DepMod]);
format_error(eimp_error) ->
case lists:member(DepApp, [App|Apps]) of
true ->
Reason = io_lib:format(
- "Failed to start Erlang application '~s': "
- "circular dependency with '~s' detected",
+ "Failed to start Erlang application '~ts': "
+ "circular dependency with '~ts' detected",
[App, DepApp]),
exit_or_halt(Reason, StartFlag);
false ->
end;
{error, Why} ->
Reason = io_lib:format(
- "Failed to start Erlang application '~s': ~s. ~s",
+ "Failed to start Erlang application '~ts': ~ts. ~ts",
[App, format_error(Why), hint()]),
exit_or_halt(Reason, StartFlag)
end;
non_existing ->
File = get_module_file(App, Mod),
Reason = io_lib:format(
- "Couldn't find file ~s needed "
- "for Erlang application '~s'. ~s",
+ "Couldn't find file ~ts needed "
+ "for Erlang application '~ts'. ~ts",
[File, App, hint()]),
exit_or_halt(Reason, StartFlag);
_ ->
Apps = [ejabberd |
[App || {App, _, _} <- application:which_applications(),
App /= ejabberd]],
- ?DEBUG("Checking consistency of applications: ~s",
+ ?DEBUG("Checking consistency of applications: ~ts",
[misc:join_atoms(Apps, <<", ">>)]),
misc:peach(
fun(App) ->
case matches_definition(Def, Cmd, CallerModule, Tag, Host, CallerInfo) of
true ->
?DEBUG("Command '~p' execution allowed by rule "
- "'~s' (CallerInfo=~p)", [Cmd, Name, CallerInfo]),
+ "'~ts' (CallerInfo=~p)", [Cmd, Name, CallerInfo]),
allow;
_ ->
none
-spec process([binary()], _) -> {integer(), [{binary(), binary()}], binary()}.
process([Token], _) ->
- ?DEBUG("Received ACME challenge request for token: ~s", [Token]),
+ ?DEBUG("Received ACME challenge request for token: ~ts", [Token]),
try ets:lookup_element(acme_challenge, Token, 2) of
Key -> {200, [{<<"Content-Type">>,
<<"application/octet-stream">>}],
{ok, #state{}}.
handle_call({request, [_|_] = Domains}, _From, State) ->
- ?INFO_MSG("Requesting new certificate for ~ts from ~s",
+ ?INFO_MSG("Requesting new certificate for ~ts from ~ts",
[misc:format_hosts_list(Domains), directory_url()]),
{Ret, State1} = issue_request(State, Domains),
{reply, Ret, State1};
handle_cast(ejabberd_started, State) ->
case request_on_start() of
{true, Domains} ->
- ?INFO_MSG("Requesting new certificate for ~ts from ~s",
+ ?INFO_MSG("Requesting new certificate for ~ts from ~ts",
[misc:format_hosts_list(Domains), directory_url()]),
{_, State1} = issue_request(State, Domains),
{noreply, State1};
{noreply, State}
end;
handle_cast({request, [_|_] = Domains}, State) ->
- ?INFO_MSG("Requesting renewal of certificate for ~ts from ~s",
+ ?INFO_MSG("Requesting renewal of certificate for ~ts from ~ts",
[misc:format_hosts_list(Domains), directory_url()]),
{_, State1} = issue_request(State, Domains),
{noreply, State1};
{error, enoent} ->
create_account_key();
{error, {bad_cert, _, _} = Reason} ->
- ?WARNING_MSG("ACME account key from '~ts' is corrupted: ~s. "
+ ?WARNING_MSG("ACME account key from '~ts' is corrupted: ~ts. "
"Trying to create a new one...",
[Path, pkix:format_error(Reason)]),
create_account_key();
{error, Reason} ->
- ?ERROR_MSG("Failed to read ACME account from ~ts: ~s. "
+ ?ERROR_MSG("Failed to read ACME account from ~ts: ~ts. "
"Try to fix permissions or delete the file completely",
[Path, pkix:format_error(Reason)]),
{error, {file, Reason}}
case file:change_mode(Path, 8#600) of
ok -> ok;
{error, Why} ->
- ?WARNING_MSG("Failed to change permissions of ~ts: ~s",
+ ?WARNING_MSG("Failed to change permissions of ~ts: ~ts",
[Path, file:format_error(Why)])
end;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to write file ~ts: ~s",
+ ?ERROR_MSG("Failed to write file ~ts: ~ts",
[Path, file:format_error(Why)]),
Err
end;
case file:delete(Path) of
ok -> ok;
{error, Why} = Err ->
- ?WARNING_MSG("Failed to delete file ~ts: ~s",
+ ?WARNING_MSG("Failed to delete file ~ts: ~ts",
[Path, file:format_error(Why)]),
Err
end.
case filelib:ensure_dir(Path) of
ok -> ok;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to create directory ~ts: ~s",
+ ?ERROR_MSG("Failed to create directory ~ts: ~ts",
[filename:dirname(Path),
file:format_error(Why)]),
Err
false ->
{ejabberd_not_running, "ejabberd is not running in that node."};
{value, {_, _, Version}} ->
- {ok, io_lib:format("ejabberd ~s is running in that node", [Version])}
+ {ok, io_lib:format("ejabberd ~ts is running in that node", [Version])}
end,
{Is_running, String1 ++ String2}.
SecondsDiff =
calendar:datetime_to_gregorian_seconds({date(), time()})
- TimestampStart,
- io:format("[~p/~p ~ps] ~s... ",
+ io:format("[~p/~p ~ps] ~ts... ",
[NumberThis, NumberLast, SecondsDiff, Desc]),
Result = (catch apply(Mod, Func, Args)),
io:format("~p~n", [Result]),
ok.
send_service_message_all_mucs(Subject, AnnouncementText) ->
- Message = str:format("~s~n~s", [Subject, AnnouncementText]),
+ Message = str:format("~ts~n~ts", [Subject, AnnouncementText]),
lists:foreach(
fun(ServerHost) ->
MUCHosts = gen_mod:get_module_opt_hosts(ServerHost, mod_muc),
true ->
case ejabberd_auth:try_register(User, Host, Password) of
ok ->
- {ok, io_lib:format("User ~s@~s successfully registered", [User, Host])};
+ {ok, io_lib:format("User ~ts@~ts successfully registered", [User, Host])};
{error, exists} ->
- Msg = io_lib:format("User ~s@~s already registered", [User, Host]),
+ Msg = io_lib:format("User ~ts@~ts already registered", [User, Host]),
{error, conflict, 10090, Msg};
{error, Reason} ->
- String = io_lib:format("Can't register user ~s@~s at node ~p: ~s",
+ String = io_lib:format("Can't register user ~ts@~ts at node ~p: ~ts",
[User, Host, node(),
mod_register:format_error(Reason)]),
{error, cannot_register, 10001, String}
ejabberd_hooks:run(ejabberd_started, []),
ejabberd:check_apps(),
{T2, _} = statistics(wall_clock),
- ?INFO_MSG("ejabberd ~s is started in the node ~p in ~.2fs",
+ ?INFO_MSG("ejabberd ~ts is started in the node ~p in ~.2fs",
[ejabberd_option:version(),
node(), (T2-T1)/1000]),
{ok, SupPid};
ejabberd:halt()
end;
Err ->
- ?CRITICAL_MSG("Failed to start ejabberd application: ~s",
+ ?CRITICAL_MSG("Failed to start ejabberd application: ~ts",
[ejabberd_config:format_error(Err)]),
ejabberd:halt()
end
%% All the processes were killed when this function is called
stop(_State) ->
- ?INFO_MSG("ejabberd ~s is stopped in the node ~p",
+ ?INFO_MSG("ejabberd ~ts is stopped in the node ~p",
[ejabberd_option:version(), node()]),
delete_pid_file().
end.
write_pid_file(Pid, PidFilename) ->
- case file:write_file(PidFilename, io_lib:format("~s~n", [Pid])) of
+ case file:write_file(PidFilename, io_lib:format("~ts~n", [Pid])) of
ok ->
ok;
{error, Reason} = Err ->
- ?CRITICAL_MSG("Cannot write PID file ~s: ~s",
+ ?CRITICAL_MSG("Cannot write PID file ~ts: ~ts",
[PidFilename, file:format_error(Reason)]),
throw({?MODULE, Err})
end.
-spec failure(binary(), binary(), atom(), any()) -> {nocache, {error, db_failure}}.
failure(User, Server, Fun, Reason) ->
?ERROR_MSG("External authentication program failed when calling "
- "'~s' for ~s@~s: ~p", [Fun, User, Server, Reason]),
+ "'~ts' for ~ts@~ts: ~p", [Fun, User, Server, Reason]),
{nocache, {error, db_failure}}.
start(Host) ->
case ejabberd_option:jwt_key(Host) of
undefined ->
- ?ERROR_MSG("Option jwt_key is not configured for ~s: "
+ ?ERROR_MSG("Option jwt_key is not configured for ~ts: "
"JWT authentication won't work", [Host]);
_ ->
ok
scram ->
case jid:resourceprep(Password) of
error ->
- ?ERROR_MSG("SASLprep failed for password of user ~s@~s",
+ ?ERROR_MSG("SASLprep failed for password of user ~ts@~ts",
[U, S]),
P;
_ ->
error ->
?ERROR_MSG(
"SASLprep failed for "
- "password of user ~s@~s",
+ "password of user ~ts@~ts",
[LUser, LServer]);
_ ->
Scram = ejabberd_auth:password_to_scram(Password),
State) ->
{next_state, StateName, State#state{shaper_state = Shaper}};
handle_event(_Event, StateName, State) ->
- ?ERROR_MSG("Unexpected event in '~s': ~p",
+ ?ERROR_MSG("Unexpected event in '~ts': ~p",
[StateName, _Event]),
{next_state, StateName, State}.
{reply, ok, StateName,
StateData#state{c2s_pid = undefined}};
handle_sync_event(_Event, _From, StateName, State) ->
- ?ERROR_MSG("Unexpected sync event in '~s': ~p",
+ ?ERROR_MSG("Unexpected sync event in '~ts': ~p",
[StateName, _Event]),
{reply, {error, badarg}, StateName, State}.
process_auth_result(#{sasl_mech := Mech, auth_module := AuthModule,
socket := Socket, ip := IP, lserver := LServer} = State,
true, User) ->
- ?INFO_MSG("(~s) Accepted c2s ~s authentication for ~s@~s by ~s backend from ~s",
+ ?INFO_MSG("(~ts) Accepted c2s ~ts authentication for ~ts@~ts by ~ts backend from ~ts",
[xmpp_socket:pp(Socket), Mech, User, LServer,
ejabberd_auth:backend_type(AuthModule),
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
process_auth_result(#{sasl_mech := Mech,
socket := Socket, ip := IP, lserver := LServer} = State,
{false, Reason}, User) ->
- ?WARNING_MSG("(~s) Failed c2s ~s authentication ~sfrom ~s: ~s",
+ ?WARNING_MSG("(~ts) Failed c2s ~ts authentication ~tsfrom ~ts: ~ts",
[xmpp_socket:pp(Socket), Mech,
if User /= <<"">> -> ["for ", User, "@", LServer, " "];
true -> ""
jid := JID, user := U, server := S, resource := R} = State,
Reason) ->
Status = format_reason(State, Reason),
- ?INFO_MSG("(~s) Closing c2s session for ~s: ~s",
+ ?INFO_MSG("(~ts) Closing c2s session for ~ts: ~ts",
[xmpp_socket:pp(Socket), jid:encode(JID), Status]),
State1 = case maps:is_key(pres_last, State) of
true ->
State1;
process_terminated(#{socket := Socket,
stop_reason := {tls, _}} = State, Reason) ->
- ?WARNING_MSG("(~s) Failed to secure c2s connection: ~s",
+ ?WARNING_MSG("(~ts) Failed to secure c2s connection: ~ts",
[xmpp_socket:pp(Socket), format_reason(State, Reason)]),
State;
process_terminated(State, _Reason) ->
sid => ejabberd_sm:make_sid()}),
State2 = ejabberd_hooks:run_fold(
c2s_session_opened, LServer, State1, []),
- ?INFO_MSG("(~s) Opened c2s session for ~s",
+ ?INFO_MSG("(~ts) Opened c2s session for ~ts",
[xmpp_socket:pp(Socket), jid:encode(JID)]),
{ok, State2};
deny ->
ejabberd_hooks:run(forbidden_session_hook, LServer, [JID]),
- ?WARNING_MSG("(~s) Forbidden c2s session for ~s",
+ ?WARNING_MSG("(~ts) Forbidden c2s session for ~ts",
[xmpp_socket:pp(Socket), jid:encode(JID)]),
Txt = ?T("Access denied by service policy"),
{error, xmpp:err_not_allowed(Txt, Lang), State}
SIDs = ejabberd_sm:get_session_sids(U, S, R),
case lists:member(SID, SIDs) of
true ->
- ?WARNING_MSG("The session for ~s@~s/~s is supposed to "
+ ?WARNING_MSG("The session for ~ts@~ts/~ts is supposed to "
"be unregistered, but session identifier ~p "
"still presents in the 'session' table",
[U, S, R, Pid]);
Lang, [challenge]),
X = #xdata{type = form, fields = Fs},
Captcha = #xcaptcha{xdata = X},
- BodyString = {?T("Your subscription request and/or messages to ~s have been blocked. "
- "To unblock your subscription request, visit ~s"), [JID, get_url(Id)]},
+ BodyString = {?T("Your subscription request and/or messages to ~ts have been blocked. "
+ "To unblock your subscription request, visit ~ts"), [JID, get_url(Id)]},
Body = xmpp:mk_text(BodyString, Lang),
OOB = #oob_x{url = get_url(Id)},
Hint = #hint{type = 'no-store'},
captcha_not_found -> {error, not_found}
end
catch _:{captcha_form, Why} ->
- ?WARNING_MSG("Malformed CAPTCHA form: ~s",
+ ?WARNING_MSG("Malformed CAPTCHA form: ~ts",
[captcha_form:format_error(Why)]),
{error, malformed}
end;
{error, image_error()}.
do_create_image(Key) ->
FileName = get_prog_name(),
- Cmd = lists:flatten(io_lib:format("~s ~s", [FileName, Key])),
+ Cmd = lists:flatten(io_lib:format("~ts ~ts", [FileName, Key])),
case cmd(Cmd) of
{ok,
<<137, $P, $N, $G, $\r, $\n, 26, $\n, _/binary>> =
when X == $7; X == $9 ->
{ok, <<"image/gif">>, Key, Img};
{error, enodata = Reason} ->
- ?ERROR_MSG("Failed to process output from \"~s\". "
+ ?ERROR_MSG("Failed to process output from \"~ts\". "
"Maybe ImageMagick's Convert program "
"is not installed.",
[Cmd]),
{error, Reason};
{error, Reason} ->
- ?ERROR_MSG("Failed to process an output from \"~s\": ~p",
+ ?ERROR_MSG("Failed to process an output from \"~ts\": ~p",
[Cmd, Reason]),
{error, Reason};
_ ->
Reason = malformed_image,
- ?ERROR_MSG("Failed to process an output from \"~s\": ~p",
+ ?ERROR_MSG("Failed to process an output from \"~ts\": ~p",
[Cmd, Reason]),
{error, Reason}
end.
{noreply, State}.
handle_info({node_up, Node}, State) ->
- ?INFO_MSG("Node ~s has joined", [Node]),
+ ?INFO_MSG("Node ~ts has joined", [Node]),
{noreply, State};
handle_info({node_down, Node}, State) ->
- ?INFO_MSG("Node ~s has left", [Node]),
+ ?INFO_MSG("Node ~ts has left", [Node]),
{noreply, State};
handle_info(Info, State) ->
?WARNING_MSG("Unexpected info: ~p", [Info]),
end.
format_type({list, {_, {tuple, Els}}}) ->
- io_lib:format("[~s]", [format_type({tuple, Els})]);
+ io_lib:format("[~ts]", [format_type({tuple, Els})]);
format_type({list, El}) ->
- io_lib:format("[~s]", [format_type(El)]);
+ io_lib:format("[~ts]", [format_type(El)]);
format_type({tuple, Els}) ->
Args = [format_type(El) || El <- Els],
- io_lib:format("{~s}", [string:join(Args, ", ")]);
+ io_lib:format("{~ts}", [string:join(Args, ", ")]);
format_type({Name, Type}) ->
- io_lib:format("~s::~s", [Name, format_type(Type)]);
+ io_lib:format("~ts::~ts", [Name, format_type(Type)]);
format_type(binary) ->
"string";
format_type(atom) ->
Langs = binary:split(Languages, <<",">>, [global]),
Out = lists:map(fun(C) -> gen_doc(C, true, Langs) end, Cmds4),
{ok, Fh} = file:open(File, [write]),
- io:format(Fh, "~s", [[html_pre(), Out, html_post()]]),
+ io:format(Fh, "~ts", [[html_pre(), Out, html_post()]]),
file:close(Fh),
ok.
"// Autogenerated with 'ejabberdctl gen_markdown_doc_for_commands'\n---">>,
Out = lists:map(fun(C) -> gen_doc(C, false, Langs) end, Cmds4),
{ok, Fh} = file:open(File, [write]),
- io:format(Fh, "~s~s", [Header, Out]),
+ io:format(Fh, "~ts~ts", [Header, Out]),
file:close(Fh),
ok.
load(Path) ->
ConfigFile = unicode:characters_to_binary(Path),
UnixTime = erlang:monotonic_time(second),
- ?INFO_MSG("Loading configuration from ~s", [ConfigFile]),
+ ?INFO_MSG("Loading configuration from ~ts", [ConfigFile]),
_ = ets:new(ejabberd_options,
[named_table, public, {read_concurrency, true}]),
case load_file(ConfigFile) of
-spec reload() -> ok | error_return().
reload() ->
ConfigFile = path(),
- ?INFO_MSG("Reloading configuration from ~s", [ConfigFile]),
+ ?INFO_MSG("Reloading configuration from ~ts", [ConfigFile]),
OldHosts = get_myhosts(),
case load_file(ConfigFile) of
ok ->
delete_host_options(DelHosts),
?INFO_MSG("Configuration reloaded successfully", []);
Err ->
- ?ERROR_MSG("Configuration reload aborted: ~s",
+ ?ERROR_MSG("Configuration reload aborted: ~ts",
[format_error(Err)]),
Err
end.
Data = fast_yaml:encode(Y),
case Output of
stdout ->
- io:format("~s~n", [Data]);
+ io:format("~ts~n", [Data]);
FileName ->
try
ok = filelib:ensure_dir(FileName),
catch ?EX_RULE(error, badarg, St) when Host /= global ->
StackTrace = ?EX_STACK(St),
Val = get_option({O, global}),
- ?WARNING_MSG("Option '~s' is not defined for virtual host '~s'. "
+ ?WARNING_MSG("Option '~ts' is not defined for virtual host '~ts'. "
"This is a bug, please report it with the following "
- "stacktrace included:~n** ~s",
+ "stacktrace included:~n** ~ts",
[O, Host, misc:format_exception(2, error, badarg, StackTrace)]),
Val
end.
case code:ensure_loaded(DBMod) of
{module, _} -> Type;
{error, _} ->
- ?WARNING_MSG("Module ~s doesn't support database '~s' "
- "defined in option '~s', using "
- "'~s' as fallback", [Mod, Type, Opt, Default]),
+ ?WARNING_MSG("Module ~ts doesn't support database '~ts' "
+ "defined in option '~ts', using "
+ "'~ts' as fallback", [Mod, Type, Opt, Default]),
Default
end.
format_error({error, {merge_conflict, Opt, Host}}) ->
lists:flatten(
io_lib:format(
- "Cannot merge value of option '~s' defined in append_host_config "
- "for virtual host ~s: only options of type list or map are allowed "
+ "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 '~s': ~s~s",
- [unicode:characters_to_binary(Path),
+ "Failed to read configuration from '~ts': ~ts~ts",
+ [Path,
case Reason of
{_, _, _} -> "at line ";
_ -> ""
format_error({error, {write_file, Path, Reason}}) ->
lists:flatten(
io_lib:format(
- "Failed to write to '~s': ~s",
- [unicode:characters_to_binary(Path),
+ "Failed to write to '~ts': ~ts",
+ [Path,
file:format_error(Reason)]));
format_error({error, {exception, Class, Reason, St}}) ->
lists:flatten(
"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** ~s",
+ "file attached and the following stacktrace included:~n** ~ts",
[misc:format_exception(2, Class, Reason, St)])).
%%%===================================================================
Y2 = (validator())(Y1),
Y3 = transform(Y2),
if Y2 /= Y3 ->
- ?DEBUG("Transformed configuration:~s~n",
+ ?DEBUG("Transformed configuration:~ts~n",
[misc:format_val({yaml, Y3})]);
true ->
ok
transform(_Host, Opt, CertFile, Acc) when (Opt == domain_certfile) orelse
(Opt == c2s_certfile) orelse
(Opt == s2s_certfile) ->
- ?WARNING_MSG("Option '~s' is deprecated and was automatically "
- "appended to 'certfiles' option. ~s",
+ ?WARNING_MSG("Option '~ts' is deprecated and was automatically "
+ "appended to 'certfiles' option. ~ts",
[Opt, adjust_hint()]),
CertFiles = maps:get(certfiles, Acc, []),
Acc1 = maps:put(certfiles, CertFiles ++ [CertFile], Acc),
case http_uri:parse(binary_to_list(URL)) of
{ok, {_, _, "acme-v01.api.letsencrypt.org", _, _, _}} ->
NewURL = ejabberd_acme:default_directory_url(),
- ?WARNING_MSG("ACME directory URL ~s defined in "
+ ?WARNING_MSG("ACME directory URL ~ts defined in "
"option acme->ca_url is deprecated "
"and was automatically replaced "
- "with ~s. ~s",
+ "with ~ts. ~ts",
[URL, NewURL, adjust_hint()]),
{ca_url, NewURL};
_ ->
"'s2s_use_starttls' is deprecated and was "
"automatically replaced with value 'required'. "
"The module 'mod_s2s_dialback' has also "
- "been automatically removed from the configuration. ~s",
+ "been automatically removed from the configuration. ~ts",
[adjust_hint()]),
Hosts = maps:get(remove_s2s_dialback, Acc, []),
Acc1 = maps:put(remove_s2s_dialback, [Host|Hosts], Acc),
({http_poll, _}) ->
?WARNING_MSG("Listening option 'http_poll' is "
"ignored: HTTP Polling support was "
- "removed in ejabberd 15.04. ~s",
+ "removed in ejabberd 15.04. ~ts",
[adjust_hint()]),
false;
({request_handlers, _}) ->
Mod == ejabberd_s2s_in ->
case lists:keyfind(certfile, 1, Opts) of
{_, CertFile} ->
- ?WARNING_MSG("Listening option 'certfile' of module ~s "
+ ?WARNING_MSG("Listening option 'certfile' of module ~ts "
"is deprecated and was automatically "
- "appended to global 'certfiles' option. ~s",
+ "appended to global 'certfiles' option. ~ts",
[Mod, adjust_hint()]),
CertFiles = maps:get(certfiles, Acc, []),
{proplists:delete(certfile, Opts),
<<"public">>]) of
true ->
?WARNING_MSG(
- "Plugin '~s' of mod_pubsub is not "
+ "Plugin '~ts' of mod_pubsub is not "
"supported anymore and has been "
"automatically removed from 'plugins' "
- "option. ~s",
+ "option. ~ts",
[Plugin, adjust_hint()]),
false;
false ->
%%% Warnings
%%%===================================================================
warn_replaced_module(From, To) ->
- ?WARNING_MSG("Module ~s is deprecated and was automatically "
- "replaced by ~s. ~s",
+ ?WARNING_MSG("Module ~ts is deprecated and was automatically "
+ "replaced by ~ts. ~ts",
[From, To, adjust_hint()]).
warn_replaced_module(From, To, Type) ->
- ?WARNING_MSG("Module ~s is deprecated and was automatically "
- "replaced by ~s with db_type: ~s. ~s",
+ ?WARNING_MSG("Module ~ts is deprecated and was automatically "
+ "replaced by ~ts with db_type: ~ts. ~ts",
[From, To, Type, adjust_hint()]).
warn_removed_module(Mod) ->
- ?WARNING_MSG("Module ~s is deprecated and was automatically "
- "removed from the configuration. ~s", [Mod, adjust_hint()]).
+ ?WARNING_MSG("Module ~ts is deprecated and was automatically "
+ "removed from the configuration. ~ts", [Mod, adjust_hint()]).
warn_replaced_handler(Opt, {Path, Module}) ->
- ?WARNING_MSG("Listening option '~s' is deprecated "
+ ?WARNING_MSG("Listening option '~ts' is deprecated "
"and was automatically replaced by "
- "HTTP request handler: \"~s\" -> ~s. ~s",
+ "HTTP request handler: \"~ts\" -> ~ts. ~ts",
[Opt, Path, Module, adjust_hint()]).
warn_deprecated_option(OldOpt, NewOpt) ->
- ?WARNING_MSG("Option '~s' is deprecated. Use option '~s' instead.",
+ ?WARNING_MSG("Option '~ts' is deprecated. Use option '~ts' instead.",
[OldOpt, NewOpt]).
warn_replaced_option(OldOpt, NewOpt) ->
- ?WARNING_MSG("Option '~s' is deprecated and was automatically "
- "replaced by '~s'. ~s",
+ ?WARNING_MSG("Option '~ts' is deprecated and was automatically "
+ "replaced by '~ts'. ~ts",
[OldOpt, NewOpt, adjust_hint()]).
warn_removed_option(Opt) ->
- ?WARNING_MSG("Option '~s' is deprecated and has no effect anymore. "
+ ?WARNING_MSG("Option '~ts' is deprecated and has no effect anymore. "
"Please remove it from the configuration.", [Opt]).
warn_removed_option(OldOpt, NewOpt) ->
- ?WARNING_MSG("Option '~s' is deprecated and has no effect anymore. "
- "Use option '~s' instead.", [OldOpt, NewOpt]).
+ ?WARNING_MSG("Option '~ts' is deprecated and has no effect anymore. "
+ "Use option '~ts' instead.", [OldOpt, NewOpt]).
warn_removed_module_option(Opt, Mod) ->
- ?WARNING_MSG("Option '~s' of module ~s is deprecated "
- "and has no effect anymore. ~s",
+ ?WARNING_MSG("Option '~ts' of module ~ts is deprecated "
+ "and has no effect anymore. ~ts",
[Opt, Mod, adjust_hint()]).
warn_huge_timeout(Opt, T) when is_integer(T), T >= 1000 ->
- ?WARNING_MSG("Value '~B' of option '~s' is too big, "
+ ?WARNING_MSG("Value '~B' of option '~ts' is too big, "
"are you sure you have set seconds?",
[T, Opt]);
warn_huge_timeout(_, _) ->
false ->
EjabberdLogPath = ejabberd_logger:get_log_path(),
print("ejabberd is not running in that node~n"
- "Check for error messages: ~s~n"
+ "Check for error messages: ~ts~n"
"or other files in that directory.~n", [EjabberdLogPath]),
?STATUS_ERROR;
true ->
- print("ejabberd ~s is running in that node~n", [ejabberd_option:version()]),
+ print("ejabberd ~ts is running in that node~n", [ejabberd_option:version()]),
?STATUS_SUCCESS
end;
case String of
[] -> ok;
_ ->
- io:format("~s~n", [String])
+ io:format("~ts~n", [String])
end,
Code.
KnownCommands = [Cmd || {Cmd, _, _} <- ejabberd_commands:list_commands(Version)],
UnknownCommand = list_to_atom(hd(Args)),
{io_lib:format(
- "Error: unknown command '~s'. Did you mean '~s'?",
+ "Error: unknown command '~ts'. Did you mean '~ts'?",
[hd(Args), misc:best_match(UnknownCommand, KnownCommands)]),
?STATUS_ERROR};
throw:Error ->
{io_lib:format("~p", [Error]), ?STATUS_ERROR};
?EX_RULE(A, Why, Stack) ->
StackTrace = ?EX_STACK(Stack),
- {io_lib:format("Unhandled exception occurred executing the command:~n** ~s",
+ {io_lib:format("Unhandled exception occurred executing the command:~n** ~ts",
[misc:format_exception(2, A, Why, StackTrace)]),
?STATUS_ERROR}
end.
{L1, L2} when L1 < L2 -> {L2-L1, "less argument"};
{L1, L2} when L1 > L2 -> {L1-L2, "more argument"}
end,
- {io_lib:format("Error: the command ~p requires ~p ~s.",
+ {io_lib:format("Error: the command ~p requires ~p ~ts.",
[CmdString, NumCompa, TextCompa]),
wrong_command_arguments}
end.
io_lib:format("~p", [Int]);
format_result([A|_]=String, {_Name, string}) when is_list(String) and is_integer(A) ->
- io_lib:format("~s", [String]);
+ io_lib:format("~ts", [String]);
format_result(Binary, {_Name, string}) when is_binary(Binary) ->
- io_lib:format("~s", [binary_to_list(Binary)]);
+ io_lib:format("~ts", [binary_to_list(Binary)]);
format_result(Atom, {_Name, string}) when is_atom(Atom) ->
- io_lib:format("~s", [atom_to_list(Atom)]);
+ io_lib:format("~ts", [atom_to_list(Atom)]);
format_result(Integer, {_Name, string}) when is_integer(Integer) ->
- io_lib:format("~s", [integer_to_list(Integer)]);
+ io_lib:format("~ts", [integer_to_list(Integer)]);
format_result(Other, {_Name, string}) ->
io_lib:format("~p", [Other]);
make_status(Code);
format_result({Code, Text}, {_Name, restuple}) ->
- {io_lib:format("~s", [Text]), make_status(Code)};
+ {io_lib:format("~ts", [Text]), make_status(Code)};
%% The result is a list of something: [something()]
format_result([], {_Name, {list, _ElementsDef}}) ->
Stack = ?EX_STACK(St),
?ERROR_MSG("Hook ~p crashed when running ~p:~p/~p:~n" ++
string:join(
- ["** ~s"|
+ ["** ~ts"|
["** Arg " ++ integer_to_list(I) ++ " = ~p"
|| I <- lists:seq(1, length(Args))]],
"~n"),
end
catch _:{case_clause, {error, Why}} ->
if Why /= closed ->
- ?WARNING_MSG("Failed to read ~s: ~s",
+ ?WARNING_MSG("Failed to read ~ts: ~ts",
[FileName, file_format_error(Why)]),
exit(normal);
true ->
{ok, IPFirst} = inet_parse:address(
binary_to_list(ClientIP)),
?DEBUG("The IP ~w was replaced with ~w due to "
- "header X-Forwarded-For: ~s",
+ "header X-Forwarded-For: ~ts",
[IPLast, IPFirst, XFF]),
IPFirst;
false -> IPLast
none;
{error, Why} ->
Reason = file_format_error(Why),
- ?ERROR_MSG("Failed to open ~s: ~s", [FileName, Reason]),
+ ?ERROR_MSG("Failed to open ~ts: ~ts", [FileName, Reason]),
make_text_output(State, 404, Reason, [], <<>>)
end;
{error, Why} ->
Reason = file_format_error(Why),
- ?ERROR_MSG("Failed to read info of ~s: ~s", [FileName, Reason]),
+ ?ERROR_MSG("Failed to read info of ~ts: ~ts", [FileName, Reason]),
make_text_output(State, 404, Reason, [], <<>>)
end.
try Fun(IQRes)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to process iq response:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to process iq response:~n~ts~n** ~ts",
[xmpp:pp(IQRes),
misc:format_exception(2, Class, Reason, StackTrace)])
end;
proc_lib:init_ack({ok, self()}),
case application:ensure_started(ejabberd) of
ok ->
- ?INFO_MSG("Start accepting ~s connections at ~s for ~p",
+ ?INFO_MSG("Start accepting ~ts connections at ~ts for ~p",
[format_transport(udp, Opts),
format_endpoint({Port1, Addr, udp}), Module]),
Opts1 = opts_to_list(Module, Opts),
Sup = start_module_sup(Module, Opts),
Interval = maps:get(accept_interval, Opts),
Proxy = maps:get(use_proxy_protocol, Opts),
- ?INFO_MSG("Start accepting ~s connections at ~s for ~p",
+ ?INFO_MSG("Start accepting ~ts connections at ~ts for ~p",
[format_transport(tcp, Opts),
format_endpoint({Port1, Addr, tcp}), Module]),
Opts1 = opts_to_list(Module, Opts),
{ok, Socket} when Proxy ->
case proxy_protocol:decode(gen_tcp, Socket, 10000) of
{error, Err} ->
- ?ERROR_MSG("(~w) Proxy protocol parsing failed: ~s",
+ ?ERROR_MSG("(~w) Proxy protocol parsing failed: ~ts",
[ListenSocket, format_error(Err)]),
gen_tcp:close(Socket);
{{Addr, Port}, {PAddr, PPort}} = SP ->
gen_tcp:close(Socket),
none
end,
- ?INFO_MSG("(~p) Accepted proxied connection ~s -> ~s",
+ ?INFO_MSG("(~p) Accepted proxied connection ~ts -> ~ts",
[Receiver,
ejabberd_config:may_hide_data(
format_endpoint({PPort, PAddr, tcp})),
gen_tcp:close(Socket),
none
end,
- ?INFO_MSG("(~p) Accepted connection ~s -> ~s",
+ ?INFO_MSG("(~p) Accepted connection ~ts -> ~ts",
[Receiver,
ejabberd_config:may_hide_data(
format_endpoint({PPort, PAddr, tcp})),
end,
accept(ListenSocket, Module, State, Sup, NewInterval, Proxy, Arity);
{error, Reason} ->
- ?ERROR_MSG("(~w) Failed TCP accept: ~s",
+ ?ERROR_MSG("(~w) Failed TCP accept: ~ts",
[ListenSocket, format_error(Reason)]),
accept(ListenSocket, Module, State, Sup, NewInterval, Proxy, Arity)
end.
udp_recv(Socket, Module, NewState)
end;
{error, Reason} ->
- ?ERROR_MSG("Unexpected UDP error: ~s", [format_error(Reason)]),
+ ?ERROR_MSG("Unexpected UDP error: ~ts", [format_error(Reason)]),
throw({error, Reason})
end.
stop_listener({_, _, Transport} = EndPoint, Module, Opts) ->
case supervisor:terminate_child(?MODULE, EndPoint) of
ok ->
- ?INFO_MSG("Stop accepting ~s connections at ~s for ~p",
+ ?INFO_MSG("Stop accepting ~ts connections at ~ts for ~p",
[format_transport(Transport, Opts),
format_endpoint(EndPoint), Module]),
ets:delete(?MODULE, EndPoint),
-spec report_socket_error(inet:posix(), endpoint(), module()) -> ok.
report_socket_error(Reason, EndPoint, Module) ->
- ?ERROR_MSG("Failed to open socket at ~s for ~s: ~s",
+ ?ERROR_MSG("Failed to open socket at ~ts for ~ts: ~ts",
[format_endpoint(EndPoint), Module, format_error(Reason)]).
-spec format_error(inet:posix() | atom()) -> string().
-spec route(stanza()) -> ok.
route(Packet) ->
- ?DEBUG("Local route:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Local route:~n~ts", [xmpp:pp(Packet)]),
Type = xmpp:get_type(Packet),
To = xmpp:get_to(Packet),
if To#jid.luser /= <<"">> ->
undefined ->
Default;
{ok, Junk} ->
- error_logger:error_msg("wrong value for ~s: ~p; "
+ error_logger:error_msg("wrong value for ~ts: ~p; "
"using ~p as a fallback~n",
[Name, Junk, Default]),
Default
undefined ->
Default;
{ok, Junk} ->
- error_logger:error_msg("wrong value for ~s: ~p; "
+ error_logger:error_msg("wrong value for ~ts: ~p; "
"using ~p as a fallback~n",
[Name, Junk, Default]),
Default
Schema = read_schema_file(),
{ok, #state{schema = Schema}};
false ->
- ?CRITICAL_MSG("Node name mismatch: I'm [~s], "
+ ?CRITICAL_MSG("Node name mismatch: I'm [~ts], "
"the database is owned by ~p", [MyNode, DbNodes]),
?CRITICAL_MSG("Either set ERLANG_NODE in ejabberdctl.cfg "
"or change node name in Mnesia", []),
end.
reset(Name, TabDef) ->
- ?INFO_MSG("Deleting Mnesia table '~s'", [Name]),
+ ?INFO_MSG("Deleting Mnesia table '~ts'", [Name]),
mnesia_op(delete_table, [Name]),
create(Name, TabDef).
[] -> CurrType
end,
if NewType /= CurrType ->
- ?INFO_MSG("Changing Mnesia table '~s' from ~s to ~s",
+ ?INFO_MSG("Changing Mnesia table '~ts' from ~ts to ~ts",
[Name, CurrType, NewType]),
mnesia_op(change_table_copy_type, [Name, node(), NewType]);
true ->
end.
delete_indexes(Name, [Index|Indexes]) ->
- ?INFO_MSG("Deleting index '~s' from Mnesia table '~s'", [Index, Name]),
+ ?INFO_MSG("Deleting index '~ts' from Mnesia table '~ts'", [Index, Name]),
case mnesia_op(del_table_index, [Name, Index]) of
{atomic, ok} ->
delete_indexes(Name, Indexes);
{atomic, ok}.
add_indexes(Name, [Index|Indexes]) ->
- ?INFO_MSG("Adding index '~s' to Mnesia table '~s'", [Index, Name]),
+ ?INFO_MSG("Adding index '~ts' to Mnesia table '~ts'", [Index, Name]),
case mnesia_op(add_table_index, [Name, Index]) of
{atomic, ok} ->
add_indexes(Name, Indexes);
case lists:keyfind(Name, 1, Schema) of
{_, Custom} ->
TabDefs = merge(Custom, Default),
- ?DEBUG("Using custom schema for table '~s': ~p",
+ ?DEBUG("Using custom schema for table '~ts': ~p",
[Name, TabDefs]),
TabDefs;
false ->
{ok, Y} ->
case econf:validate(validator(), lists:flatten(Y)) of
{ok, []} ->
- ?WARNING_MSG("Mnesia schema file ~s is empty", [File]),
+ ?WARNING_MSG("Mnesia schema file ~ts is empty", [File]),
[];
{ok, Config} ->
lists:map(
end, Opts)}
end, Config);
{error, Reason, Ctx} ->
- ?ERROR_MSG("Failed to read Mnesia schema from ~s: ~s",
+ ?ERROR_MSG("Failed to read Mnesia schema from ~ts: ~ts",
[File, econf:format_error(Reason, Ctx)]),
[]
end;
{error, enoent} ->
- ?DEBUG("No custom Mnesia schema file found at ~s", [File]),
+ ?DEBUG("No custom Mnesia schema file found at ~ts", [File]),
[];
{error, Reason} ->
- ?ERROR_MSG("Failed to read Mnesia schema file ~s: ~s",
+ ?ERROR_MSG("Failed to read Mnesia schema file ~ts: ~ts",
[File, fast_yaml:format_error(Reason)])
end.
({disc_only_copies, _}, _) -> " disc_only ";
(_, Acc) -> Acc
end, " ", TabDef),
- ?INFO_MSG("Creating Mnesia~stable '~s'", [Type, Name]),
+ ?INFO_MSG("Creating Mnesia~tstable '~ts'", [Type, Name]),
case mnesia_op(create_table, [Name, TabDef]) of
{atomic, ok} ->
add_table_copy(Name);
transform(Module, Name, Attrs, Attrs) ->
case need_transform(Module, Name) of
true ->
- ?INFO_MSG("Transforming table '~s', this may take a while", [Name]),
+ ?INFO_MSG("Transforming table '~ts', this may take a while", [Name]),
transform_table(Module, Name);
false ->
{atomic, ok}
try Module:transform(Obj)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to transform Mnesia table ~s:~n"
+ ?ERROR_MSG("Failed to transform Mnesia table ~ts:~n"
"** Record: ~p~n"
- "** ~s",
+ "** ~ts",
[Name, Obj,
misc:format_exception(2, Class, Reason, StackTrace)]),
erlang:raise(Class, Reason, StackTrace)
{atomic, ok} ->
{atomic, ok};
Other ->
- ?ERROR_MSG("Failure on mnesia ~s ~p: ~p",
+ ?ERROR_MSG("Failure on mnesia ~ts ~p: ~p",
[Fun, Args, Other]),
Other
end.
end, mnesia:system_info(tables)),
case file:write_file(File, [fast_yaml:encode(Schema), io_lib:nl()]) of
ok ->
- io:format("Mnesia schema is written to ~s~n", [File]);
+ io:format("Mnesia schema is written to ~ts~n", [File]);
{error, Reason} ->
- io:format("Failed to write Mnesia schema to ~s: ~s",
+ io:format("Failed to write Mnesia schema to ~ts: ~ts",
[File, file:format_error(Reason)])
end.
transform_globals(Opt, Opts) when Opt == override_global;
Opt == override_local;
Opt == override_acls ->
- ?WARNING_MSG("Option '~s' has no effect anymore", [Opt]),
+ ?WARNING_MSG("Option '~ts' has no effect anymore", [Opt]),
Opts;
transform_globals({node_start, _}, Opts) ->
?WARNING_MSG("Option 'node_start' has no effect anymore", []),
Res;
{error, Reason} ->
ErrTxt = file:format_error(Reason),
- ?ERROR_MSG("Failed to open file '~s': ~s", [FileName, ErrTxt]),
+ ?ERROR_MSG("Failed to open file '~ts': ~ts", [FileName, ErrTxt]),
{error, Reason}
end.
end, ok, FilesAndHosts);
{error, Reason} ->
ErrTxt = file:format_error(Reason),
- ?ERROR_MSG("Failed to open file '~s': ~s", [DFn, ErrTxt]),
+ ?ERROR_MSG("Failed to open file '~ts': ~ts", [DFn, ErrTxt]),
{error, Reason}
end.
end;
{error, Reason} ->
ErrTxt = file:format_error(Reason),
- ?ERROR_MSG("Failed to open file '~s': ~s", [DFn, ErrTxt]),
+ ?ERROR_MSG("Failed to open file '~ts': ~ts", [DFn, ErrTxt]),
{error, Reason}
end.
?NS_PIE ->
{ok, State};
NS ->
- stop("Unknown 'server-data' namespace = ~s", [NS])
+ stop("Unknown 'server-data' namespace = ~ts", [NS])
end;
process_el({xmlstreamend, _}, State) ->
{ok, State};
true ->
process_users(Els, State#state{server = S});
false ->
- stop("Unknown host: ~s", [S])
+ stop("Unknown host: ~ts", [S])
end
catch _:{bad_jid, _} ->
- stop("Invalid 'jid': ~s", [JIDS])
+ stop("Invalid 'jid': ~ts", [JIDS])
end;
process_el({xmlstreamstart, <<"user">>, Attrs}, State = #state{server = S})
when S /= <<"">> ->
case jid:nodeprep(Name) of
error ->
- stop("Invalid 'user': ~s", [Name]);
+ stop("Invalid 'user': ~ts", [Name]);
LUser ->
case ejabberd_auth:try_register(LUser, LServer, Pass) of
ok ->
{error, invalid_password} when (Password == <<>>) ->
process_user_els(Els, State#state{user = LUser});
{error, Err} ->
- stop("Failed to create user '~s': ~p", [Name, Err])
+ stop("Failed to create user '~ts': ~p", [Name, Err])
end
end.
end
catch _:{xmpp_codec, Why} ->
ErrTxt = xmpp:format_error(Why),
- stop("failed to decode XML '~s': ~s",
+ stop("failed to decode XML '~ts': ~ts",
[fxml:element_to_binary(El), ErrTxt])
end.
%% @spec () -> string()
make_piefxis_server_head() ->
- io_lib:format("<server-data xmlns='~s' xmlns:xi='~s'>",
+ io_lib:format("<server-data xmlns='~ts' xmlns:xi='~ts'>",
[?NS_PIE, ?NS_XI]).
%% @spec () -> string()
%% @spec (Host::string()) -> string()
make_piefxis_host_head(Host) ->
- io_lib:format("<host xmlns='~s' xmlns:xi='~s' jid='~s'>",
+ io_lib:format("<host xmlns='~ts' xmlns:xi='~ts' jid='~ts'>",
[?NS_PIE, ?NS_XI, Host]).
%% @spec () -> string()
%% @spec (Fn::string()) -> string()
make_xinclude(Fn) ->
Base = filename:basename(Fn),
- io_lib:format("<xi:include href='~s'/>", [Base]).
+ io_lib:format("<xi:include href='~ts'/>", [Base]).
print(Fd, String) ->
file:write(Fd, String).
case pkix:is_pem_file(Path) of
true -> Path;
{false, Reason} ->
- ?ERROR_MSG("Failed to read PEM file ~s: ~s",
+ ?ERROR_MSG("Failed to read PEM file ~ts: ~ts",
[Path, pkix:format_error(Reason)]),
erlang:error(badarg)
end.
cert_expired(_Cert, #{domains := Domains,
expiry := Expiry,
files := [{Path, Line}|_]}) ->
- ?WARNING_MSG("Certificate in ~s (at line: ~B)~s ~s",
+ ?WARNING_MSG("Certificate in ~ts (at line: ~B)~ts ~ts",
[Path, Line,
case Domains of
[] -> "";
case pkix:add_file(File) of
ok -> ok;
{error, Reason} = Err ->
- ?ERROR_MSG("Failed to read PEM file ~s: ~s",
+ ?ERROR_MSG("Failed to read PEM file ~ts: ~ts",
[File, pkix:format_error(Reason)]),
Err
end.
-spec do_commit() -> {ok, [{filename(), pkix:error_reason()}]} | error.
do_commit() ->
CAFile = ejabberd_option:ca_file(),
- ?DEBUG("Using CA root certificates from: ~s", [CAFile]),
+ ?DEBUG("Using CA root certificates from: ~ts", [CAFile]),
Opts = [{cafile, CAFile},
{notify_before, [7*24*60*60, % 1 week
24*60*60, % 1 day
fast_tls_add_certfiles(),
{ok, Errors};
{error, File, Reason} ->
- ?CRITICAL_MSG("Failed to write to ~s: ~s",
+ ?CRITICAL_MSG("Failed to write to ~ts: ~ts",
[File, file:format_error(Reason)]),
error
end.
case get_certfile_no_default(Host) of
error ->
?WARNING_MSG(
- "No certificate found matching ~s",
+ "No certificate found matching ~ts",
[Host]);
_ ->
ok
{ok, CWD} ->
unicode:characters_to_binary(filename:join(CWD, Path0));
{error, Reason} ->
- ?WARNING_MSG("Failed to get current directory name: ~s",
+ ?WARNING_MSG("Failed to get current directory name: ~ts",
[file:format_error(Reason)]),
unicode:characters_to_binary(Path0)
end;
wildcard(Path) ->
case filelib:wildcard(Path) of
[] ->
- ?WARNING_MSG("Path ~s is empty, please make sure ejabberd has "
+ ?WARNING_MSG("Path ~ts is empty, please make sure ejabberd has "
"sufficient rights to read it", [Path]),
[];
Files ->
fast_tls:clear_cache().
reason_to_fmt({invalid_cert, _, _}) ->
- "Invalid certificate in ~s: ~s";
+ "Invalid certificate in ~ts: ~ts";
reason_to_fmt(_) ->
- "Failed to read PEM file ~s: ~s".
+ "Failed to read PEM file ~ts: ~ts".
-spec log_warnings([{filename(), pkix:error_reason()}]) -> ok.
log_warnings(Warnings) ->
-spec log_cafile_error({filename(), pkix:error_reason()} | undefined) -> ok.
log_cafile_error({File, Reason}) ->
- ?CRITICAL_MSG("Failed to read CA certitificates from ~s: ~s. "
+ ?CRITICAL_MSG("Failed to read CA certitificates from ~ts: ~ts. "
"Try to change/set option 'ca_file'",
[File, pkix:format_error(Reason)]);
log_cafile_error(_) ->
case maps:is_key(Channel, State#state.subscriptions) of
true -> eredis_sub:ack_message(Pid);
false ->
- ?WARNING_MSG("Got subscription ack for unknown channel ~s",
+ ?WARNING_MSG("Got subscription ack for unknown channel ~ts",
[Channel])
end;
_ ->
ConnTimeout = ejabberd_option:redis_connect_timeout(),
try case do_connect(Num, Server, Port, Pass, DB, ConnTimeout) of
{ok, Client} ->
- ?DEBUG("Connection #~p established to Redis at ~s:~p",
+ ?DEBUG("Connection #~p established to Redis at ~ts:~p",
[Num, Server, Port]),
register(get_connection(Num), Client),
{ok, Client};
catch _:Reason ->
Timeout = p1_rand:uniform(
min(10, ejabberd_redis_sup:get_pool_size())),
- ?ERROR_MSG("Redis connection #~p at ~s:~p has failed: ~p; "
+ ?ERROR_MSG("Redis connection #~p at ~ts:~p has failed: ~p; "
"reconnecting in ~p seconds",
[Num, Server, Port, Reason, Timeout]),
erlang:send_after(timer:seconds(Timeout), self(), connect),
log_error(Cmd, Reason) ->
?ERROR_MSG("Redis request has failed:~n"
"** request = ~p~n"
- "** response = ~s",
+ "** response = ~ts",
[Cmd, format_error(Reason)]).
-spec get_rnd_id() -> pos_integer().
{ok, _} -> ok;
{error, {already_started, _}} -> ok;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to start ~s: ~p", [?MODULE, Why]),
+ ?ERROR_MSG("Failed to start ~ts: ~p", [?MODULE, Why]),
Err
end
end.
try do_route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end.
Pkt -> route(From, To, Pkt)
catch _:{xmpp_codec, Why} ->
?ERROR_MSG("Failed to decode xml element ~p when "
- "routing from ~s to ~s: ~s",
+ "routing from ~ts to ~ts: ~ts",
[El, jid:encode(From), jid:encode(To),
xmpp:format_error(Why)])
end;
case Mod:register_route(LDomain, LServerHost, LocalHint,
get_component_number(LDomain), Pid) of
ok ->
- ?DEBUG("Route registered: ~s", [LDomain]),
+ ?DEBUG("Route registered: ~ts", [LDomain]),
monitor_route(LDomain, Pid),
ejabberd_hooks:run(route_registered, [LDomain]),
delete_cache(Mod, LDomain);
{error, Err} ->
- ?ERROR_MSG("Failed to register route ~s: ~p",
+ ?ERROR_MSG("Failed to register route ~ts: ~p",
[LDomain, Err])
end
end.
case Mod:unregister_route(
LDomain, get_component_number(LDomain), Pid) of
ok ->
- ?DEBUG("Route unregistered: ~s", [LDomain]),
+ ?DEBUG("Route unregistered: ~ts", [LDomain]),
demonitor_route(LDomain, Pid),
ejabberd_hooks:run(route_unregistered, [LDomain]),
delete_cache(Mod, LDomain);
{error, Err} ->
- ?ERROR_MSG("Failed to unregister route ~s: ~p",
+ ?ERROR_MSG("Failed to unregister route ~ts: ~p",
[LDomain, Err])
end
end.
handle_info({'DOWN', MRef, _, Pid, Info}, State) ->
MRefs = maps:filter(
fun({Domain, P}, M) when P == Pid, M == MRef ->
- ?DEBUG("Process ~p with route registered to ~s "
+ ?DEBUG("Process ~p with route registered to ~ts "
"has terminated unexpectedly with reason: ~p",
[P, Domain, Info]),
try unregister_route(Domain, Pid)
%%--------------------------------------------------------------------
-spec do_route(stanza()) -> ok.
do_route(OrigPacket) ->
- ?DEBUG("Route:~n~s", [xmpp:pp(OrigPacket)]),
+ ?DEBUG("Route:~n~ts", [xmpp:pp(OrigPacket)]),
case ejabberd_hooks:run_fold(filter_packet, OrigPacket, []) of
drop ->
ok;
%% Destinations = [#jid]
-spec do_route(binary(), [jid()], stanza()) -> any().
do_route(Domain, Destinations, Packet) ->
- ?DEBUG("Route multicast:~n~s~nDomain: ~s~nDestinations: ~s~n",
+ ?DEBUG("Route multicast:~n~ts~nDomain: ~ts~nDestinations: ~ts~n",
[xmpp:pp(Packet), Domain,
str:join([jid:encode(To) || To <- Destinations], <<", ">>)]),
%% Try to find an appropriate multicast service
StackTrace = ?EX_STACK(St),
?ERROR_MSG("Failed to decode row from 'route' table:~n"
"** Row = ~p~n"
- "** Domain = ~s~n"
- "** ~s",
+ "** Domain = ~ts~n"
+ "** ~ts",
[Row, Domain,
misc:format_exception(2, Class, Reason, StackTrace)]),
[]
-spec external_host_overloaded(binary()) -> {aborted, any()} | {atomic, ok}.
external_host_overloaded(Host) ->
- ?INFO_MSG("Disabling s2s connections to ~s for ~p seconds",
+ ?INFO_MSG("Disabling s2s connections to ~ts for ~p seconds",
[Host, ?S2S_OVERLOAD_BLOCK_PERIOD]),
mnesia:transaction(fun () ->
Time = erlang:monotonic_time(),
case mnesia:transaction(F) of
{atomic, _} -> ok;
{aborted, Reason} ->
- ?ERROR_MSG("Failed to unregister s2s connection ~s -> ~s: "
+ ?ERROR_MSG("Failed to unregister s2s connection ~ts -> ~ts: "
"Mnesia failure: ~p",
[From, To, Reason])
end;
case mnesia:transaction(F) of
{atomic, Res} -> Res;
{aborted, Reason} ->
- ?ERROR_MSG("Failed to register s2s connection ~s -> ~s: "
+ ?ERROR_MSG("Failed to register s2s connection ~ts -> ~ts: "
"Mnesia failure: ~p",
[From, To, Reason]),
false
try route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
-spec route(stanza()) -> ok.
route(Packet) ->
- ?DEBUG("Local route:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Local route:~n~ts", [xmpp:pp(Packet)]),
From = xmpp:get_from(Packet),
To = xmpp:get_to(Packet),
case start_connection(From, To) of
end,
[Pid1];
{aborted, Reason} ->
- ?ERROR_MSG("Failed to register s2s connection ~s -> ~s: "
+ ?ERROR_MSG("Failed to register s2s connection ~ts -> ~ts: "
"Mnesia failure: ~p",
[MyServer, Server, Reason]),
ejabberd_s2s_out:stop(Pid),
#{ip := IP} ->
ejabberd_config:may_hide_data(misc:ip_to_list(IP))
end,
- ?INFO_MSG("Closing inbound s2s connection ~s -> ~s: ~s",
+ ?INFO_MSG("Closing inbound s2s connection ~ts -> ~ts: ~ts",
[RServer, LServer, xmpp_stream_out:format_error(Reason)]),
stop(State).
auth_domains := AuthDomains,
server_host := ServerHost,
lserver := LServer} = State) ->
- ?INFO_MSG("(~s) Accepted inbound s2s ~s authentication ~s -> ~s (~s)",
+ ?INFO_MSG("(~ts) Accepted inbound s2s ~ts authentication ~ts -> ~ts (~ts)",
[xmpp_socket:pp(Socket), Mech, RServer, LServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
State1 = case ejabberd_s2s:allow_host(ServerHost, RServer) of
#{socket := Socket, ip := IP,
server_host := ServerHost,
lserver := LServer} = State) ->
- ?WARNING_MSG("(~s) Failed inbound s2s ~s authentication ~s -> ~s (~s): ~s",
+ ?WARNING_MSG("(~ts) Failed inbound s2s ~ts authentication ~ts -> ~ts (~ts): ~ts",
[xmpp_socket:pp(Socket), Mech, RServer, LServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP)), Reason]),
ejabberd_hooks:run_fold(s2s_in_auth_result,
socket := Socket} = State) ->
case maps:get(stop_reason, State, undefined) of
{tls, _} = Err ->
- ?WARNING_MSG("(~s) Failed to secure inbound s2s connection: ~s",
+ ?WARNING_MSG("(~ts) Failed to secure inbound s2s connection: ~ts",
[xmpp_socket:pp(Socket), xmpp_stream_in:format_error(Err)]);
_ ->
ok
process_auth_result(#{server := LServer, remote_server := RServer} = State,
{false, Reason}) ->
Delay = get_delay(),
- ?WARNING_MSG("Failed to establish outbound s2s connection ~s -> ~s: "
+ ?WARNING_MSG("Failed to establish outbound s2s connection ~ts -> ~ts: "
"authentication failed; bouncing for ~p seconds",
[LServer, RServer, Delay div 1000]),
State1 = State#{on_route => bounce, stop_reason => Reason},
process_closed(#{server := LServer, remote_server := RServer,
on_route := send} = State,
Reason) ->
- ?INFO_MSG("Closing outbound s2s connection ~s -> ~s: ~s",
+ ?INFO_MSG("Closing outbound s2s connection ~ts -> ~ts: ~ts",
[LServer, RServer, format_error(Reason)]),
stop(State);
process_closed(#{server := LServer, remote_server := RServer} = State,
Reason) ->
Delay = get_delay(),
- ?WARNING_MSG("Failed to establish outbound s2s connection ~s -> ~s: ~s; "
+ ?WARNING_MSG("Failed to establish outbound s2s connection ~ts -> ~ts: ~ts; "
"bouncing for ~p seconds",
[LServer, RServer, format_error(Reason), Delay div 1000]),
State1 = State#{on_route => bounce},
remote_server := RServer,
server_host := ServerHost,
server := LServer} = State) ->
- ?INFO_MSG("(~s) Accepted outbound s2s ~s authentication ~s -> ~s (~s)",
+ ?INFO_MSG("(~ts) Accepted outbound s2s ~ts authentication ~ts -> ~ts (~ts)",
[xmpp_socket:pp(Socket), Mech, LServer, RServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
ejabberd_hooks:run_fold(s2s_out_auth_result, ServerHost, State, [true]).
remote_server := RServer,
server_host := ServerHost,
server := LServer} = State) ->
- ?WARNING_MSG("(~s) Failed outbound s2s ~s authentication ~s -> ~s (~s): ~s",
+ ?WARNING_MSG("(~ts) Failed outbound s2s ~ts authentication ~ts -> ~ts (~ts): ~ts",
[xmpp_socket:pp(Socket), Mech, LServer, RServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP)),
xmpp_stream_out:format_error(Reason)]),
server_host => ServerHost,
shaper => none},
State2 = xmpp_stream_out:set_timeout(State1, Timeout),
- ?INFO_MSG("Outbound s2s connection started: ~s -> ~s",
+ ?INFO_MSG("Outbound s2s connection started: ~ts -> ~ts",
[LServer, RServer]),
ejabberd_hooks:run_fold(s2s_out_init, ServerHost, {ok, State2}, [Opts]).
Pids = ejabberd_s2s:get_connections_pids(FromTo),
case lists:member(self(), Pids) of
true ->
- ?WARNING_MSG("Outgoing s2s connection ~s -> ~s is supposed "
+ ?WARNING_MSG("Outgoing s2s connection ~ts -> ~ts is supposed "
"to be unregistered, but pid ~p still presents "
"in 's2s' table", [LServer, RServer, self()]),
State;
{ok, Password} ->
{Password, undefined};
error ->
- ?WARNING_MSG("(~s) Domain ~s is unconfigured for "
- "external component from ~s",
+ ?WARNING_MSG("(~ts) Domain ~ts is unconfigured for "
+ "external component from ~ts",
[xmpp_socket:pp(Socket), RemoteServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
{false, undefined}
#{remote_server := RemoteServer, host_opts := HostOpts,
socket := Socket, ip := IP,
global_routes := GlobalRoutes} = State) ->
- ?INFO_MSG("(~s) Accepted external component ~s authentication "
- "for ~s from ~s",
+ ?INFO_MSG("(~ts) Accepted external component ~ts authentication "
+ "for ~ts from ~ts",
[xmpp_socket:pp(Socket), Mech, RemoteServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
Routes = if GlobalRoutes ->
handle_auth_failure(_, Mech, Reason,
#{remote_server := RemoteServer,
socket := Socket, ip := IP} = State) ->
- ?WARNING_MSG("(~s) Failed external component ~s authentication "
- "for ~s from ~s: ~s",
+ ?WARNING_MSG("(~ts) Failed external component ~ts authentication "
+ "for ~ts from ~ts: ~ts",
[xmpp_socket:pp(Socket), Mech, RemoteServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP)),
Reason]),
econf:and_then(
econf:shaper(),
fun(S) ->
- ?WARNING_MSG("Listening option 'shaper_rule' of module ~s "
+ ?WARNING_MSG("Listening option 'shaper_rule' of module ~ts "
"is renamed to 'shaper'. Please adjust your "
"configuration", [?MODULE]),
S
update(none, _Size) -> {none, 0};
update(Shaper1, Size) ->
Shaper2 = p1_shaper:update(Shaper1, Size),
- ?DEBUG("Shaper update:~n~s =>~n~s",
+ ?DEBUG("Shaper update:~n~ts =>~n~ts",
[p1_shaper:pp(Shaper1), p1_shaper:pp(Shaper2)]),
Shaper2.
try {true, {maps:get(Name, Shapers), Rule}}
catch _:{badkey, _} ->
?WARNING_MSG(
- "Shaper rule '~s' refers to unknown shaper: ~s",
+ "Shaper rule '~ts' refers to unknown shaper: ~ts",
[ShaperRule, Name]),
false
end;
-include("logger.hrl").
-export([accept/1, start/3, start_link/3, listen_options/0]).
fail() ->
- ?CRITICAL_MSG("Listening module ~s is not available: "
+ ?CRITICAL_MSG("Listening module ~ts is not available: "
"ejabberd is not compiled with SIP support",
[?MODULE]),
erlang:error(sip_not_compiled).
try do_route(To, Term), ok
catch ?EX_RULE(E, R, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route term to ~s:~n"
+ ?ERROR_MSG("Failed to route term to ~ts:~n"
"** Term = ~p~n"
- "** ~s",
+ "** ~ts",
[jid:encode(To), Term,
misc:format_exception(2, E, R, StackTrace)])
end.
#jid{lserver = LServer} = xmpp:get_to(Packet),
case ejabberd_hooks:run_fold(sm_receive_packet, LServer, Packet, []) of
drop ->
- ?DEBUG("Hook dropped stanza:~n~s", [xmpp:pp(Packet)]);
+ ?DEBUG("Hook dropped stanza:~n~ts", [xmpp:pp(Packet)]);
Packet1 ->
do_route(Packet1),
ok
ejabberd_router:route_error(Packet, Err),
{stop, Acc};
bounce_sm_packet({_, Packet} = Acc) ->
- ?DEBUG("Dropping packet to unavailable resource:~n~s",
+ ?DEBUG("Dropping packet to unavailable resource:~n~ts",
[xmpp:pp(Packet)]),
Acc.
do_route(jid:replace_resource(To, R), Term)
end, get_user_resources(To#jid.user, To#jid.server));
do_route(To, Term) ->
- ?DEBUG("Broadcasting ~p to ~s", [Term, jid:encode(To)]),
+ ?DEBUG("Broadcasting ~p to ~ts", [Term, jid:encode(To)]),
{U, S, R} = jid:tolower(To),
Mod = get_sm_backend(S),
case get_sessions(Mod, U, S, R) of
-spec do_route(stanza()) -> any().
do_route(#presence{to = To, type = T} = Packet)
when T == subscribe; T == subscribed; T == unsubscribe; T == unsubscribed ->
- ?DEBUG("Processing subscription:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Processing subscription:~n~ts", [xmpp:pp(Packet)]),
#jid{luser = LUser, lserver = LServer} = To,
case is_privacy_allow(Packet) andalso
ejabberd_hooks:run_fold(
priority = Prio}) when is_integer(Prio) ->
Pid = element(2, SID),
Packet1 = Packet#presence{to = jid:replace_resource(To, R)},
- ?DEBUG("Sending to process ~p:~n~s",
+ ?DEBUG("Sending to process ~p:~n~ts",
[Pid, xmpp:pp(Packet1)]),
ejabberd_c2s:route(Pid, {route, Packet1});
(_) ->
ok
end;
do_route(#presence{to = #jid{lresource = <<"">>} = To} = Packet) ->
- ?DEBUG("Processing presence to bare JID:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Processing presence to bare JID:~n~ts", [xmpp:pp(Packet)]),
{LUser, LServer, _} = jid:tolower(To),
lists:foreach(
fun({_, R}) ->
do_route(Packet#presence{to = jid:replace_resource(To, R)})
end, get_user_present_resources(LUser, LServer));
do_route(#message{to = #jid{lresource = <<"">>} = To, type = T} = Packet) ->
- ?DEBUG("Processing message to bare JID:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Processing message to bare JID:~n~ts", [xmpp:pp(Packet)]),
if T == chat; T == headline; T == normal ->
route_message(Packet);
true ->
end;
do_route(#iq{to = #jid{lresource = <<"">>} = To, type = T} = Packet) ->
if T == set; T == get ->
- ?DEBUG("Processing IQ to bare JID:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Processing IQ to bare JID:~n~ts", [xmpp:pp(Packet)]),
gen_iq_handler:handle(?MODULE, Packet);
true ->
ejabberd_hooks:run_fold(bounce_sm_packet,
To#jid.lserver, {pass, Packet}, [])
end;
do_route(Packet) ->
- ?DEBUG("Processing packet to full JID:~n~s", [xmpp:pp(Packet)]),
+ ?DEBUG("Processing packet to full JID:~n~ts", [xmpp:pp(Packet)]),
To = xmpp:get_to(Packet),
{LUser, LServer, LResource} = jid:tolower(To),
Mod = get_sm_backend(LServer),
Ss ->
Session = lists:max(Ss),
Pid = element(2, Session#session.sid),
- ?DEBUG("Sending to process ~p:~n~s", [Pid, xmpp:pp(Packet)]),
+ ?DEBUG("Sending to process ~p:~n~ts", [Pid, xmpp:pp(Packet)]),
ejabberd_c2s:route(Pid, {route, Packet})
end.
V when V >= ?MIN_REDIS_VERSION ->
ejabberd_redis:script_load(Data);
V ->
- ?CRITICAL_MSG("Unsupported Redis version: ~s. "
- "The version must be ~s or above",
+ ?CRITICAL_MSG("Unsupported Redis version: ~ts. "
+ "The version must be ~ts or above",
[V, ?MIN_REDIS_VERSION]),
{error, unsupported_redis_version}
end;
Term
catch _:{badmatch, {error, {Line, Mod, Reason}, _}} ->
?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
- "** Scanner error: at line ~B: ~s~n"
- "** Term: ~s",
+ "** Scanner error: at line ~B: ~ts~n"
+ "** Term: ~ts",
[Line, Mod:format_error(Reason), Bin]),
erlang:error(badarg);
_:{badmatch, {error, {Line, Mod, Reason}}} ->
?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
- "** Parser error: at line ~B: ~s~n"
- "** Term: ~s",
+ "** Parser error: at line ~B: ~ts~n"
+ "** Term: ~ts",
[Line, Mod:format_error(Reason), Bin]),
erlang:error(badarg)
end.
{ok, Cwd} ->
filename:join([Cwd|Path]);
{error, Reason} ->
- ?ERROR_MSG("Failed to get current directory: ~s",
+ ?ERROR_MSG("Failed to get current directory: ~ts",
[file:format_error(Reason)]),
filename:join(Path)
end;
State#state.pending_requests)
catch error:full ->
Err = <<"SQL request queue is overfilled">>,
- ?ERROR_MSG("~s, bouncing all pending requests", [Err]),
+ ?ERROR_MSG("~ts, bouncing all pending requests", [Err]),
Q = p1_queue:dropwhile(
fun({sql_cmd, _, To, TS}) ->
reply(To, {error, Err}, TS),
?TOP_LEVEL_TXN ->
{backtrace, T} = process_info(self(), backtrace),
?ERROR_MSG("Inner transaction called at outer txn "
- "level. Trace: ~s",
+ "level. Trace: ~ts",
[T]),
erlang:exit(implementation_faulty);
_N -> ok
_N ->
{backtrace, T} = process_info(self(), backtrace),
?ERROR_MSG("Outer transaction called at inner txn "
- "level. Trace: ~s",
+ "level. Trace: ~ts",
[T]),
erlang:exit(implementation_faulty)
end,
{error, <<"shutdown">>};
?EX_RULE(Class, Reason, Stack) ->
StackTrace = ?EX_STACK(Stack),
- ?ERROR_MSG("Internal error while processing SQL query:~n** ~s",
+ ?ERROR_MSG("Internal error while processing SQL query:~n** ~ts",
[misc:format_exception(2, Class, Reason, StackTrace)]),
{error, <<"internal error">>}
end,
end;
sql_query_internal(Query) ->
State = get(?STATE_KEY),
- ?DEBUG("SQL: \"~s\"", [Query]),
+ ?DEBUG("SQL: \"~ts\"", [Query]),
QueryTimeout = query_timeout(State#state.host),
Res = case State#state.db_type of
odbc ->
pgsql:execute(State#state.db_ref, SQLQuery#sql_query.hash, Args),
% {T, ExecuteRes} =
% timer:tc(pgsql, execute, [State#state.db_ref, SQLQuery#sql_query.hash, Args]),
-% io:format("T ~s ~p~n", [SQLQuery#sql_query.hash, T]),
+% io:format("T ~ts ~p~n", [SQLQuery#sql_query.hash, T]),
Res = pgsql_execute_to_odbc(ExecuteRes),
sql_query_format_res(Res, SQLQuery).
?EX_RULE(Class, Reason, Stack) ->
StackTrace = ?EX_STACK(Stack),
?ERROR_MSG("Error while processing SQL query result:~n"
- "** Row: ~p~n** ~s",
+ "** Row: ~p~n** ~ts",
[Row,
misc:format_exception(2, Class, Reason, StackTrace)]),
[]
warn_if_ssl_unsupported(ssl, pgsql) ->
ok;
warn_if_ssl_unsupported(ssl, Type) ->
- ?WARNING_MSG("SSL connection is not supported for ~s", [Type]).
+ ?WARNING_MSG("SSL connection is not supported for ~ts", [Type]).
get_ssl_opts(ssl, Host) ->
Opts1 = case ejabberd_option:sql_ssl_certfile(Host) of
undefined -> <<"ejabberd">>;
D -> D
end,
- FreeTDS = io_lib:fwrite("[~s]~n"
- "\thost = ~s~n"
+ FreeTDS = io_lib:fwrite("[~ts]~n"
+ "\thost = ~ts~n"
"\tport = ~p~n"
"\tclient charset = UTF-8~n"
"\ttds version = 7.1~n",
"Setup = libtdsS.so~n"
"UsageCount = 1~n"
"FileUsage = 1~n", []),
- ODBCINI = io_lib:fwrite("[~s]~n"
+ ODBCINI = io_lib:fwrite("[~ts]~n"
"Description = MS SQL~n"
"Driver = freetds~n"
- "Servername = ~s~n"
- "Database = ~s~n"
+ "Servername = ~ts~n"
+ "Database = ~ts~n"
"Port = ~p~n",
[Host, Host, DB, Port]),
- ?DEBUG("~s:~n~s", [freetds_config(), FreeTDS]),
- ?DEBUG("~s:~n~s", [odbcinst_config(), ODBCINST]),
- ?DEBUG("~s:~n~s", [odbc_config(), ODBCINI]),
+ ?DEBUG("~ts:~n~ts", [freetds_config(), FreeTDS]),
+ ?DEBUG("~ts:~n~ts", [odbcinst_config(), ODBCINST]),
+ ?DEBUG("~ts:~n~ts", [odbc_config(), ODBCINI]),
case filelib:ensure_dir(freetds_config()) of
ok ->
try
os:putenv("FREETDSCONF", freetds_config()),
ok
catch error:{badmatch, {error, Reason} = Err} ->
- ?ERROR_MSG("Failed to create temporary files in ~s: ~s",
+ ?ERROR_MSG("Failed to create temporary files in ~ts: ~ts",
[tmp_dir(), file:format_error(Reason)]),
Err
end;
{error, Reason} = Err ->
- ?ERROR_MSG("Failed to create temporary directory ~s: ~s",
+ ?ERROR_MSG("Failed to create temporary directory ~ts: ~ts",
[tmp_dir(), file:format_error(Reason)]),
Err
end.
%% ***IMPORTANT*** This error format requires extended_errors turned on.
extended_error({"08S01", _, Reason}) ->
% TCP Provider: The specified network name is no longer available
- ?DEBUG("ODBC Link Failure: ~s", [Reason]),
+ ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
<<"Communication link failure">>;
extended_error({"08001", _, Reason}) ->
% Login timeout expired
- ?DEBUG("ODBC Connect Timeout: ~s", [Reason]),
+ ?DEBUG("ODBC Connect Timeout: ~ts", [Reason]),
<<"SQL connection failed">>;
extended_error({"IMC01", _, Reason}) ->
% The connection is broken and recovery is not possible
- ?DEBUG("ODBC Link Failure: ~s", [Reason]),
+ ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
<<"Communication link failure">>;
extended_error({"IMC06", _, Reason}) ->
% The connection is broken and recovery is not possible
- ?DEBUG("ODBC Link Failure: ~s", [Reason]),
+ ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
<<"Communication link failure">>;
extended_error({Code, _, Reason}) ->
- ?DEBUG("ODBC Error ~s: ~s", [Code, Reason]),
+ ?DEBUG("ODBC Error ~ts: ~ts", [Code, Reason]),
iolist_to_binary(Reason);
extended_error(Error) ->
Error.
Err;
check_error({error, Why}, #sql_query{} = Query) ->
Err = extended_error(Why),
- ?ERROR_MSG("SQL query '~s' at ~p failed: ~p",
+ ?ERROR_MSG("SQL query '~ts' at ~p failed: ~p",
[Query#sql_query.hash, Query#sql_query.loc, Err]),
{error, Err};
check_error({error, Why}, Query) ->
Err = extended_error(Why),
case catch iolist_to_binary(Query) of
SQuery when is_binary(SQuery) ->
- ?ERROR_MSG("SQL query '~s' failed: ~p", [SQuery, Err]);
+ ?ERROR_MSG("SQL query '~ts' failed: ~p", [SQuery, Err]);
_ ->
?ERROR_MSG("SQL query ~p failed: ~p", [Query, Err])
end,
{ok, _} -> ok;
{error, {already_started, _}} -> ok;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to start ~s: ~p", [?MODULE, Why]),
+ ?ERROR_MSG("Failed to start ~ts: ~p", [?MODULE, Why]),
Err
end
end.
[ok = sqlite3:sql_exec(DB, Q) || Q <- Qs],
ok = sqlite3:sql_exec(DB, "commit");
{error, Reason} ->
- ?WARNING_MSG("Failed to read SQLite schema file: ~s",
+ ?WARNING_MSG("Failed to read SQLite schema file: ~ts",
[file:format_error(Reason)])
end.
-include("logger.hrl").
-export([accept/1, start/3, start_link/3, listen_options/0]).
fail() ->
- ?CRITICAL_MSG("Listening module ~s is not available: "
+ ?CRITICAL_MSG("Listening module ~ts is not available: "
"ejabberd is not compiled with STUN/TURN support",
[?MODULE]),
erlang:error(stun_not_compiled).
"'auth_realm' is undefined and "
"'auth_type' is set to 'user', "
"most likely the TURN relay won't "
- "be working properly. Using ~s as "
+ "be working properly. Using ~ts as "
"a fallback", [ejabberd_config:get_myname()]);
true ->
ok
case proc_stat(Pid, get_app_pids()) of
#proc_stat{name = Name} = ProcStat ->
error_logger:warning_msg(
- "Process ~p consumes more than 5% of OS memory (~s)~n",
+ "Process ~p consumes more than 5% of OS memory (~ts)~n",
[Name, format_proc(ProcStat)]),
handle_overload(State),
{ok, State};
error_logger:warning_msg(
"The system is overloaded with ~b messages "
"queued by ~b process(es) (~b%) "
- "from the following applications: ~s; "
- "the top processes are:~n~s~n",
+ "from the following applications: ~ts; "
+ "the top processes are:~n~ts~n",
[TotalMsgs, ProcsNum,
round(ProcsNum*100/length(Procs)),
format_apps(Apps),
current_function = CurrFun, ancestors = Ancs,
application = App}) ->
io_lib:format(
- "msgs = ~b, memory = ~b, initial_call = ~s, "
- "current_function = ~s, ancestors = ~w, application = ~w",
+ "msgs = ~b, memory = ~b, initial_call = ~ts, "
+ "current_function = ~ts, ancestors = ~w, application = ~w",
[Len, Mem, format_mfa(InitCall), format_mfa(CurrFun), Ancs, App]).
-spec format_mfa(mfa()) -> iodata().
format_mfa({M, F, A}) when is_atom(M), is_atom(F), is_integer(A) ->
- io_lib:format("~s:~s/~b", [M, F, A]);
+ io_lib:format("~ts:~ts/~b", [M, F, A]);
format_mfa(WTF) ->
io_lib:format("~w", [WTF]).
"documentation with the environment variable "
"EJABBERD_DOC_PATH. Check the ejabberd "
"Guide for more information.">>,
- ?WARNING_MSG("Problem '~p' accessing the local Guide file ~s", [Error, Help]),
+ ?WARNING_MSG("Problem '~p' accessing the local Guide file ~ts", [Error, Help]),
case Error of
eacces -> {403, [], <<"Forbidden", Help/binary>>};
enoent -> {307, [{<<"Location">>, <<"http://docs.ejabberd.im/admin/guide/configuration/">>}], <<"Not found", Help/binary>>};
end;
_ -> translate:translate(Lang, ?T("Online"))
end,
- [?XC(<<"h1">>, (str:format(translate:translate(Lang, ?T("User ~s")),
+ [?XC(<<"h1">>, (str:format(translate:translate(Lang, ?T("User ~ts")),
[us_to_list(US)])))]
++
case Res of
?DEBUG("TCP connection was closed, exit", []),
websocket_close(Socket, WsHandleLoopPid, SocketMode, 0);
{tcp_error, Socket, Reason} ->
- ?DEBUG("TCP connection error: ~s", [inet:format_error(Reason)]),
+ ?DEBUG("TCP connection error: ~ts", [inet:format_error(Reason)]),
websocket_close(Socket, WsHandleLoopPid, SocketMode, 0);
{'DOWN', Ref, process, WsHandleLoopPid, Reason} ->
Code = case Reason of
8 -> % Close
CloseCode = case Unmasked of
<<Code:16/integer-big, Message/binary>> ->
- ?DEBUG("WebSocket close op: ~p ~s",
+ ?DEBUG("WebSocket close op: ~p ~ts",
[Code, Message]),
Code;
<<Code:16/integer-big>> ->
El ->
case fxmlrpc:decode(El) of
{error, _} = Err ->
- ?ERROR_MSG("XML-RPC request ~s failed with reason: ~p",
+ ?ERROR_MSG("XML-RPC request ~ts failed with reason: ~p",
[Data, Err]),
{400, [],
#xmlel{name = <<"h1">>, attrs = [],
case export(LServer, Table, IO, ConvertFun) of
{atomic, ok} -> ok;
{aborted, {no_exists, _}} ->
- ?WARNING_MSG("Ignoring export for module ~s: "
- "Mnesia table ~s doesn't exist (most likely "
+ ?WARNING_MSG("Ignoring export for module ~ts: "
+ "Mnesia table ~ts doesn't exist (most likely "
"because the module is unused)",
[Module1, Table]);
{aborted, Reason} ->
{error, enoent} ->
ok;
eof ->
- ?INFO_MSG("It seems like SQL dump ~s is empty", [FileName]);
+ ?INFO_MSG("It seems like SQL dump ~ts is empty", [FileName]);
Err ->
- ?ERROR_MSG("Failed to open SQL dump ~s: ~s",
+ ?ERROR_MSG("Failed to open SQL dump ~ts: ~ts",
[FileName, format_error(Err)])
end
end, import_info(Mod)),
eof ->
ok;
Err ->
- ?ERROR_MSG("Failed to read row from SQL dump: ~s",
+ ?ERROR_MSG("Failed to read row from SQL dump: ~ts",
[format_error(Err)])
end.
end;
handle_info({Tag, _Socket}, Fsm_state, S)
when Tag == tcp_closed; Tag == ssl_closed ->
- ?WARNING_MSG("LDAP server closed the connection: ~s:~p~nIn "
+ ?WARNING_MSG("LDAP server closed the connection: ~ts:~p~nIn "
"State: ~p",
[S#eldap.host, S#eldap.port, Fsm_state]),
{next_state, connecting, close_and_retry(S)};
close_and_retry(S, ?RETRY_TIMEOUT).
report_bind_failure(Host, Port, Reason) ->
- ?WARNING_MSG("LDAP bind failed on ~s:~p~nReason: ~p",
+ ?WARNING_MSG("LDAP bind failed on ~ts:~p~nReason: ~p",
[Host, Port, Reason]).
%%-----------------------------------------------------------------------
[{packet, asn1}, {active, true}, {keepalive, true},
{send_timeout, ?SEND_TIMEOUT}, binary]
end,
- ?DEBUG("Connecting to LDAP server at ~s:~p with options ~p",
+ ?DEBUG("Connecting to LDAP server at ~ts:~p with options ~p",
[Host, S#eldap.port, Opts]),
HostS = binary_to_list(Host),
SockMod = case S#eldap.tls of
{ok, connecting, NewS#eldap{host = Host}}
end;
{error, Reason} ->
- ?ERROR_MSG("LDAP connection to ~s:~b failed: ~s",
+ ?ERROR_MSG("LDAP connection to ~ts:~b failed: ~ts",
[Host, S#eldap.port, format_error(SockMod, Reason)]),
NewS = close_and_retry(S),
{ok, connecting, NewS#eldap{host = Host}}
end, Contrib, modules_spec(sources_dir(), "*/*")),
Repos = maps:fold(fun(Repo, _Mods, Acc) ->
Update = add_sources(Repo),
- ?INFO_MSG("Update packages from repo ~s: ~p", [Repo, Update]),
+ ?INFO_MSG("Update packages from repo ~ts: ~p", [Repo, Update]),
case Update of
ok -> Acc;
Error -> [{repository, Repo, Error}|Acc]
Res = lists:foldl(fun({Package, Spec}, Acc) ->
Repo = proplists:get_value(url, Spec, ""),
Update = add_sources(Package, Repo),
- ?INFO_MSG("Update package ~s: ~p", [Package, Update]),
+ ?INFO_MSG("Update package ~ts: ~p", [Package, Update]),
case Update of
ok -> Acc;
Error -> [{Package, Repo, Error}|Acc]
{reply, decode_bool(N), State};
{Port, Data} ->
?ERROR_MSG("Received unexpected response from external "
- "authentication program '~s': ~p "
+ "authentication program '~ts': ~p "
"(port = ~p, pid = ~w)",
[State#state.prog, Data, Port, State#state.os_pid]),
{reply, {error, unexpected_response}, State};
start_time = Time} = State) ->
case curr_time() - Time of
Diff when Diff < 1000 ->
- ?ERROR_MSG("Failed to start external authentication program '~s'",
+ ?ERROR_MSG("Failed to start external authentication program '~ts'",
[State#state.prog]),
{stop, normal, State};
_ ->
- ?ERROR_MSG("External authentication program '~s' has terminated "
+ ?ERROR_MSG("External authentication program '~ts' has terminated "
"unexpectedly (pid=~w), restarting via supervisor...",
[State#state.prog, State#state.os_pid]),
{stop, normal, State}
start(Host) ->
case extauth:prog_name(Host) of
undefined ->
- ?ERROR_MSG("Option 'extauth_program' is not set for '~s'",
+ ?ERROR_MSG("Option 'extauth_program' is not set for '~ts'",
[Host]),
ignore;
Prog ->
ok
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to process iq:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to process iq:~n~ts~n** ~ts",
[xmpp:pp(IQ),
misc:format_exception(2, Class, Reason, StackTrace)]),
Txt = ?T("Module failed to handle the query"),
-spec start_modules() -> any().
start_modules() ->
Hosts = ejabberd_option:hosts(),
- ?INFO_MSG("Loading modules for ~s", [misc:format_hosts_list(Hosts)]),
+ ?INFO_MSG("Loading modules for ~ts", [misc:format_hosts_list(Hosts)]),
lists:foreach(fun start_modules/1, Hosts).
-spec start_modules(binary()) -> ok.
-spec start_module(binary(), atom(), opts(), integer()) -> ok | {ok, pid()}.
start_module(Host, Module, Opts, Order) ->
- ?DEBUG("Loading ~s at ~s", [Module, Host]),
+ ?DEBUG("Loading ~ts at ~ts", [Module, Host]),
store_options(Host, Module, Opts, Order),
try case Module:start(Host, Opts) of
ok -> ok;
reload_module(Host, Module, NewOpts, OldOpts, Order) ->
case erlang:function_exported(Module, reload, 3) of
true ->
- ?DEBUG("Reloading ~s at ~s", [Module, Host]),
+ ?DEBUG("Reloading ~ts at ~ts", [Module, Host]),
store_options(Host, Module, NewOpts, Order),
try case Module:reload(Host, NewOpts, OldOpts) of
ok -> ok;
erlang:raise(Class, Reason, StackTrace)
end;
false ->
- ?WARNING_MSG("Module ~s doesn't support reloading "
+ ?WARNING_MSG("Module ~ts doesn't support reloading "
"and will be restarted", [Module]),
stop_module(Host, Module),
start_module(Host, Module, NewOpts, Order)
-spec stop_module_keep_config(binary(), atom()) -> error | ok.
stop_module_keep_config(Host, Module) ->
- ?DEBUG("Stopping ~s at ~s", [Module, Host]),
+ ?DEBUG("Stopping ~ts at ~ts", [Module, Host]),
try Module:stop(Host) of
_ ->
ets:delete(ejabberd_modules, {Module, Host}),
ok
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to stop module ~s at ~s:~n** ~s",
+ ?ERROR_MSG("Failed to stop module ~ts at ~ts:~n** ~ts",
[Module, Host,
misc:format_exception(2, Class, Reason, StackTrace)]),
error
format_module_error(Module, Fun, Arity, Opts, Class, Reason, St) ->
case {Class, Reason} of
{error, {bad_return, Module, {error, _} = Err}} ->
- io_lib:format("Failed to ~s module ~s: ~s",
+ io_lib:format("Failed to ~ts module ~ts: ~ts",
[Fun, Module, misc:format_val(Err)]);
{error, {bad_return, Module, Ret}} ->
- io_lib:format("Module ~s returned unexpected value from ~s/~B:~n"
+ io_lib:format("Module ~ts returned unexpected value from ~ts/~B:~n"
"** Error: ~p~n"
"** Hint: this is either not an ejabberd module "
"or it implements ejabberd API incorrectly",
[Module, Fun, Arity, Ret]);
_ ->
- io_lib:format("Internal error of module ~s has "
- "occurred during ~s:~n"
+ io_lib:format("Internal error of module ~ts has "
+ "occurred during ~ts:~n"
"** Options: ~p~n"
- "** ~s",
+ "** ~ts",
[Module, Fun, Opts,
misc:format_exception(2, Class, Reason, St)])
end.
-spec warn_soft_dep_fail(module(), module()) -> ok.
warn_soft_dep_fail(DepMod, Mod) ->
- ?WARNING_MSG("Module ~s is recommended for module "
- "~s but is not found in the config",
+ ?WARNING_MSG("Module ~ts is recommended for module "
+ "~ts but is not found in the config",
[DepMod, Mod]).
-spec warn_cyclic_dep([module()]) -> ok.
warn_cyclic_dep(Path) ->
- ?WARNING_MSG("Cyclic dependency detected between modules ~s. "
+ ?WARNING_MSG("Cyclic dependency detected between modules ~ts. "
"This is either a bug, or the modules are not "
"supposed to work together in this configuration. "
"The modules will still be loaded though",
El when is_record(El, xmlel) ->
case catch process_xdb(User, Server, El) of
{'EXIT', Reason} ->
- ?ERROR_MSG("Error while processing file \"~s\": "
+ ?ERROR_MSG("Error while processing file \"~ts\": "
"~p~n",
[File, Reason]),
{error, Reason};
_ -> ok
end;
{error, Reason} ->
- ?ERROR_MSG("Can't parse file \"~s\": ~p~n",
+ ?ERROR_MSG("Can't parse file \"~ts\": ~p~n",
[File, Reason]),
{error, Reason}
end;
{error, Reason} ->
- ?ERROR_MSG("Can't read file \"~s\": ~p~n",
+ ?ERROR_MSG("Can't read file \"~ts\": ~p~n",
[File, Reason]),
{error, Reason}
end;
false ->
- ?ERROR_MSG("Illegal user/server name in file \"~s\"~n",
+ ?ERROR_MSG("Illegal user/server name in file \"~ts\"~n",
[File]),
{error, <<"illegal user/server">>}
end.
From,
[{XMLNS, El#xmlel{attrs = NewAttrs}}]);
_ ->
- ?DEBUG("Unknown namespace \"~s\"~n", [XMLNS])
+ ?DEBUG("Unknown namespace \"~ts\"~n", [XMLNS])
end,
ok
end.
ok
catch _:{xmpp_codec, Why} ->
Txt = xmpp:format_error(Why),
- ?ERROR_MSG("Failed to decode XML '~s': ~s",
+ ?ERROR_MSG("Failed to decode XML '~ts': ~ts",
[fxml:element_to_binary(El), Txt])
end
end, Els).
file:close(Fd),
iolist_to_binary(Path);
{error, Why} ->
- ?ERROR_MSG("Failed to read ~s: ~s", [Path, file:format_error(Why)]),
+ ?ERROR_MSG("Failed to read ~ts: ~ts", [Path, file:format_error(Why)]),
erlang:error(badarg)
end.
end,
case http_uri:parse(URL) of
{ok, {Scheme, _, _, _, _, _}} when Scheme /= http, Scheme /= https ->
- ?ERROR_MSG("Unsupported URI scheme: ~s", [URL]),
+ ?ERROR_MSG("Unsupported URI scheme: ~ts", [URL]),
erlang:error(badarg);
{ok, {_, _, Host, _, _, _}} when Host == ""; Host == <<"">> ->
- ?ERROR_MSG("Invalid URL: ~s", [URL]),
+ ?ERROR_MSG("Invalid URL: ~ts", [URL]),
erlang:error(badarg);
{ok, _} ->
iolist_to_binary(URL);
{error, _} ->
- ?ERROR_MSG("Invalid URL: ~s", [URL]),
+ ?ERROR_MSG("Invalid URL: ~ts", [URL]),
erlang:error(badarg)
end.
format_hosts_list([H1, H2, H3]) ->
[H1, ", ", H2, " and ", H3];
format_hosts_list([H1, H2|Hs]) ->
- io_lib:format("~s, ~s and ~B more hosts",
+ io_lib:format("~ts, ~ts and ~B more hosts",
[H1, H2, length(Hs)]).
-spec format_cycle([atom(), ...]) -> iolist().
{ok, Data} ->
{ok, Data};
{error, Why} = Err ->
- ?ERROR_MSG("Failed to read file ~s: ~s",
+ ?ERROR_MSG("Failed to read file ~ts: ~ts",
[Path, file:format_error(Why)]),
Err
end.
Pkt = xmpp:decode(El, ?NS_CLIENT, CodecOpts),
ejabberd_router:route(xmpp:set_from_to(Pkt, From, To))
catch _:{xmpp_codec, Why} ->
- io:format("incorrect stanza: ~s~n", [xmpp:format_error(Why)]),
+ io:format("incorrect stanza: ~ts~n", [xmpp:format_error(Why)]),
{error, Why};
_:{badmatch, {error, Why}} ->
io:format("invalid xml: ~p~n", [Why]),
{error, Why};
_:{bad_jid, S} ->
- io:format("malformed JID: ~s~n", [S]),
+ io:format("malformed JID: ~ts~n", [S]),
{error, "JID malformed"}
end.
io:format("invalid xml: ~p~n", [Why]),
Err;
_:{xmpp_codec, Why} ->
- io:format("incorrect stanza: ~s~n", [xmpp:format_error(Why)]),
+ io:format("incorrect stanza: ~ts~n", [xmpp:format_error(Why)]),
{error, Why}
end.
SCols, ");"]).
sql_query(Host, Query) ->
- io:format("executing \"~s\" on ~s~n", [Query, Host]),
+ io:format("executing \"~ts\" on ~ts~n", [Query, Host]),
case ejabberd_sql:sql_query(Host, Query) of
{error, Error} ->
io:format("error: ~p~n", [Error]),
ok
end
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode motd packet ~p: ~s",
+ ?ERROR_MSG("Failed to decode motd packet ~p: ~ts",
[Packet, xmpp:format_error(Why)])
end;
_ ->
#message{body = Body, subject = Subject} ->
{xmpp:get_text(Subject), xmpp:get_text(Body)}
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode motd packet ~p: ~s",
+ ?ERROR_MSG("Failed to decode motd packet ~p: ~ts",
[Packet, xmpp:format_error(Why)])
end;
_ ->
{ok, El};
_ ->
?ERROR_MSG("Malformed XML element in SQL table "
- "'motd' for username='': ~s", [XML]),
+ "'motd' for username='': ~ts", [XML]),
{error, db_failure}
end.
set_vcard_avatar(From, Photo, #{})
end;
_ ->
- ?WARNING_MSG("Invalid avatar metadata of ~s@~s published "
- "with item id ~s",
+ ?WARNING_MSG("Invalid avatar metadata of ~ts@~ts published "
+ "with item id ~ts",
[LUser, LServer, ItemId])
catch _:{xmpp_codec, Why} ->
- ?WARNING_MSG("Failed to decode avatar metadata of ~s@~s: ~s",
+ ?WARNING_MSG("Failed to decode avatar metadata of ~ts@~ts: ~ts",
[LUser, LServer, xmpp:format_error(Why)])
end;
pubsub_publish_item(_, _, _, _, _, _) ->
{ok, Data};
_ ->
?WARNING_MSG("Invalid avatar data detected "
- "for ~s@~s with item id ~s",
+ "for ~ts@~ts with item id ~ts",
[LUser, LServer, ItemID]),
{error, invalid_data}
catch _:{xmpp_codec, Why} ->
?WARNING_MSG("Failed to decode avatar data for "
- "~s@~s with item id ~s: ~s",
+ "~ts@~ts with item id ~ts: ~ts",
[LUser, LServer, ItemID,
xmpp:format_error(Why)]),
{error, invalid_data}
end;
#pubsub_item{payload = []} ->
?WARNING_MSG("Empty avatar data detected "
- "for ~s@~s with item id ~s",
+ "for ~ts@~ts with item id ~ts",
[LUser, LServer, ItemID]),
{error, invalid_data};
{error, #stanza_error{reason = 'item-not-found'}} ->
{error, notfound};
{error, Reason} ->
- ?WARNING_MSG("Failed to get item for ~s@~s at node ~s "
- "with item id ~s: ~p",
+ ?WARNING_MSG("Failed to get item for ~ts@~ts at node ~ts "
+ "with item id ~ts: ~p",
[LUser, LServer, ?NS_AVATAR_METADATA, ItemID, Reason]),
{error, internal_error}
end.
{ok, ItemID, Meta};
_ ->
?WARNING_MSG("Invalid metadata payload detected "
- "for ~s@~s with item id ~s",
+ "for ~ts@~ts with item id ~ts",
[LUser, LServer, ItemID]),
{error, invalid_metadata}
catch _:{xmpp_codec, Why} ->
?WARNING_MSG("Failed to decode metadata for "
- "~s@~s with item id ~s: ~s",
+ "~ts@~ts with item id ~ts: ~ts",
[LUser, LServer, ItemID,
xmpp:format_error(Why)]),
{error, invalid_metadata}
{error, #stanza_error{reason = 'item-not-found'}} ->
{error, notfound};
{error, Reason} ->
- ?WARNING_MSG("Failed to get items for ~s@~s at node ~s: ~p",
+ ?WARNING_MSG("Failed to get items for ~ts@~ts at node ~ts: ~p",
[LUser, LServer, ?NS_AVATAR_METADATA, Reason]),
{error, internal_error}
end.
{result, _} ->
IQ;
{error, StanzaErr} ->
- ?ERROR_MSG("Failed to publish avatar metadata for ~s: ~p",
+ ?ERROR_MSG("Failed to publish avatar metadata for ~ts: ~p",
[jid:encode(JID), StanzaErr]),
{stop, StanzaErr}
end;
{error, #stanza_error{reason = 'not-acceptable'} = StanzaErr} ->
- ?WARNING_MSG("Failed to publish avatar data for ~s: ~p",
+ ?WARNING_MSG("Failed to publish avatar data for ~ts: ~p",
[jid:encode(JID), StanzaErr]),
{stop, StanzaErr};
{error, StanzaErr} ->
- ?ERROR_MSG("Failed to publish avatar data for ~s: ~p",
+ ?ERROR_MSG("Failed to publish avatar data for ~ts: ~p",
[jid:encode(JID), StanzaErr]),
{stop, StanzaErr}
end.
if NewType == undefined ->
pass;
true ->
- ?DEBUG("Converting avatar of ~s@~s: ~s -> ~s",
+ ?DEBUG("Converting avatar of ~ts@~ts: ~ts -> ~ts",
[LUser, LServer, Type, NewType]),
RateLimit = mod_avatar_opt:rate_limit(LServer),
Opts = [{limit_by, {LUser, LServer}},
{ok, encode_mime_type(NewType), NewData};
{error, Reason} = Err ->
?ERROR_MSG("Failed to convert avatar of "
- "~s@~s (~s -> ~s): ~s",
+ "~ts@~ts (~ts -> ~ts): ~ts",
[LUser, LServer, Type, NewType,
eimp:format_error(Reason)]),
Err
#vcard_temp{} = VCard ->
{ok, VCard};
_ ->
- ?ERROR_MSG("Invalid vCard of ~s@~s in the database",
+ ?ERROR_MSG("Invalid vCard of ~ts@~ts in the database",
[LUser, LServer]),
{error, invalid_vcard}
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode vCard of ~s@~s: ~s",
+ ?ERROR_MSG("Failed to decode vCard of ~ts@~ts: ~ts",
[LUser, LServer, xmpp:format_error(Why)]),
{error, invalid_vcard}
end.
case mod_block_strangers_opt:log(LServer) of
true ->
?INFO_MSG("Challenge subscription request "
- "from stranger ~s to ~s with "
+ "from stranger ~ts to ~ts with "
"CAPTCHA",
[jid:encode(From), jid:encode(To)]);
false ->
Log = mod_block_strangers_opt:log(LServer),
if
Log ->
- ?INFO_MSG("~s message from stranger ~s to ~s",
+ ?INFO_MSG("~ts message from stranger ~ts to ~ts",
[if Drop -> "Rejecting";
true -> "Allow"
end,
broadcast_event(From, #block{items = Items}),
xmpp:make_iq_result(IQ);
{error, notfound} ->
- ?ERROR_MSG("Failed to set default list '~s': "
+ ?ERROR_MSG("Failed to set default list '~ts': "
"the list should exist, but not found",
[Name]),
err_db_failure(IQ);
try
{ok, binary_to_term(Pid)}
catch _:badarg ->
- ?ERROR_MSG("Malformed data in redis (key = '~s'): ~p",
+ ?ERROR_MSG("Malformed data in redis (key = '~ts'): ~p",
[SID, Pid]),
{error, db_failure}
end;
-spec enable(binary(), binary(), binary(), binary()) -> ok | {error, any()}.
enable(Host, U, R, CC)->
- ?DEBUG("Enabling carbons for ~s@~s/~s", [U, Host, R]),
+ ?DEBUG("Enabling carbons for ~ts@~ts/~ts", [U, Host, R]),
case ejabberd_sm:set_user_info(U, Host, R, carboncopy, CC) of
ok -> ok;
{error, Reason} = Err ->
- ?ERROR_MSG("Failed to enable carbons for ~s@~s/~s: ~p",
+ ?ERROR_MSG("Failed to enable carbons for ~ts@~ts/~ts: ~p",
[U, Host, R, Reason]),
Err
end.
-spec disable(binary(), binary(), binary()) -> ok | {error, any()}.
disable(Host, U, R)->
- ?DEBUG("Disabling carbons for ~s@~s/~s", [U, Host, R]),
+ ?DEBUG("Disabling carbons for ~ts@~ts/~ts", [U, Host, R]),
case ejabberd_sm:del_user_info(U, Host, R, carboncopy) of
ok -> ok;
{error, notfound} -> ok;
{error, Reason} = Err ->
- ?ERROR_MSG("Failed to disable carbons for ~s@~s/~s: ~p",
+ ?ERROR_MSG("Failed to disable carbons for ~ts@~ts/~ts: ~p",
[U, Host, R, Reason]),
Err
end.
filter_presence({#presence{to = To, type = Type} = Pres,
#{csi_state := inactive} = C2SState})
when Type == available; Type == unavailable ->
- ?DEBUG("Got availability presence stanza for ~s", [jid:encode(To)]),
+ ?DEBUG("Got availability presence stanza for ~ts", [jid:encode(To)]),
enqueue_stanza(presence, Pres, C2SState);
filter_presence(Acc) ->
Acc.
%% conversations across clients.
Acc;
_ ->
- ?DEBUG("Got standalone chat state notification for ~s",
+ ?DEBUG("Got standalone chat state notification for ~ts",
[jid:encode(To)]),
enqueue_stanza(chatstate, Msg, C2SState)
end;
undefined ->
Acc;
Node ->
- ?DEBUG("Got PEP notification for ~s", [jid:encode(To)]),
+ ?DEBUG("Got PEP notification for ~ts", [jid:encode(To)]),
enqueue_stanza({pep, Node}, Msg, C2SState)
end;
filter_pep(Acc) ->
#{csi_resend := true} ->
Acc;
_ ->
- ?DEBUG("Won't add stanza for ~s to CSI queue", [jid:encode(JID)]),
+ ?DEBUG("Won't add stanza for ~ts to CSI queue", [jid:encode(JID)]),
From = case xmpp:get_from(Stanza) of
undefined -> JID;
F -> F
%% This may happen when the module is (re)loaded in runtime
init_csi_state(C2SState);
Q ->
- ?DEBUG("Flushing packets of ~s@~s from CSI queue of ~s",
+ ?DEBUG("Flushing packets of ~ts@~ts from CSI queue of ~ts",
[U, S, jid:encode(JID)]),
{Elems, Q1} = queue_take(Sender, Q),
C2SState1 = flush_stanzas(C2SState, Elems),
-spec flush_queue(c2s_state()) -> c2s_state().
flush_queue(#{csi_queue := Q, jid := JID} = C2SState) ->
- ?DEBUG("Flushing CSI queue of ~s", [jid:encode(JID)]),
+ ?DEBUG("Flushing CSI queue of ~ts", [jid:encode(JID)]),
C2SState1 = flush_stanzas(C2SState, queue_to_list(Q)),
C2SState1#{csi_queue => queue_new()}.
Host == FH orelse str:suffix(DotHost, FH)],
lists:map(
fun (T) ->
- Name = str:format(tr(Lang, ?T("To ~s")),[T]),
+ Name = str:format(tr(Lang, ?T("To ~ts")),[T]),
#disco_item{jid = jid:make(Host),
node = <<"outgoing s2s/", T/binary>>,
name = Name}
lists:map(
fun ({F, _T}) ->
Node = <<"outgoing s2s/", To/binary, "/", F/binary>>,
- Name = str:format(tr(Lang, ?T("From ~s")), [F]),
+ Name = str:format(tr(Lang, ?T("From ~ts")), [F]),
#disco_item{jid = jid:make(Host), node = Node, name = Name}
end,
lists:keysort(
case ejabberd_cluster:call(Node, mnesia, system_info, [tables]) of
{badrpc, Reason} ->
?ERROR_MSG("RPC call mnesia:system_info(tables) on node "
- "~s failed: ~p", [Node, Reason]),
+ "~ts failed: ~p", [Node, Reason]),
{error, xmpp:err_internal_server_error()};
Tables ->
STables = lists:sort(Tables),
fields = [?HFIELD()|Fs]}}
catch _:{case_clause, {badrpc, Reason}} ->
?ERROR_MSG("RPC call mnesia:table_info/2 "
- "on node ~s failed: ~p", [Node, Reason]),
+ "on node ~ts failed: ~p", [Node, Reason]),
{error, xmpp:err_internal_server_error()}
end
end
Node, mnesia, backup, [binary_to_list(String)],
timer:minutes(10)) of
{badrpc, Reason} ->
- ?ERROR_MSG("RPC call mnesia:backup(~s) to node ~s "
+ ?ERROR_MSG("RPC call mnesia:backup(~ts) to node ~ts "
"failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
{error, Reason} ->
- ?ERROR_MSG("RPC call mnesia:backup(~s) to node ~s "
+ ?ERROR_MSG("RPC call mnesia:backup(~ts) to node ~ts "
"failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
_ ->
Node, ejabberd_admin, restore,
[String], timer:minutes(10)) of
{badrpc, Reason} ->
- ?ERROR_MSG("RPC call ejabberd_admin:restore(~s) to node "
- "~s failed: ~p", [String, Node, Reason]),
+ ?ERROR_MSG("RPC call ejabberd_admin:restore(~ts) to node "
+ "~ts failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
{error, Reason} ->
- ?ERROR_MSG("RPC call ejabberd_admin:restore(~s) to node "
- "~s failed: ~p", [String, Node, Reason]),
+ ?ERROR_MSG("RPC call ejabberd_admin:restore(~ts) to node "
+ "~ts failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
_ ->
{result, undefined}
Node, ejabberd_admin, dump_to_textfile,
[String], timer:minutes(10)) of
{badrpc, Reason} ->
- ?ERROR_MSG("RPC call ejabberd_admin:dump_to_textfile(~s) "
- "to node ~s failed: ~p", [String, Node, Reason]),
+ ?ERROR_MSG("RPC call ejabberd_admin:dump_to_textfile(~ts) "
+ "to node ~ts failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
{error, Reason} ->
- ?ERROR_MSG("RPC call ejabberd_admin:dump_to_textfile(~s) "
- "to node ~s failed: ~p", [String, Node, Reason]),
+ ?ERROR_MSG("RPC call ejabberd_admin:dump_to_textfile(~ts) "
+ "to node ~ts failed: ~p", [String, Node, Reason]),
{error, xmpp:err_internal_server_error()};
_ ->
{result, undefined}
allow ->
send_disco_queries(ServerHost, Host, NS);
deny ->
- ?DEBUG("Denied delegation for ~s on ~s", [Host, NS])
+ ?DEBUG("Denied delegation for ~ts on ~ts", [Host, NS])
end
end, NSAttrsAccessList),
{noreply, State};
Delegations =
maps:filter(
fun({NS, Type}, {H, _}) when H == Host ->
- ?INFO_MSG("Remove delegation of namespace '~s' "
- "from external component '~s'",
+ ?INFO_MSG("Remove delegation of namespace '~ts' "
+ "from external component '~ts'",
[NS, Host]),
gen_iq_handler:remove_iq_handler(Type, ServerHost, NS),
false;
end
catch _:_ ->
?ERROR_MSG("Got iq-result with invalid delegated "
- "payload:~n~s", [xmpp:pp(ResIQ)]),
+ "payload:~n~ts", [xmpp:pp(ResIQ)]),
Txt = ?T("External component failure"),
Err = xmpp:err_internal_server_error(Txt, Lang),
ejabberd_router:route_error(IQ, Err)
gen_iq_handler:add_iq_handler(Type, ServerHost, NS, ?MODULE, Type),
ejabberd_router:route(Msg),
set_delegations(ServerHost, Delegations1),
- ?INFO_MSG("Namespace '~s' is delegated to external component '~s'",
+ ?INFO_MSG("Namespace '~ts' is delegated to external component '~ts'",
[NS, Host]);
{ok, {AnotherHost, _}} ->
- ?WARNING_MSG("Failed to delegate namespace '~s' to "
- "external component '~s' because it's already "
- "delegated to '~s'",
+ ?WARNING_MSG("Failed to delegate namespace '~ts' to "
+ "external component '~ts' because it's already "
+ "delegated to '~ts'",
[NS, Host, AnotherHost])
end.
UnbanDate = format_date(
calendar:now_to_universal_time(msec_to_now(UnbanTS))),
Format = ?T("Too many (~p) failed authentications "
- "from this IP address (~s). The address "
- "will be unblocked at ~s UTC"),
+ "from this IP address (~ts). The address "
+ "will be unblocked at ~ts UTC"),
Args = [Attempts, IP, UnbanDate],
- ?WARNING_MSG("Connection attempt from blacklisted IP ~s: ~s",
+ ?WARNING_MSG("Connection attempt from blacklisted IP ~ts: ~ts",
[IP, io_lib:fwrite(Format, Args)]),
Err = xmpp:serr_policy_violation({Format, Args}, Lang),
{stop, ejabberd_c2s:send(State, Err)}.
?EX_RULE(Class, Error, Stack) ->
StackTrace = ?EX_STACK(Stack),
?ERROR_MSG("REST API Error: "
- "~s(~p) -> ~p:~p ~p",
+ "~ts(~p) -> ~p:~p ~p",
[Call, hide_sensitive_args(Args),
Class, Error, StackTrace]),
{500, <<"internal_error">>}
case proplists:get_all_values(A, L) of
[Value] -> {Value, proplists:delete(A, L)};
[_, _ | _] ->
- ?INFO_MSG("Command ~s call rejected, it has duplicate attribute ~w",
+ ?INFO_MSG("Command ~ts call rejected, it has duplicate attribute ~w",
[Call, A]),
throw({invalid_parameter,
io_lib:format("Request have duplicate argument: ~w", [A])});
{list, _} ->
{[], L};
_ ->
- ?INFO_MSG("Command ~s call rejected, missing attribute ~w",
+ ?INFO_MSG("Command ~ts call rejected, missing attribute ~w",
[Call, A]),
throw({invalid_parameter,
io_lib:format("Request have missing argument: ~w", [A])})
[] -> R;
L when is_list(L) ->
ExtraArgs = [N || {N, _} <- L],
- ?INFO_MSG("Command ~s call rejected, it has unknown arguments ~w",
+ ?INFO_MSG("Command ~ts call rejected, it has unknown arguments ~w",
[Call, ExtraArgs]),
throw({invalid_parameter,
io_lib:format("Request have unknown arguments: ~w", [ExtraArgs])})
log(Call, Args, {Addr, Port}) ->
AddrS = misc:ip_to_list({Addr, Port}),
- ?INFO_MSG("API call ~s ~p from ~s:~p", [Call, hide_sensitive_args(Args), AddrS, Port]);
+ ?INFO_MSG("API call ~ts ~p from ~ts:~p", [Call, hide_sensitive_args(Args), AddrS, Port]);
log(Call, Args, IP) ->
- ?INFO_MSG("API call ~s ~p (~p)", [Call, hide_sensitive_args(Args), IP]).
+ ?INFO_MSG("API call ~ts ~p (~p)", [Call, hide_sensitive_args(Args), IP]).
hide_sensitive_args(Args=[_H|_T]) ->
lists:map( fun({<<"password">>, Password}) -> {<<"password">>, ejabberd_config:may_hide_data(Password)};
ContentTypes = build_list_content_types(
mod_http_fileserver_opt:content_types(Opts),
?DEFAULT_CONTENT_TYPES),
- ?DEBUG("Known content types: ~s",
+ ?DEBUG("Known content types: ~ts",
[str:join([[$*, K, " -> ", V] || {K, V} <- ContentTypes],
<<", ">>)]),
#state{host = Host,
add_to_log(FileSize, Code, Request#request{host = VHost}),
{Code, Headers, Contents}
catch _:{Why, _} when Why == noproc; Why == invalid_domain; Why == unregistered_route ->
- ?DEBUG("Received an HTTP request with Host: ~s, "
+ ?DEBUG("Received an HTTP request with Host: ~ts, "
"but couldn't find the related "
"ejabberd virtual host", [Host]),
{FileSize1, Code1, Headers1, Contents1} = ?HTTP_ERR_HOST_UNKNOWN,
end.
serve_not_modified(FileInfo, FileName, CustomHeaders) ->
- ?DEBUG("Delivering not modified: ~s", [FileName]),
+ ?DEBUG("Delivering not modified: ~ts", [FileName]),
{0, 304,
[{<<"Server">>, <<"ejabberd">>},
{<<"Last-Modified">>, last_modified(FileInfo)}
%% Assume the file exists if we got this far and attempt to read it in
%% and serve it up.
serve_file(FileInfo, FileName, CustomHeaders, DefaultContentType, ContentTypes) ->
- ?DEBUG("Delivering: ~s", [FileName]),
+ ?DEBUG("Delivering: ~ts", [FileName]),
ContentType = content_type(FileName, DefaultContentType,
ContentTypes),
{FileInfo#file_info.size, 200,
%% Missing time zone = (`+' | `-') 4*digit
%% Missing protocol version: HTTP/1.1
%% For reference: http://httpd.apache.org/docs/2.2/logs.html
- io:format(File, "~s - - [~p/~p/~p:~p:~p:~p] \"~s /~s~s\" ~p ~p ~p ~p~n",
+ io:format(File, "~ts - - [~p/~p/~p:~p:~p:~p] \"~ts /~ts~ts\" ~p ~p ~p ~p~n",
[IP, Day, Month, Year, Hour, Minute, Second, Request#request.method, Path, Query, Code,
FileSize, Referer, UserAgent]).
-spec terminate(normal | shutdown | {shutdown, _} | _, state()) -> ok.
terminate(Reason, #state{server_host = ServerHost, hosts = Hosts}) ->
- ?DEBUG("Stopping HTTP upload process for ~s: ~p", [ServerHost, Reason]),
+ ?DEBUG("Stopping HTTP upload process for ~ts: ~p", [ServerHost, Reason]),
ejabberd_hooks:delete(remove_user, ServerHost, ?MODULE, remove_user, 50),
lists:foreach(fun ejabberd_router:unregister_route/1, Hosts).
-spec code_change({down, _} | _, state(), _) -> {ok, state()}.
code_change(_OldVsn, #state{server_host = ServerHost} = State, _Extra) ->
- ?DEBUG("Updating HTTP upload process for ~s", [ServerHost]),
+ ?DEBUG("Updating HTTP upload process for ~ts", [ServerHost]),
{ok, State}.
%%--------------------------------------------------------------------
Method == 'PUT' orelse
Method == 'GET' orelse
Method == 'HEAD' ->
- ?DEBUG("Rejecting ~s request from ~s for ~s: Too few path components",
+ ?DEBUG("Rejecting ~ts request from ~ts for ~ts: Too few path components",
[Method, encode_addr(IP), Host]),
http_response(404);
process(_LocalPath, #request{method = 'PUT', host = Host, ip = IP,
{Proc, Slot} = parse_http_request(Request),
try gen_server:call(Proc, {use_slot, Slot, Length}, ?CALL_TIMEOUT) of
{ok, Path, FileMode, DirMode, GetPrefix, Thumbnail, CustomHeaders} ->
- ?DEBUG("Storing file from ~s for ~s: ~s",
+ ?DEBUG("Storing file from ~ts for ~ts: ~ts",
[encode_addr(IP), Host, Path]),
case store_file(Path, Request, FileMode, DirMode,
GetPrefix, Slot, Thumbnail) of
{ok, Headers, OutData} ->
http_response(201, Headers ++ CustomHeaders, OutData);
{error, closed} ->
- ?DEBUG("Cannot store file ~s from ~s for ~s: connection closed",
+ ?DEBUG("Cannot store file ~ts from ~ts for ~ts: connection closed",
[Path, encode_addr(IP), Host]),
http_response(404);
{error, Error} ->
- ?ERROR_MSG("Cannot store file ~s from ~s for ~s: ~s",
+ ?ERROR_MSG("Cannot store file ~ts from ~ts for ~ts: ~ts",
[Path, encode_addr(IP), Host, format_error(Error)]),
http_response(500)
end;
{error, size_mismatch} ->
- ?WARNING_MSG("Rejecting file ~s from ~s for ~s: Unexpected size (~B)",
+ ?WARNING_MSG("Rejecting file ~ts from ~ts for ~ts: Unexpected size (~B)",
[lists:last(Slot), encode_addr(IP), Host, Length]),
http_response(413);
{error, invalid_slot} ->
- ?WARNING_MSG("Rejecting file ~s from ~s for ~s: Invalid slot",
+ ?WARNING_MSG("Rejecting file ~ts from ~ts for ~ts: Invalid slot",
[lists:last(Slot), encode_addr(IP), Host]),
http_response(403)
catch
exit:{noproc, _} ->
- ?WARNING_MSG("Cannot handle PUT request from ~s for ~s: "
+ ?WARNING_MSG("Cannot handle PUT request from ~ts for ~ts: "
"Upload not configured for this host",
[encode_addr(IP), Host]),
http_response(404);
_:Error ->
- ?ERROR_MSG("Cannot handle PUT request from ~s for ~s: ~p",
+ ?ERROR_MSG("Cannot handle PUT request from ~ts for ~ts: ~p",
[encode_addr(IP), Host, Error]),
http_response(500)
end;
case file:open(Path, [read]) of
{ok, Fd} ->
file:close(Fd),
- ?INFO_MSG("Serving ~s to ~s", [Path, encode_addr(IP)]),
+ ?INFO_MSG("Serving ~ts to ~ts", [Path, encode_addr(IP)]),
ContentType = guess_content_type(FileName),
Headers1 = case ContentType of
<<"image/", _SubType/binary>> -> [];
Headers3 = Headers2 ++ CustomHeaders,
http_response(200, Headers3, {file, Path});
{error, eacces} ->
- ?WARNING_MSG("Cannot serve ~s to ~s: Permission denied",
+ ?WARNING_MSG("Cannot serve ~ts to ~ts: Permission denied",
[Path, encode_addr(IP)]),
http_response(403);
{error, enoent} ->
- ?WARNING_MSG("Cannot serve ~s to ~s: No such file",
+ ?WARNING_MSG("Cannot serve ~ts to ~ts: No such file",
[Path, encode_addr(IP)]),
http_response(404);
{error, eisdir} ->
- ?WARNING_MSG("Cannot serve ~s to ~s: Is a directory",
+ ?WARNING_MSG("Cannot serve ~ts to ~ts: Is a directory",
[Path, encode_addr(IP)]),
http_response(404);
{error, Error} ->
- ?WARNING_MSG("Cannot serve ~s to ~s: ~s",
+ ?WARNING_MSG("Cannot serve ~ts to ~ts: ~ts",
[Path, encode_addr(IP), format_error(Error)]),
http_response(500)
end
catch
exit:{noproc, _} ->
- ?WARNING_MSG("Cannot handle ~s request from ~s for ~s: "
+ ?WARNING_MSG("Cannot handle ~ts request from ~ts for ~ts: "
"Upload not configured for this host",
[Method, encode_addr(IP), Host]),
http_response(404);
_:Error ->
- ?ERROR_MSG("Cannot handle ~s request from ~s for ~s: ~p",
+ ?ERROR_MSG("Cannot handle ~ts request from ~ts for ~ts: ~p",
[Method, encode_addr(IP), Host, Error]),
http_response(500)
end;
process(_LocalPath, #request{method = 'OPTIONS', host = Host,
ip = IP} = Request) ->
- ?DEBUG("Responding to OPTIONS request from ~s for ~s",
+ ?DEBUG("Responding to OPTIONS request from ~ts for ~ts",
[encode_addr(IP), Host]),
{Proc, _Slot} = parse_http_request(Request),
try gen_server:call(Proc, get_conf, ?CALL_TIMEOUT) of
http_response(200, [AllowHeader | CustomHeaders])
catch
exit:{noproc, _} ->
- ?WARNING_MSG("Cannot handle OPTIONS request from ~s for ~s: "
+ ?WARNING_MSG("Cannot handle OPTIONS request from ~ts for ~ts: "
"Upload not configured for this host",
[encode_addr(IP), Host]),
http_response(404);
_:Error ->
- ?ERROR_MSG("Cannot handle OPTIONS request from ~s for ~s: ~p",
+ ?ERROR_MSG("Cannot handle OPTIONS request from ~ts for ~ts: ~p",
[encode_addr(IP), Host, Error]),
http_response(500)
end;
process(_LocalPath, #request{method = Method, host = Host, ip = IP}) ->
- ?DEBUG("Rejecting ~s request from ~s for ~s",
+ ?DEBUG("Rejecting ~ts request from ~ts for ~ts",
[Method, encode_addr(IP), Host]),
http_response(405, [{<<"Allow">>, <<"OPTIONS, HEAD, GET, PUT">>}]).
xmpp:make_error(IQ, Error)
end;
deny ->
- ?DEBUG("Denying HTTP upload slot request from ~s",
+ ?DEBUG("Denying HTTP upload slot request from ~ts",
[jid:encode(From)]),
Txt = ?T("Access denied by service policy"),
xmpp:make_error(IQ, xmpp:err_forbidden(Txt, Lang))
when MaxSize /= infinity,
Size > MaxSize ->
Text = {?T("File larger than ~w bytes"), [MaxSize]},
- ?WARNING_MSG("Rejecting file ~s from ~s (too large: ~B bytes)",
+ ?WARNING_MSG("Rejecting file ~ts from ~ts (too large: ~B bytes)",
[File, jid:encode(JID), Size]),
Error = xmpp:err_not_acceptable(Text, Lang),
Els = xmpp:get_els(Error),
allow ->
RandStr = p1_rand:get_alphanum_string(SecretLength),
FileStr = make_file_string(File),
- ?INFO_MSG("Got HTTP upload slot for ~s (file: ~s, size: ~B)",
+ ?INFO_MSG("Got HTTP upload slot for ~ts (file: ~ts, size: ~B)",
[jid:encode(JID), File, Size]),
{ok, [UserStr, RandStr, FileStr]};
deny ->
case binary:split(Body, <<$\n>>, [global, trim]) of
[<<"http", _/binary>> = PutURL,
<<"http", _/binary>> = GetURL] ->
- ?INFO_MSG("Got HTTP upload slot for ~s (file: ~s, size: ~B)",
+ ?INFO_MSG("Got HTTP upload slot for ~ts (file: ~ts, size: ~B)",
[jid:encode(JID), File, Size]),
{ok, PutURL, GetURL};
Lines ->
- ?ERROR_MSG("Can't parse data received for ~s from <~s>: ~p",
+ ?ERROR_MSG("Can't parse data received for ~ts from <~ts>: ~p",
[jid:encode(JID), ServiceURL, Lines]),
Txt = ?T("Failed to parse HTTP response"),
{error, xmpp:err_service_unavailable(Txt, Lang)}
end;
{ok, {402, _Body}} ->
- ?WARNING_MSG("Got status code 402 for ~s from <~s>",
+ ?WARNING_MSG("Got status code 402 for ~ts from <~ts>",
[jid:encode(JID), ServiceURL]),
{error, xmpp:err_resource_constraint()};
{ok, {403, _Body}} ->
- ?WARNING_MSG("Got status code 403 for ~s from <~s>",
+ ?WARNING_MSG("Got status code 403 for ~ts from <~ts>",
[jid:encode(JID), ServiceURL]),
{error, xmpp:err_not_allowed()};
{ok, {413, _Body}} ->
- ?WARNING_MSG("Got status code 413 for ~s from <~s>",
+ ?WARNING_MSG("Got status code 413 for ~ts from <~ts>",
[jid:encode(JID), ServiceURL]),
{error, xmpp:err_not_acceptable()};
{ok, {Code, _Body}} ->
- ?ERROR_MSG("Unexpected status code for ~s from <~s>: ~B",
+ ?ERROR_MSG("Unexpected status code for ~ts from <~ts>: ~B",
[jid:encode(JID), ServiceURL, Code]),
{error, xmpp:err_service_unavailable()};
{error, Reason} ->
- ?ERROR_MSG("Error requesting upload slot for ~s from <~s>: ~p",
+ ?ERROR_MSG("Error requesting upload slot for ~ts from <~ts>: ~p",
[jid:encode(JID), ServiceURL, Reason]),
{error, xmpp:err_service_unavailable()}
end.
width = proplists:get_value(width, Info),
height = proplists:get_value(height, Info)}};
{error, Why} ->
- ?DEBUG("Cannot identify type of ~s: ~s",
+ ?DEBUG("Cannot identify type of ~ts: ~ts",
[Path, eimp:format_error(Why)]),
pass
end;
{error, Reason} ->
- ?DEBUG("Failed to read file ~s: ~s",
+ ?DEBUG("Failed to read file ~ts: ~ts",
[Path, format_error(Reason)]),
pass
end.
-spec convert(binary(), media_info()) -> {ok, media_info()} | pass.
convert(InData, #media_info{path = Path, type = T, width = W, height = H} = Info) ->
if W * H >= 25000000 ->
- ?DEBUG("The image ~s is more than 25 Mpix", [Path]),
+ ?DEBUG("The image ~ts is more than 25 Mpix", [Path]),
pass;
W =< 300, H =< 300 ->
{ok, Info};
ok ->
{ok, OutInfo};
{error, Why} ->
- ?ERROR_MSG("Failed to write to ~s: ~s",
+ ?ERROR_MSG("Failed to write to ~ts: ~ts",
[OutPath, format_error(Why)]),
pass
end;
{error, Why} ->
- ?ERROR_MSG("Failed to convert ~s to ~s: ~s",
+ ?ERROR_MSG("Failed to convert ~ts to ~ts: ~ts",
[Path, OutPath, eimp:format_error(Why)]),
pass
end
UserDir = str:join([DocRoot1, UserStr], <<$/>>),
case misc:delete_dir(UserDir) of
ok ->
- ?INFO_MSG("Removed HTTP upload directory of ~s@~s", [User, Server]);
+ ?INFO_MSG("Removed HTTP upload directory of ~ts@~ts", [User, Server]);
{error, enoent} ->
- ?DEBUG("Found no HTTP upload directory of ~s@~s", [User, Server]);
+ ?DEBUG("Found no HTTP upload directory of ~ts@~ts", [User, Server]);
{error, Error} ->
- ?ERROR_MSG("Cannot remove HTTP upload directory of ~s@~s: ~s",
+ ?ERROR_MSG("Cannot remove HTTP upload directory of ~ts@~ts: ~ts",
[User, Server, format_error(Error)])
end,
ok.
end,
NewSize = case {HardQuota, SoftQuota} of
{0, 0} ->
- ?DEBUG("No quota specified for ~s",
+ ?DEBUG("No quota specified for ~ts",
[jid:encode(JID)]),
undefined;
{0, _} ->
- ?WARNING_MSG("No hard quota specified for ~s",
+ ?WARNING_MSG("No hard quota specified for ~ts",
[jid:encode(JID)]),
enforce_quota(Path, Size, OldSize, SoftQuota, SoftQuota);
{_, 0} ->
- ?WARNING_MSG("No soft quota specified for ~s",
+ ?WARNING_MSG("No soft quota specified for ~ts",
[jid:encode(JID)]),
enforce_quota(Path, Size, OldSize, HardQuota, HardQuota);
_ when SoftQuota > HardQuota ->
- ?WARNING_MSG("Bad quota for ~s (soft: ~p, hard: ~p)",
+ ?WARNING_MSG("Bad quota for ~ts (soft: ~p, hard: ~p)",
[jid:encode(JID),
SoftQuota, HardQuota]),
enforce_quota(Path, Size, OldSize, SoftQuota, SoftQuota);
_ ->
- ?DEBUG("Enforcing quota for ~s",
+ ?DEBUG("Enforcing quota for ~ts",
[jid:encode(JID)]),
enforce_quota(Path, Size, OldSize, SoftQuota, HardQuota)
end,
docroot = DocRoot,
max_days = MaxDays} = State)
when is_integer(MaxDays), MaxDays > 0 ->
- ?DEBUG("Got 'sweep' message for ~s", [ServerHost]),
+ ?DEBUG("Got 'sweep' message for ~ts", [ServerHost]),
case file:list_dir(DocRoot) of
{ok, Entries} ->
BackThen = secs_since_epoch() - (MaxDays * 86400),
delete_old_files(UserDir, BackThen)
end, UserDirs);
{error, Error} ->
- ?ERROR_MSG("Cannot open document root ~s: ~s",
+ ?ERROR_MSG("Cannot open document root ~ts: ~ts",
[DocRoot, ?FORMAT(Error)])
end,
{noreply, State};
-spec terminate(normal | shutdown | {shutdown, _} | _, state()) -> ok.
terminate(Reason, #state{server_host = ServerHost, timers = Timers}) ->
- ?DEBUG("Stopping upload quota process for ~s: ~p", [ServerHost, Reason]),
+ ?DEBUG("Stopping upload quota process for ~ts: ~p", [ServerHost, Reason]),
ejabberd_hooks:delete(http_upload_slot_request, ServerHost, ?MODULE,
handle_slot_request, 50),
lists:foreach(fun timer:cancel/1, Timers).
-spec code_change({down, _} | _, state(), _) -> {ok, state()}.
code_change(_OldVsn, #state{server_host = ServerHost} = State, _Extra) ->
- ?DEBUG("Updating upload quota process for ~s", [ServerHost]),
+ ?DEBUG("Updating upload quota process for ~ts", [ServerHost]),
{ok, State}.
%%--------------------------------------------------------------------
size = Size}} ->
[{Path, Size, Time} | Acc];
{ok, _Info} ->
- ?DEBUG("Won't stat(2) non-regular file ~s",
+ ?DEBUG("Won't stat(2) non-regular file ~ts",
[Path]),
Acc;
{error, Error} ->
- ?ERROR_MSG("Cannot stat(2) ~s: ~s",
+ ?ERROR_MSG("Cannot stat(2) ~ts: ~ts",
[Path, ?FORMAT(Error)]),
Acc
end
end, [], Entries);
{error, enoent} ->
- ?DEBUG("Directory ~s doesn't exist", [Dir]),
+ ?DEBUG("Directory ~ts doesn't exist", [Dir]),
[];
{error, Error} ->
- ?ERROR_MSG("Cannot open directory ~s: ~s", [Dir, ?FORMAT(Error)]),
+ ?ERROR_MSG("Cannot open directory ~ts: ~ts", [Dir, ?FORMAT(Error)]),
[]
end.
del_file_and_dir(File) ->
case file:delete(File) of
ok ->
- ?INFO_MSG("Removed ~s", [File]),
+ ?INFO_MSG("Removed ~ts", [File]),
Dir = filename:dirname(File),
case file:del_dir(Dir) of
ok ->
- ?DEBUG("Removed ~s", [Dir]);
+ ?DEBUG("Removed ~ts", [Dir]);
{error, Error} ->
- ?DEBUG("Cannot remove ~s: ~s", [Dir, ?FORMAT(Error)])
+ ?DEBUG("Cannot remove ~ts: ~ts", [Dir, ?FORMAT(Error)])
end;
{error, Error} ->
- ?WARNING_MSG("Cannot remove ~s: ~s", [File, ?FORMAT(Error)])
+ ?WARNING_MSG("Cannot remove ~ts: ~ts", [File, ?FORMAT(Error)])
end.
-spec secs_since_epoch() -> non_neg_integer().
allow ->
case jid:make(U, S, R) of
#jid{} = Normalized ->
- ?DEBUG("Normalized JID for ~s: ~s",
+ ?DEBUG("Normalized JID for ~ts: ~ts",
[jid:encode(From), jid:encode(JID)]),
xmpp:make_iq_result(IQ, #jidprep{jid = Normalized});
error -> % Cannot happen.
- ?DEBUG("Normalizing JID failed for ~s: ~s",
+ ?DEBUG("Normalizing JID failed for ~ts: ~ts",
[jid:encode(From), jid:encode(JID)]),
Txt = ?T("JID normalization failed"),
xmpp:make_error(IQ, xmpp:err_jid_malformed(Txt, Lang))
end;
deny ->
- ?DEBUG("Won't return normalized JID to ~s: ~s",
+ ?DEBUG("Won't return normalized JID to ~ts: ~ts",
[jid:encode(From), jid:encode(JID)]),
Txt = ?T("JID normalization denied by service policy"),
xmpp:make_error(IQ, xmpp:err_forbidden(Txt, Lang))
start(Host, Opts) ->
case mod_mam_opt:db_type(Opts) of
mnesia ->
- ?WARNING_MSG("Mnesia backend for ~s is not recommended: "
+ ?WARNING_MSG("Mnesia backend for ~ts is not recommended: "
"it's limited to 2GB and often gets corrupted "
"when reaching this limit. SQL backend is "
"recommended. Namely, for small servers SQLite "
{ok, #forwarded{sub_els = [Pkt3], delay = Delay}}
catch _:{xmpp_codec, Why} ->
?ERROR_MSG("Failed to decode raw element ~p from message "
- "archive of user ~s: ~s",
+ "archive of user ~ts: ~ts",
[El, jid:encode(JidArchive), xmpp:format_error(Why)]),
{error, invalid_xml}
end.
{atomic, ok} ->
delete_old_user_messages(NextRecord, TimeStamp, Type);
{aborted, Err} ->
- ?ERROR_MSG("Cannot delete old MAM messages: ~s", [Err]),
+ ?ERROR_MSG("Cannot delete old MAM messages: ~ts", [Err]),
Err
end.
case {mnesia:table_info(archive_msg, disc_only_copies),
mnesia:table_info(archive_msg, memory)} of
{[_|_], TableSize} when TableSize > ?TABLE_SIZE_LIMIT ->
- ?ERROR_MSG("MAM archives too large, won't store message for ~s@~s",
+ ?ERROR_MSG("MAM archives too large, won't store message for ~ts@~ts",
[LUser, LServer]),
{error, overflow};
_ ->
{atomic, ok} ->
ok;
{aborted, Err} ->
- ?ERROR_MSG("Cannot add message to MAM archive of ~s@~s: ~s",
+ ?ERROR_MSG("Cannot add message to MAM archive of ~ts@~ts: ~ts",
[LUser, LServer, Err]),
Err
end
MsgType, JidRequestor, JidArchive)
catch _:{bad_jid, _} ->
?ERROR_MSG("Malformed 'peer' field with value "
- "'~s' detected for user ~s in table "
+ "'~ts' detected for user ~ts in table "
"'archive': invalid JID",
[Peer, jid:encode(JidArchive)]),
{error, invalid_jid}
end
catch _:_ ->
- ?ERROR_MSG("Malformed 'timestamp' field with value '~s' "
- "detected for user ~s in table 'archive': "
+ ?ERROR_MSG("Malformed 'timestamp' field with value '~ts' "
+ "detected for user ~ts in table 'archive': "
"not an integer",
[TS, jid:encode(JidArchive)]),
{error, invalid_timestamp}
end;
{error, {_, Reason}} ->
- ?ERROR_MSG("Malformed 'xml' field with value '~s' detected "
- "for user ~s in table 'archive': ~s",
+ ?ERROR_MSG("Malformed 'xml' field with value '~ts' detected "
+ "for user ~ts in table 'archive': ~ts",
[XML, jid:encode(JidArchive), Reason]),
{error, invalid_xml}
end.
get_socket(N-1)
end;
{error, Reason} = Err ->
- ?ERROR_MSG("Can not open udp socket to grapherl: ~s",
+ ?ERROR_MSG("Can not open udp socket to grapherl: ~ts",
[inet:format_error(Reason)]),
Err
end;
process_mix_message(Msg)
end;
route(Pkt) ->
- ?DEBUG("Dropping packet:~n~s", [xmpp:pp(Pkt)]).
+ ?DEBUG("Dropping packet:~n~ts", [xmpp:pp(Pkt)]).
-spec process_disco_info(iq()) -> iq().
process_disco_info(#iq{type = set, lang = Lang} = IQ) ->
try route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
%%%===================================================================
-spec report_corrupted(#sql_query{}) -> ok.
report_corrupted(SQL) ->
- ?ERROR_MSG("Corrupted values returned by SQL request: ~s",
+ ?ERROR_MSG("Corrupted values returned by SQL request: ~ts",
[SQL#sql_query.hash]).
%%%===================================================================
-spec report_corrupted(atom(), #sql_query{}) -> ok.
report_corrupted(Column, SQL) ->
- ?ERROR_MSG("Corrupted value of '~s' column returned by "
- "SQL request: ~s", [Column, SQL#sql_query.hash]).
+ ?ERROR_MSG("Corrupted value of '~ts' column returned by "
+ "SQL request: ~ts", [Column, SQL#sql_query.hash]).
when Pid == self() ->
route(Mod, LServer, Pkt, ExpiryTime, Continuation1, Num);
{ok, {Pid, SubOpts, ID}, Continuation1} ->
- ?DEBUG("Route to ~p: ~s", [Pid, Pkt#publish.topic]),
+ ?DEBUG("Route to ~p: ~ts", [Pid, Pkt#publish.topic]),
MinQoS = min(SubOpts#sub_opts.qos, Pkt#publish.qos),
Retain = case SubOpts#sub_opts.retain_as_published of
false -> false;
catch ets:new(?MQTT_TOPIC_CACHE,
[named_table, ordered_set, public,
{heir, erlang:group_leader(), none}]),
- ?INFO_MSG("Building MQTT cache for ~s, this may take a while", [Host]),
+ ?INFO_MSG("Building MQTT cache for ~ts, this may take a while", [Host]),
case Mod:list_topics(Host) of
{ok, Topics} ->
lists:foreach(
case mnesia:transaction(F) of
{atomic, _} -> ok;
{aborted, Reason} ->
- db_fail("Failed to register MQTT session for ~s",
+ db_fail("Failed to register MQTT session for ~ts",
Reason, [jid:encode(USR)])
end.
case mnesia:transaction(F) of
{atomic, _} -> ok;
{aborted, Reason} ->
- db_fail("Failed to subscribe ~s to ~s",
+ db_fail("Failed to subscribe ~ts to ~ts",
Reason, [jid:encode(USR), TopicFilter])
end.
case mnesia:transaction(F) of
{atomic, _} -> ok;
{aborted, Reason} ->
- db_fail("Failed to unsubscribe ~s from ~s",
+ db_fail("Failed to unsubscribe ~ts from ~ts",
Reason, [jid:encode(USR), Topic])
end.
case mnesia:transaction(F) of
{atomic, _} -> ok;
{aborted, Reason} ->
- db_fail("Failed to unregister MQTT session for ~s",
+ db_fail("Failed to unregister MQTT session for ~ts",
Reason, [jid:encode(USR)])
end.
format_error({payload_format_invalid, publish}) ->
"PUBLISH payload format doesn't match its indicator";
format_error({peer_disconnected, Code, <<>>}) ->
- format("Peer disconnected with reason: ~s",
+ format("Peer disconnected with reason: ~ts",
[mqtt_codec:format_reason_code(Code)]);
format_error({peer_disconnected, Code, Reason}) ->
- format("Peer disconnected with reason: ~s (~s)", [Reason, Code]);
+ format("Peer disconnected with reason: ~ts (~ts)", [Reason, Code]);
format_error({replaced, Pid}) ->
- format("Replaced by ~p at ~s", [Pid, node(Pid)]);
+ format("Replaced by ~p at ~ts", [Pid, node(Pid)]);
format_error({resumed, Pid}) ->
- format("Resumed by ~p at ~s", [Pid, node(Pid)]);
+ format("Resumed by ~p at ~ts", [Pid, node(Pid)]);
format_error({unexpected_packet, Name}) ->
- format("Unexpected ~s packet", [string:to_upper(atom_to_list(Name))]);
+ format("Unexpected ~ts packet", [string:to_upper(atom_to_list(Name))]);
format_error({tls, Reason}) ->
- format("TLS failed: ~s", [format_tls_error(Reason)]);
+ format("TLS failed: ~ts", [format_tls_error(Reason)]);
format_error({socket, A}) ->
- format("Connection failed: ~s", [format_inet_error(A)]);
+ format("Connection failed: ~ts", [format_inet_error(A)]);
format_error({code, Code}) ->
- format("Protocol error: ~s", [mqtt_codec:format_reason_code(Code)]);
+ format("Protocol error: ~ts", [mqtt_codec:format_reason_code(Code)]);
format_error({auth, Code}) ->
- format("Authentication failed: ~s", [mqtt_codec:format_reason_code(Code)]);
+ format("Authentication failed: ~ts", [mqtt_codec:format_reason_code(Code)]);
format_error({codec, CodecError}) ->
- format("Protocol error: ~s", [mqtt_codec:format_error(CodecError)]);
+ format("Protocol error: ~ts", [mqtt_codec:format_error(CodecError)]);
format_error(A) when is_atom(A) ->
atom_to_list(A);
format_error(Reason) ->
{stop, Status, State1} ->
{stop, Status, State1#state{stop_reason = {replaced, Pid}}};
{noreply, State1, _} ->
- ?DEBUG("Transferring MQTT session state to ~p at ~s", [Pid, node(Pid)]),
+ ?DEBUG("Transferring MQTT session state to ~p at ~ts", [Pid, node(Pid)]),
Q1 = p1_queue:file_to_ram(State1#state.queue),
p1_server:reply(From, {ok, State1#state{queue = Q1}}),
SessionExpiry = State1#state.session_expiry,
handle_info(Msg, #state{stop_reason = {resumed, Pid} = Reason} = State) ->
case Msg of
{#publish{}, _} ->
- ?DEBUG("Relaying delayed publish to ~p at ~s", [Pid, node(Pid)]),
+ ?DEBUG("Relaying delayed publish to ~p at ~ts", [Pid, node(Pid)]),
ejabberd_cluster:send(Pid, Msg),
noreply(State);
timeout ->
{ok, Data} ->
case mqtt_codec:decode(Codec, Data) of
{ok, Pkt, Codec1} ->
- ?DEBUG("Got MQTT packet:~n~s", [pp(Pkt)]),
+ ?DEBUG("Got MQTT packet:~n~ts", [pp(Pkt)]),
State1 = State#state{codec = Codec1},
case handle_packet(Pkt, State1) of
{ok, State2} ->
?DEBUG("MQTT connection reset by peer", []),
stop(State, {socket, closed});
handle_info({tcp_error, _Sock, Reason}, State) ->
- ?DEBUG("MQTT connection error: ~s", [format_inet_error(Reason)]),
+ ?DEBUG("MQTT connection error: ~ts", [format_inet_error(Reason)]),
stop(State, {socket, Reason});
handle_info(timeout, #state{socket = Socket} = State) ->
case Socket of
handle_packet(#puback{id = ID}, #state{in_flight = #publish{qos = 1, id = ID}} = State) ->
resend(State#state{in_flight = undefined});
handle_packet(#puback{id = ID, code = Code}, State) ->
- ?DEBUG("Ignoring unexpected PUBACK with id=~B and code '~s'", [ID, Code]),
+ ?DEBUG("Ignoring unexpected PUBACK with id=~B and code '~ts'", [ID, Code]),
{ok, State};
handle_packet(#pubrec{id = ID, code = Code},
#state{in_flight = #publish{qos = 2, id = ID}} = State) ->
case mqtt_codec:is_error_code(Code) of
true ->
- ?DEBUG("Got PUBREC with error code '~s', "
+ ?DEBUG("Got PUBREC with error code '~ts', "
"aborting acknowledgement", [Code]),
resend(State#state{in_flight = undefined});
false ->
handle_packet(#pubrec{id = ID, code = Code}, State) ->
case mqtt_codec:is_error_code(Code) of
true ->
- ?DEBUG("Ignoring unexpected PUBREC with id=~B and code '~s'",
+ ?DEBUG("Ignoring unexpected PUBREC with id=~B and code '~ts'",
[ID, Code]),
{ok, State};
false ->
Code1 = 'packet-identifier-not-found',
?DEBUG("Unexpected PUBREC with id=~B, "
- "sending PUBREL with error code '~s'", [ID, Code1]),
+ "sending PUBREL with error code '~ts'", [ID, Code1]),
send(State, #pubrel{id = ID, code = Code1})
end;
handle_packet(#pubcomp{id = ID}, #state{in_flight = #pubrel{id = ID}} = State) ->
error ->
Code = 'packet-identifier-not-found',
?DEBUG("Unexpected PUBREL with id=~B, "
- "sending PUBCOMP with error code '~s'", [ID, Code]),
+ "sending PUBCOMP with error code '~ts'", [ID, Code]),
Pubcomp = #pubcomp{id = ID, code = Code},
send(State, Pubcomp)
end;
end,
{error, State2, {peer_disconnected, Code, Reason}};
handle_packet(Pkt, State) ->
- ?WARNING_MSG("Unexpected packet:~n~s~n** when state:~n~s",
+ ?WARNING_MSG("Unexpected packet:~n~ts~n** when state:~n~ts",
[pp(Pkt), pp(State)]),
{error, State, {unexpected_packet, element(1, Pkt)}}.
subscriptions = State2#state.subscriptions,
id = State2#state.id,
in_flight = State2#state.in_flight},
- ?DEBUG("Resumed state from ~p at ~s:~n~s",
+ ?DEBUG("Resumed state from ~p at ~ts:~n~ts",
[Pid, node(Pid), pp(State3)]),
register_session(State3, JID, Pid);
{error, Why} ->
{error, State, Why}
catch exit:{Why, {p1_server, _, _}} ->
- ?WARNING_MSG("Failed to copy session state from ~p at ~s: ~s",
+ ?WARNING_MSG("Failed to copy session state from ~p at ~ts: ~ts",
[Pid, node(Pid), format_exit_reason(Why)]),
register_session(State, JID, undefined)
end;
ok ->
case resubscribe(USR, State#state.subscriptions) of
ok ->
- ?INFO_MSG("~s for ~s from ~s",
+ ?INFO_MSG("~ts for ~ts from ~ts",
[if is_pid(Parent) ->
io_lib:format(
"Reopened MQTT session via ~p",
{error, State#state{session_expiry = 0}, Why}
end;
{error, Reason} ->
- ?ERROR_MSG("Failed to register MQTT session for ~s from ~s: ~s",
+ ?ERROR_MSG("Failed to register MQTT session for ~ts from ~ts: ~ts",
err_args(JID, IP, Reason)),
{error, State, Reason}
end.
-spec unregister_session(state(), error_reason()) -> ok.
unregister_session(#state{jid = #jid{} = JID, peername = IP} = State, Reason) ->
- Msg = "Closing MQTT session for ~s from ~s: ~s",
+ Msg = "Closing MQTT session for ~ts from ~ts: ~ts",
case Reason of
{Tag, _} when Tag == replaced; Tag == resumed ->
?DEBUG(Msg, err_args(JID, IP, Reason));
ok -> ok;
{error, Why} ->
?ERROR_MSG(
- "Failed to close MQTT session for ~s from ~s: ~s",
+ "Failed to close MQTT session for ~ts from ~ts: ~ts",
err_args(JID, IP, Why))
end;
unregister_session(_, _) ->
State1 = State#state{in_flight = Dup},
{ok, do_send(State1, Pkt1)};
false ->
- ?DEBUG("Queueing packet:~n~s~n** when state:~n~s",
+ ?DEBUG("Queueing packet:~n~ts~n** when state:~n~ts",
[pp(Pkt), pp(State)]),
try p1_queue:in(Pkt, State#state.queue) of
Q ->
-spec do_send(state(), mqtt_packet()) -> state().
do_send(#state{socket = {SockMod, Sock} = Socket} = State, Pkt) ->
- ?DEBUG("Send MQTT packet:~n~s", [pp(Pkt)]),
+ ?DEBUG("Send MQTT packet:~n~ts", [pp(Pkt)]),
Data = mqtt_codec:encode(State#state.version, Pkt),
Res = SockMod:send(Sock, Data),
check_sock_result(Socket, Res),
Props1 = Props#{message_expiry_interval => Left},
{false, Pkt#publish{properties = Props1}};
true ->
- ?DEBUG("Dropping expired packet:~n~s", [pp(Pkt)]),
+ ?DEBUG("Dropping expired packet:~n~ts", [pp(Pkt)]),
true
end
end.
LUser, <<>>, LServer, Pass) of
{true, AuthModule} ->
?INFO_MSG(
- "Accepted MQTT authentication for ~s "
- "by ~s backend from ~s",
+ "Accepted MQTT authentication for ~ts "
+ "by ~ts backend from ~ts",
[jid:encode(JID),
ejabberd_auth:backend_type(AuthModule),
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
jid = #jid{} = JID} = State) ->
case publish(State, Will) of
{ok, _} ->
- ?DEBUG("Will of ~s has been published to ~s",
+ ?DEBUG("Will of ~ts has been published to ~ts",
[jid:encode(JID), Will#publish.topic]);
{error, Why} ->
- ?WARNING_MSG("Failed to publish will of ~s to ~s: ~s",
+ ?WARNING_MSG("Failed to publish will of ~ts to ~ts: ~ts",
[jid:encode(JID), Will#publish.topic,
format_error(Why)])
end,
-spec log_disconnection(state(), error_reason()) -> ok.
log_disconnection(#state{jid = JID, peername = IP}, Reason) ->
Msg = case JID of
- undefined -> "Rejected MQTT connection from ~s: ~s";
- _ -> "Closing MQTT connection for ~s from ~s: ~s"
+ undefined -> "Rejected MQTT connection from ~ts: ~ts";
+ _ -> "Closing MQTT connection for ~ts from ~ts: ~ts"
end,
case Reason of
{Tag, _} when Tag == replaced; Tag == resumed; Tag == socket ->
{ok, {Payload, QoS, Props, Expiry}}
catch _:badarg ->
?ERROR_MSG("Malformed value of 'payload_format' column "
- "for topic '~s'", [Topic]),
+ "for topic '~ts'", [Topic]),
{error, db_failure}
end
catch _:badarg ->
?ERROR_MSG("Malformed value of 'user_properties' column "
- "for topic '~s'", [Topic]),
+ "for topic '~ts'", [Topic]),
{error, db_failure}
end;
{selected, []} ->
Pid when Pid == self() ->
route_to_room(Pkt, ServerHost);
Pid when is_pid(Pid) ->
- ?DEBUG("Routing to MUC worker ~p:~n~s", [Proc, xmpp:pp(Pkt)]),
+ ?DEBUG("Routing to MUC worker ~p:~n~ts", [Proc, xmpp:pp(Pkt)]),
?GEN_SERVER:cast(Pid, {route_to_room, Pkt});
undefined ->
?DEBUG("MUC worker ~p is dead", [Proc]),
{stop, normal, ok, State};
handle_call({create, Room, Host, From, Nick, Opts}, _From,
#{server_host := ServerHost} = State) ->
- ?DEBUG("MUC: create new room '~s'~n", [Room]),
+ ?DEBUG("MUC: create new room '~ts'~n", [Room]),
NewOpts = case Opts of
default -> mod_muc_opt:default_room_options(ServerHost);
_ -> Opts
try route_to_room(Packet, ServerHost)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
try route(Packet, ServerHost)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
RMod = gen_mod:ram_db_mod(Opts, ?MODULE),
lists:foreach(
fun(Host) ->
- ?DEBUG("Loading rooms at ~s", [Host]),
+ ?DEBUG("Loading rooms at ~ts", [Host]),
lists:foreach(
fun(R) ->
{Room, _} = R#muc_room.name_host,
Opts0 ->
case proplists:get_bool(persistent, Opts0) of
true ->
- ?DEBUG("Restore room: ~s", [Room]),
+ ?DEBUG("Restore room: ~ts", [Room]),
start_room(RMod, Host, ServerHost, Room, Opts0);
_ ->
- ?DEBUG("Restore hibernated non-persistent room: ~s", [Room]),
+ ?DEBUG("Restore hibernated non-persistent room: ~ts", [Room]),
Res = start_room(RMod, Host, ServerHost, Room, Opts0),
Mod = gen_mod:db_mod(ServerHost, mod_muc),
case erlang:function_exported(Mod, get_subscribed_rooms, 3) of
end.
start_new_room(RMod, Host, ServerHost, Room, Pass, From, Nick) ->
- ?DEBUG("Open new room: ~s", [Room]),
+ ?DEBUG("Open new room: ~ts", [Room]),
DefRoomOpts = mod_muc_opt:default_room_options(ServerHost),
DefRoomOpts2 = add_password_options(Pass, DefRoomOpts),
start_room(RMod, Host, ServerHost, Room, DefRoomOpts2, From, Nick).
%% Create the room only in the database.
%% It is required to restart the MUC service for the room to appear.
muc_create_room(ServerHost, {Name, Host, _}, DefRoomOpts) ->
- io:format("Creating room ~s@~s~n", [Name, Host]),
+ io:format("Creating room ~ts@~ts~n", [Name, Host]),
mod_muc:store_room(ServerHost, Host, Name, DefRoomOpts).
%% @spec (Name::binary(), Host::binary()) ->
end.
destroy_room({N, H, SH}) ->
- io:format("Destroying room: ~s@~s - vhost: ~s~n", [N, H, SH]),
+ io:format("Destroying room: ~ts@~ts - vhost: ~ts~n", [N, H, SH]),
destroy_room(N, H).
case io:get_line(F, "") of
eof -> eof;
String ->
- case io_lib:fread("~s", String) of
+ case io_lib:fread("~ts", String) of
{ok, [RoomJID], _} -> split_roomjid(list_to_binary(RoomJID));
{error, What} ->
io:format("Parse error: what: ~p~non the line: ~p~n~n", [What, String])
rooms_report(Method, Action, Service, Days) ->
{NA, NP, RP} = muc_unused(Method, Action, Service, Days),
- io:format("rooms ~s: ~p out of ~p~n", [Method, NP, NA]),
+ io:format("rooms ~ts: ~p out of ~p~n", [Method, NP, NA]),
[<<R/binary, "@", H/binary>> || {R, H, _SH, _P} <- RP].
muc_unused(Method, Action, Service, Last_allowed) ->
act_on_room(Method, destroy, {N, H, SH, Pid}) ->
Message = iolist_to_binary(io_lib:format(
- <<"Room destroyed by rooms_~s_destroy.">>, [Method])),
+ <<"Room destroyed by rooms_~ts_destroy.">>, [Method])),
mod_muc_room:destroy(Pid, Message),
mod_muc:room_destroyed(H, N, Pid, SH),
mod_muc:forget_room(SH, H, N);
fw(F, <<"<div class=\"legend\">">>),
fw(F,
<<" <a href=\"http://www.ejabberd.im\"><img "
- "style=\"border:0\" src=\"~s/powered-by-ejabbe"
+ "style=\"border:0\" src=\"~ts/powered-by-ejabbe"
"rd.png\" alt=\"Powered by ejabberd - robust, scalable and extensible XMPP server\"/></a>">>,
[Images_dir]),
fw(F,
<<" <a href=\"http://www.erlang.org/\"><img "
- "style=\"border:0\" src=\"~s/powered-by-erlang"
+ "style=\"border:0\" src=\"~ts/powered-by-erlang"
".png\" alt=\"Powered by Erlang\"/></a>">>,
[Images_dir]),
fw(F, <<"<span class=\"w3c\">">>),
fw(F,
<<" <a href=\"http://validator.w3.org/check?uri"
"=referer\"><img style=\"border:0;width:88px;h"
- "eight:31px\" src=\"~s/valid-xhtml10.png\" "
+ "eight:31px\" src=\"~ts/valid-xhtml10.png\" "
"alt=\"Valid XHTML 1.0 Transitional\" "
"/></a>">>,
[Images_dir]),
fw(F,
<<" <a href=\"http://jigsaw.w3.org/css-validato"
"r/\"><img style=\"border:0;width:88px;height:"
- "31px\" src=\"~s/vcss.png\" alt=\"Valid "
+ "31px\" src=\"~ts/vcss.png\" alt=\"Valid "
"CSS!\"/></a>">>,
[Images_dir]),
fw(F, <<"</span></div></body></html>">>).
RoomConfig = roomconfig_to_string(Room#room.config,
Lang, FileFormat),
put_room_config(F, RoomConfig, Lang, FileFormat),
- io_lib:format("<font class=\"mrcm\">~s</font><br/>",
+ io_lib:format("<font class=\"mrcm\">~ts</font><br/>",
[tr(Lang, ?T("Chatroom configuration modified"))]);
{roomconfig_change, Occupants} ->
RoomConfig = roomconfig_to_string(Room#room.config,
RoomOccupants = roomoccupants_to_string(Occupants,
FileFormat),
put_room_occupants(F, RoomOccupants, Lang, FileFormat),
- io_lib:format("<font class=\"mrcm\">~s</font><br/>",
+ io_lib:format("<font class=\"mrcm\">~ts</font><br/>",
[tr(Lang, ?T("Chatroom configuration modified"))]);
join ->
- io_lib:format("<font class=\"mj\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mj\">~ts ~ts</font><br/>",
[Nick, tr(Lang, ?T("joins the room"))]);
leave ->
- io_lib:format("<font class=\"ml\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"ml\">~ts ~ts</font><br/>",
[Nick, tr(Lang, ?T("leaves the room"))]);
{leave, Reason} ->
- io_lib:format("<font class=\"ml\">~s ~s: ~s</font><br/>",
+ io_lib:format("<font class=\"ml\">~ts ~ts: ~ts</font><br/>",
[Nick, tr(Lang, ?T("leaves the room")),
htmlize(Reason, NoFollow, FileFormat)]);
{kickban, 301, <<"">>} ->
- io_lib:format("<font class=\"mb\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mb\">~ts ~ts</font><br/>",
[Nick, tr(Lang, ?T("has been banned"))]);
{kickban, 301, Reason} ->
- io_lib:format("<font class=\"mb\">~s ~s: ~s</font><br/>",
+ io_lib:format("<font class=\"mb\">~ts ~ts: ~ts</font><br/>",
[Nick, tr(Lang, ?T("has been banned")),
htmlize(Reason, FileFormat)]);
{kickban, 307, <<"">>} ->
- io_lib:format("<font class=\"mk\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mk\">~ts ~ts</font><br/>",
[Nick, tr(Lang, ?T("has been kicked"))]);
{kickban, 307, Reason} ->
- io_lib:format("<font class=\"mk\">~s ~s: ~s</font><br/>",
+ io_lib:format("<font class=\"mk\">~ts ~ts: ~ts</font><br/>",
[Nick, tr(Lang, ?T("has been kicked")),
htmlize(Reason, FileFormat)]);
{kickban, 321, <<"">>} ->
- io_lib:format("<font class=\"mk\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mk\">~ts ~ts</font><br/>",
[Nick,
tr(Lang, ?T("has been kicked because of an affiliation "
"change"))]);
{kickban, 322, <<"">>} ->
- io_lib:format("<font class=\"mk\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mk\">~ts ~ts</font><br/>",
[Nick,
tr(Lang, ?T("has been kicked because the room has "
"been changed to members-only"))]);
{kickban, 332, <<"">>} ->
- io_lib:format("<font class=\"mk\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mk\">~ts ~ts</font><br/>",
[Nick,
tr(Lang, ?T("has been kicked because of a system "
"shutdown"))]);
{nickchange, OldNick} ->
- io_lib:format("<font class=\"mnc\">~s ~s ~s</font><br/>",
+ io_lib:format("<font class=\"mnc\">~ts ~ts ~ts</font><br/>",
[htmlize(OldNick, FileFormat),
tr(Lang, ?T("is now known as")), Nick]);
{subject, T} ->
- io_lib:format("<font class=\"msc\">~s~s~s</font><br/>",
+ io_lib:format("<font class=\"msc\">~ts~ts~ts</font><br/>",
[Nick, tr(Lang, ?T(" has set the subject to: ")),
htmlize(T, NoFollow, FileFormat)]);
{body, T} ->
case {ejabberd_regexp:run(T, <<"^/me ">>), Nick} of
{_, <<"">>} ->
- io_lib:format("<font class=\"msm\">~s</font><br/>",
+ io_lib:format("<font class=\"msm\">~ts</font><br/>",
[htmlize(T, NoFollow, FileFormat)]);
{match, _} ->
- io_lib:format("<font class=\"mne\">~s ~s</font><br/>",
+ io_lib:format("<font class=\"mne\">~ts ~ts</font><br/>",
[Nick,
str:substr(htmlize(T, FileFormat), 5)]);
{nomatch, _} ->
- io_lib:format("<font class=\"mn\">~s</font> ~s<br/>",
+ io_lib:format("<font class=\"mn\">~ts</font> ~ts<br/>",
[Nick2, htmlize(T, NoFollow, FileFormat)])
end;
{room_existence, RoomNewExistence} ->
- io_lib:format("<font class=\"mrcm\">~s</font><br/>",
+ io_lib:format("<font class=\"mrcm\">~ts</font><br/>",
[get_room_existence_string(RoomNewExistence,
Lang)])
end,
STime = io_lib:format("~2..0w:~2..0w:~2..0w",
[Hour, Minute, Second]),
{_, _, Microsecs} = Now,
- STimeUnique = io_lib:format("~s.~w",
+ STimeUnique = io_lib:format("~ts.~w",
[STime, Microsecs]),
catch fw(F,
list_to_binary(
- io_lib:format("<a id=\"~s\" name=\"~s\" href=\"#~s\" "
- "class=\"ts\">[~s]</a> ",
+ io_lib:format("<a id=\"~ts\" name=\"~ts\" href=\"#~ts\" "
+ "class=\"ts\">[~ts]</a> ",
[STimeUnique, STimeUnique, STimeUnique, STime])
++ Text),
FileFormat),
list_to_binary(
case Lang of
<<"en">> ->
- io_lib:format("~s, ~s ~w, ~w", [Weekday, Month, D, Y]);
+ io_lib:format("~ts, ~ts ~w, ~w", [Weekday, Month, D, Y]);
<<"es">> ->
- io_lib:format("~s ~w de ~s de ~w",
+ io_lib:format("~ts ~w de ~ts de ~w",
[Weekday, D, Month, Y]);
_ ->
- io_lib:format("~s, ~w ~s ~w", [Weekday, D, Month, Y])
+ io_lib:format("~ts, ~w ~ts ~w", [Weekday, D, Month, Y])
end).
make_dir_rec(Dir) ->
case file:copy(Src, Dst) of
{ok, _} -> ok;
{error, Why} ->
- ?ERROR_MSG("Failed to copy ~s to ~s: ~s",
+ ?ERROR_MSG("Failed to copy ~ts to ~ts: ~ts",
[Src, Dst, file:format_error(Why)])
end
end, Filenames).
"org/TR/xhtml1/DTD/xhtml1-transitional.dtd\">">>),
fw(F,
<<"<html xmlns=\"http://www.w3.org/1999/xhtml\" "
- "xml:lang=\"~s\" lang=\"~s\">">>,
+ "xml:lang=\"~ts\" lang=\"~ts\">">>,
[Lang, Lang]),
fw(F, <<"<head>">>),
fw(F,
<<"<meta http-equiv=\"Content-Type\" content=\"t"
"ext/html; charset=utf-8\" />">>),
- fw(F, <<"<title>~s - ~s</title>">>,
+ fw(F, <<"<title>~ts - ~ts</title>">>,
[htmlize(Room#room.title), Date]),
put_header_css(F, CSSFile),
put_header_script(F),
<<"<div style=\"text-align: right;\"><a "
"style=\"color: #AAAAAA; font-family: "
"monospace; text-decoration: none; font-weight"
- ": bold;\" href=\"~s\">~s</a></div>">>,
+ ": bold;\" href=\"~ts\">~ts</a></div>">>,
[Top_url, Top_text]),
- fw(F, <<"<div class=\"roomtitle\">~s</div>">>,
+ fw(F, <<"<div class=\"roomtitle\">~ts</div>">>,
[htmlize(Room#room.title)]),
fw(F,
- <<"<a class=\"roomjid\" href=\"xmpp:~s?join\">~s"
+ <<"<a class=\"roomjid\" href=\"xmpp:~ts?join\">~ts"
"</a>">>,
[Room#room.jid, Room#room.jid]),
fw(F,
- <<"<div class=\"logdate\">~s<span class=\"w3c\">"
- "<a class=\"nav\" href=\"~s\"><</a> "
+ <<"<div class=\"logdate\">~ts<span class=\"w3c\">"
+ "<a class=\"nav\" href=\"~ts\"><</a> "
"<a class=\"nav\" href=\"./\">^</a> <a "
- "class=\"nav\" href=\"~s\">></a></span></di"
+ "class=\"nav\" href=\"~ts\">></a></span></di"
"v>">>,
[Date, Date_prev, Date_next]),
case {htmlize(Room#room.subject_author),
of
{<<"">>, <<"">>} -> ok;
{SuA, Su} ->
- fw(F, <<"<div class=\"roomsubject\">~s~s~s</div>">>,
+ fw(F, <<"<div class=\"roomsubject\">~ts~ts~ts</div>">>,
[SuA, tr(Lang, ?T(" has set the subject to: ")), Su])
end,
RoomConfig = roomconfig_to_string(Room#room.config,
true -> io_lib:format("~p", [Hour_offset]);
false -> io_lib:format("+~p", [Hour_offset])
end,
- fw(F, <<"<br/><a class=\"ts\">GMT~s</a><br/>">>,
+ fw(F, <<"<br/><a class=\"ts\">GMT~ts</a><br/>">>,
[Time_offset_str]).
put_header_css(F, {file, Path}) ->
put_header_css(F, {url, URL}) ->
fw(F,
<<"<link rel=\"stylesheet\" type=\"text/css\" "
- "href=\"~s\" media=\"all\">">>,
+ "href=\"~ts\" media=\"all\">">>,
[URL]).
put_header_script(F) ->
fw(F, <<"<div class=\"rc\">">>),
fw(F,
<<"<div class=\"rct\" onclick=\"sh('a~p');return "
- "false;\">~s</div>">>,
+ "false;\">~ts</div>">>,
[Now2, tr(Lang, ?T("Room Configuration"))]),
fw(F,
<<"<div class=\"rcos\" id=\"a~p\" style=\"displa"
- "y: none;\" ><br/>~s</div>">>,
+ "y: none;\" ><br/>~ts</div>">>,
[Now2, RoomConfig]),
fw(F, <<"</div>">>).
fw(F, <<"<div class=\"rc\">">>),
fw(F,
<<"<div class=\"rct\" onclick=\"sh('o~p');return "
- "false;\">~s</div>">>,
+ "false;\">~ts</div>">>,
[Now2, tr(Lang, ?T("Room Occupants"))]),
fw(F,
<<"<div class=\"rcos\" id=\"o~p\" style=\"displa"
- "y: none;\" ><br/>~s</div>">>,
+ "y: none;\" ><br/>~ts</div>">>,
[Now2, RoomOccupants]),
fw(F, <<"</div>">>).
room_shaper = Shaper}),
State1 = set_opts(DefRoomOpts, State),
store_room(State1),
- ?INFO_MSG("Created MUC room ~s@~s by ~s",
+ ?INFO_MSG("Created MUC room ~ts@~ts by ~ts",
[Room, Host, jid:encode(Creator)]),
add_to_log(room_existence, created, State1),
add_to_log(room_existence, started, State1),
case is_user_online(From, StateData) of
true ->
ErrorText = ?T("It is not allowed to send error messages to the"
- " room. The participant (~s) has sent an error "
- "message (~s) and got kicked from the room"),
+ " room. The participant (~ts) has sent an error "
+ "message (~ts) and got kicked from the room"),
NewState = expulse_participant(Packet, From, StateData,
translate:translate(Lang,
ErrorText)),
{expulse_sender, Reason} ->
?DEBUG(Reason, []),
ErrorText = ?T("It is not allowed to send error messages to the"
- " room. The participant (~s) has sent an error "
- "message (~s) and got kicked from the room"),
+ " room. The participant (~ts) has sent an error "
+ "message (~ts) and got kicked from the room"),
NewState = expulse_participant(Packet, From, StateData,
translate:translate(Lang, ErrorText)),
{next_state, normal_state, NewState};
case maps:size(StateData#state.users) of
0 ->
store_room_no_checks(StateData, []),
- ?INFO_MSG("Hibernating room ~s@~s", [StateData#state.room, StateData#state.host]),
+ ?INFO_MSG("Hibernating room ~ts@~ts", [StateData#state.room, StateData#state.host]),
{stop, normal, StateData#state{hibernate_timer = hibernating}};
_ ->
{next_state, normal_state, StateData}
handle_event({destroy, Reason}, _StateName,
StateData) ->
_ = destroy_room(#muc_destroy{xmlns = ?NS_MUC_OWNER, reason = Reason}, StateData),
- ?INFO_MSG("Destroyed MUC room ~s with reason: ~p",
+ ?INFO_MSG("Destroyed MUC room ~ts with reason: ~p",
[jid:encode(StateData#state.jid), Reason]),
add_to_log(room_existence, destroyed, StateData),
Conf = StateData#state.config,
{stop, shutdown, StateData#state{config = Conf#config{persistent = false}}};
handle_event(destroy, StateName, StateData) ->
- ?INFO_MSG("Destroyed MUC room ~s",
+ ?INFO_MSG("Destroyed MUC room ~ts",
[jid:encode(StateData#state.jid)]),
handle_event({destroy, <<"">>}, StateName, StateData);
handle_event({set_affiliations, Affiliations},
terminate(Reason, _StateName,
#state{server_host = LServer, host = Host, room = Room} = StateData) ->
try
- ?INFO_MSG("Stopping MUC room ~s@~s", [Room, Host]),
+ ?INFO_MSG("Stopping MUC room ~ts@~ts", [Room, Host]),
ReasonT = case Reason of
shutdown ->
?T("You are being removed from the room "
catch ?EX_RULE(E, R, St) ->
StackTrace = ?EX_STACK(St),
mod_muc:room_destroyed(Host, Room, self(), LServer),
- ?ERROR_MSG("Got exception on room termination:~n** ~s",
+ ?ERROR_MSG("Got exception on room termination:~n** ~ts",
[misc:format_exception(2, E, R, StackTrace)])
end.
%%%----------------------------------------------------------------------
-spec route(pid(), stanza()) -> ok.
route(Pid, Packet) ->
- ?DEBUG("Routing to MUC room ~p:~n~s", [Pid, xmpp:pp(Packet)]),
+ ?DEBUG("Routing to MUC room ~p:~n~ts", [Pid, xmpp:pp(Packet)]),
#jid{lresource = Nick} = xmpp:get_to(Packet),
p1_fsm:send_event(Pid, {route, Nick, Packet}).
do_process_presence(_Nick, #presence{from = From, type = error, lang = Lang} = Packet,
StateData) ->
ErrorText = ?T("It is not allowed to send error messages to the"
- " room. The participant (~s) has sent an error "
- "message (~s) and got kicked from the room"),
+ " room. The participant (~ts) has sent an error "
+ "message (~ts) and got kicked from the room"),
expulse_participant(Packet, From, StateData,
translate:translate(Lang, ErrorText)).
andalso maps:size(StateData1#state.users) == 0
andalso maps:size(StateData1#state.subscribers) == 0 of
true ->
- ?INFO_MSG("Destroyed MUC room ~s because it's temporary "
+ ?INFO_MSG("Destroyed MUC room ~ts because it's temporary "
"and empty",
[jid:encode(StateData1#state.jid)]),
add_to_log(room_existence, destroyed, StateData1),
%% If this is an error stanza and its condition matches a criteria
true ->
Reason = str:format("This participant is considered a ghost "
- "and is expulsed: ~s",
+ "and is expulsed: ~ts",
[jid:encode(From)]),
{expulse_sender, Reason};
false -> continue_delivery
Items, Lang, StateData, [])
of
{result, Res} ->
- ?INFO_MSG("Processing MUC admin query from ~s in "
- "room ~s:~n ~p",
+ ?INFO_MSG("Processing MUC admin query from ~ts in "
+ "room ~ts:~n ~p",
[jid:encode(UJID),
jid:encode(StateData#state.jid), Res]),
case lists:foldl(process_item_change(UJID),
undefined ->
<<"">>
end,
- ?ERROR_MSG("Failed to set item ~p~s:~n** ~s",
+ ?ERROR_MSG("Failed to set item ~p~ts:~n** ~ts",
[Item, FromSuffix,
misc:format_exception(2, E, R, StackTrace)]),
{error, xmpp:err_internal_server_error()}
Nick /= <<"">> ->
case find_jids_by_nick(Nick, StateData) of
[] ->
- ErrText = {?T("Nickname ~s does not exist in the room"),
+ ErrText = {?T("Nickname ~ts does not exist in the room"),
[Nick]},
throw({error, xmpp:err_not_acceptable(ErrText, Lang)});
JIDList ->
ErrText = ?T("Owner privileges required"),
{error, xmpp:err_forbidden(ErrText, Lang)};
Destroy /= undefined, Config == undefined, Items == [] ->
- ?INFO_MSG("Destroyed MUC room ~s by the owner ~s",
+ ?INFO_MSG("Destroyed MUC room ~ts by the owner ~ts",
[jid:encode(StateData#state.jid), jid:encode(From)]),
add_to_log(room_existence, destroyed, StateData),
destroy_room(Destroy, StateData);
Config = StateData#state.config,
MaxUsersRoom = get_max_users(StateData),
Title = str:format(
- translate:translate(Lang, ?T("Configuration of room ~s")),
+ translate:translate(Lang, ?T("Configuration of room ~ts")),
[jid:encode(StateData#state.jid)]),
Fs = [{roomname, Config#config.title},
{roomdesc, Config#config.description},
[Opt, Lang]) of
{0, undefined} ->
?ERROR_MSG("set_room_option hook failed for "
- "option '~s' with value ~p", [O, V]),
- Txt = {?T("Failed to process option '~s'"), [O]},
+ "option '~ts' with value ~p", [O, V]),
+ Txt = {?T("Failed to process option '~ts'"), [O]},
{error, xmpp:err_internal_server_error(Txt, Lang)};
{Pos, Val} ->
setelement(Pos, C, Val)
[io_lib:format(
translate:translate(
Lang,
- ?T("~s invites you to the room ~s")),
+ ?T("~ts invites you to the room ~ts")),
[jid:encode(From),
jid:encode({StateData#state.room, StateData#state.host, <<"">>})]),
case (StateData#state.config)#config.password_protected of
ejabberd_sql:sql_query_t(?SQL("delete from muc_room_subscribers where "
"room=%(Room)s and host=%(Host)s and jid=%(SJID)s"));
change_room(Host, Room, Change) ->
- ?ERROR_MSG("Unsupported change on room ~s@~s: ~p", [Room, Host, Change]).
+ ?ERROR_MSG("Unsupported change on room ~ts@~ts: ~p", [Room, Host, Change]).
restore_room(LServer, Host, Name) ->
case catch ejabberd_sql:sql_query(
|| Dest <- Dests],
[route_error(
xmpp:set_from_to(Packet, From, From), jid_malformed,
- str:format(?T("This service can not process the address: ~s"), [D]))
+ str:format(?T("This service can not process the address: ~ts"), [D]))
|| D <- Dests2].
%%%-------------------------
Pkt2 = add_delay_info(Pkt1, LServer, R#offline_msg.timestamp),
{route, Pkt2}
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode packet ~p of user ~s: ~s",
+ ?ERROR_MSG("Failed to decode packet ~p of user ~ts: ~ts",
[R#offline_msg.packet, jid:encode(To),
xmpp:format_error(Why)]),
error
[{Node, Pkt2}]
catch _:{xmpp_codec, Why} ->
?ERROR_MSG("Failed to decode packet ~p "
- "of user ~s: ~s",
+ "of user ~ts: ~ts",
[El, jid:encode(To),
xmpp:format_error(Why)]),
[]
end,
Hdrs = get_messages_subset(User, Server, HdrsAll),
FMsgs = format_user_queue(Hdrs),
- PageTitle = str:format(translate:translate(Lang, ?T("~s's Offline Messages Queue")), [us_to_list(US)]),
+ PageTitle = str:format(translate:translate(Lang, ?T("~ts's Offline Messages Queue")), [us_to_list(US)]),
(?H1GL(PageTitle, <<"mod-offline">>, <<"mod_offline">>))
++ [?XREST(?T("Submitted"))] ++
[?XAE(<<"form">>,
User, Server, _Query) ->
case delete_all_msgs(User, Server) of
{atomic, ok} ->
- ?INFO_MSG("Removed all offline messages for ~s@~s",
+ ?INFO_MSG("Removed all offline messages for ~ts@~ts",
[User, Server]),
{stop, ok};
Err ->
"server_host=%(LServer)s",
"xml=%(XML)s"])]
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode packet ~p of user ~s@~s: ~s",
+ ?ERROR_MSG("Failed to decode packet ~p of user ~ts@~ts: ~ts",
[El, LUser, LServer, xmpp:format_error(Why)]),
[]
end;
#xmlel{} = El ->
el_to_offline_msg(El);
Err ->
- ?ERROR_MSG("Got ~p when parsing XML packet ~s",
+ ?ERROR_MSG("Got ~p when parsing XML packet ~ts",
[Err, XML]),
Err
end.
write(Dir, R#pres_counter{logged = true}),
case Dir of
in ->
- ?WARNING_MSG("User ~s is being flooded, ignoring received "
+ ?WARNING_MSG("User ~ts is being flooded, ignoring received "
"presence subscriptions",
[jid:encode(JID)]);
out ->
IP = ejabberd_sm:get_user_ip(JID#jid.luser,
JID#jid.lserver,
JID#jid.lresource),
- ?WARNING_MSG("Flooder detected: ~s, on IP: ~s ignoring "
+ ?WARNING_MSG("Flooder detected: ~ts, on IP: ~ts ignoring "
"sent presence subscriptions~n",
[jid:encode(JID),
misc:ip_to_list(IP)])
#privacy_query{default = undefined, active = Active} ->
case Active of
none ->
- ?DEBUG("Removing active privacy list for user: ~s",
+ ?DEBUG("Removing active privacy list for user: ~ts",
[jid:encode(To)]),
State#{privacy_active_list => none};
undefined ->
_ ->
case get_user_list(U, S, Active) of
{ok, _} ->
- ?DEBUG("Setting active privacy list '~s' for user: ~s",
+ ?DEBUG("Setting active privacy list '~ts' for user: ~ts",
[Active, jid:encode(To)]),
State#{privacy_active_list => Active};
_ ->
{ok, {_, List}} ->
do_check_packet(JID, List, Packet, Dir);
_ ->
- ?DEBUG("Non-existing active list '~s' is set "
- "for user '~s'", [ListName, jid:encode(JID)]),
+ ?DEBUG("Non-existing active list '~ts' is set "
+ "for user '~ts'", [ListName, jid:encode(JID)]),
check_packet(Acc, JID, Packet, Dir)
end
end;
{ok, El};
_ ->
?ERROR_MSG("Malformed XML element in SQL table "
- "'private_storage' for user ~s@~s: ~s",
+ "'private_storage' for user ~ts@~ts: ~ts",
[LUser, LServer, XML]),
error
end.
#privilege_perm{access = presence,
type = PresencePerm}]},
?INFO_MSG("Granting permissions to external "
- "component '~s': roster = ~s, presence = ~s, "
- "message = ~s",
+ "component '~ts': roster = ~ts, presence = ~ts, "
+ "message = ~ts",
[Host, RosterPerm, PresencePerm, MessagePerm]),
Msg = #message{from = From, to = To, sub_els = [Priv]},
ejabberd_router:route(Msg),
ets:insert(?MODULE, {ServerHost, Permissions}),
{noreply, State};
true ->
- ?INFO_MSG("Granting no permissions to external component '~s'",
+ ?INFO_MSG("Granting no permissions to external component '~ts'",
[Host]),
{noreply, State}
end;
end),
ok;
_:badarg ->
- ?ERROR_MSG("Malformed data in redis (key = '~s'): ~p",
+ ?ERROR_MSG("Malformed data in redis (key = '~ts'): ~p",
[SIDKey, Val]),
{error, db_failure}
end
catch _:badarg when Val == undefined ->
ok;
_:badarg ->
- ?ERROR_MSG("Malformed data in redis (key = '~s'): ~p",
+ ?ERROR_MSG("Malformed data in redis (key = '~ts'): ~p",
[SIDKey, Val]),
{error, db_failure}
end
catch _:badarg when Val == undefined ->
{error, notfound};
_:badarg ->
- ?ERROR_MSG("Malformed data in redis (key = '~s'): ~p",
+ ?ERROR_MSG("Malformed data in redis (key = '~ts'): ~p",
[SIDKey, Val]),
{error, db_failure}
end
try route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
Txt = ?T("Bytestream already activated"),
xmpp:make_error(IQ, xmpp:err_conflict(Txt, Lang));
{error, Err} ->
- ?ERROR_MSG("Failed to activate bytestream from ~s to ~s: ~p",
+ ?ERROR_MSG("Failed to activate bytestream from ~ts to ~ts: ~p",
[Initiator, Target, Err]),
Txt = ?T("Database failure"),
xmpp:make_error(IQ, xmpp:err_internal_server_error(Txt, Lang))
P2 ! {activate, P1, S1, J1, J2},
JID1 = jid:encode(J1),
JID2 = jid:encode(J2),
- ?INFO_MSG("(~w:~w) Activated bytestream for ~s "
- "-> ~s",
+ ?INFO_MSG("(~w:~w) Activated bytestream for ~ts "
+ "-> ~ts",
[P1, P2, JID1, JID2]),
ok;
_ -> error
fun (Name, Acc) ->
Plugin = plugin(Host, Name),
apply(Plugin, init, [Host, ServerHost, Opts]),
- ?DEBUG("** init ~s plugin", [Name]),
+ ?DEBUG("** init ~ts plugin", [Name]),
[Name | Acc]
end,
[], Plugins),
terminate_plugins(Host, ServerHost, Plugins, TreePlugin) ->
lists:foreach(
fun (Name) ->
- ?DEBUG("** terminate ~s plugin", [Name]),
+ ?DEBUG("** terminate ~ts plugin", [Name]),
Plugin = plugin(Host, Name),
Plugin:terminate(Host, ServerHost)
end,
try route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
-spec send_pending_auth_events(binary(), binary(), jid(),
binary()) -> ok | {error, stanza_error()}.
send_pending_auth_events(Host, Node, Owner, Lang) ->
- ?DEBUG("Sending pending auth events for ~s on ~s:~s",
+ ?DEBUG("Sending pending auth events for ~ts on ~ts:~ts",
[jid:encode(Owner), Host, Node]),
Action =
fun(#pubsub_node{id = Nidx, type = Type}) ->
tree_call(Server, Function, Args);
tree_call(Host, Function, Args) ->
Tree = tree(Host),
- ?DEBUG("Tree_call apply(~s, ~s, ~p) @ ~s", [Tree, Function, Args, Host]),
+ ?DEBUG("Tree_call apply(~ts, ~ts, ~p) @ ~ts", [Tree, Function, Args, Host]),
case apply(Tree, Function, Args) of
{error, #stanza_error{}} = Err ->
Err;
get_tree_action_result({atomic, Result}) ->
Result;
get_tree_action_result({aborted, {exception, Class, Reason, StackTrace}}) ->
- ?ERROR_MSG("Transaction aborted:~n** ~s",
+ ?ERROR_MSG("Transaction aborted:~n** ~ts",
[misc:format_exception(2, Class, Reason, StackTrace)]),
get_tree_action_result({error, db_failure});
get_tree_action_result({aborted, Reason}) ->
Lang = ejabberd_option:language(),
{error, xmpp:err_internal_server_error(?T("Database failure"), Lang)};
get_transaction_response({exception, Class, Reason, StackTrace}) ->
- ?ERROR_MSG("Transaction aborted:~n** ~s",
+ ?ERROR_MSG("Transaction aborted:~n** ~ts",
[misc:format_exception(2, Class, Reason, StackTrace)]),
get_transaction_response({error, db_failure});
get_transaction_response(Err) ->
{TS, PID} ->
case store_session(LUser, LServer, TS, PushJID, Node, XData) of
{ok, _} ->
- ?INFO_MSG("Enabling push notifications for ~s",
+ ?INFO_MSG("Enabling push notifications for ~ts",
[jid:encode(JID)]),
ejabberd_c2s:cast(PID, push_enable);
{error, _} = Err ->
- ?ERROR_MSG("Cannot enable push for ~s: database error",
+ ?ERROR_MSG("Cannot enable push for ~ts: database error",
[jid:encode(JID)]),
Err
end;
none ->
- ?WARNING_MSG("Cannot enable push for ~s: session not found",
+ ?WARNING_MSG("Cannot enable push for ~ts: session not found",
[jid:encode(JID)]),
{error, notfound}
end.
PushJID, Node) ->
case ejabberd_sm:get_session_sid(LUser, LServer, LResource) of
{_TS, PID} ->
- ?INFO_MSG("Disabling push notifications for ~s",
+ ?INFO_MSG("Disabling push notifications for ~ts",
[jid:encode(JID)]),
ejabberd_c2s:cast(PID, push_disable);
none ->
- ?WARNING_MSG("Session not found while disabling push for ~s",
+ ?WARNING_MSG("Session not found while disabling push for ~ts",
[jid:encode(JID)])
end,
if Node /= <<>> ->
{ok, [_|_] = Clients} ->
case drop_online_sessions(LUser, LServer, Clients) of
[_|_] = Clients1 ->
- ?DEBUG("Notifying ~s@~s of MAM message", [LUser, LServer]),
+ ?DEBUG("Notifying ~ts@~ts of MAM message", [LUser, LServer]),
notify(LUser, LServer, Clients1, Pkt, Dir);
[] ->
ok
offline_message(#message{to = #jid{luser = LUser, lserver = LServer}} = Pkt) ->
case lookup_sessions(LUser, LServer) of
{ok, [_|_] = Clients} ->
- ?DEBUG("Notifying ~s@~s of offline message", [LUser, LServer]),
+ ?DEBUG("Notifying ~ts@~ts of offline message", [LUser, LServer]),
notify(LUser, LServer, Clients, Pkt, recv);
_ ->
ok
-spec remove_user(binary(), binary()) -> ok | {error, err_reason()}.
remove_user(LUser, LServer) ->
- ?INFO_MSG("Removing any push sessions of ~s@~s", [LUser, LServer]),
+ ?INFO_MSG("Removing any push sessions of ~ts@~ts", [LUser, LServer]),
Mod = gen_mod:db_mod(LServer, ?MODULE),
LookupFun = fun() -> Mod:lookup_sessions(LUser, LServer) end,
delete_sessions(LUser, LServer, LookupFun, Mod).
fun({TS, PushLJID, Node, XData}) ->
HandleResponse =
fun(#iq{type = result}) ->
- ?DEBUG("~s accepted notification for ~s@~s (~s)",
+ ?DEBUG("~ts accepted notification for ~ts@~ts (~ts)",
[jid:encode(PushLJID), LUser, LServer, Node]);
(#iq{type = error} = IQ) ->
case inspect_error(IQ) of
{wait, Reason} ->
- ?INFO_MSG("~s rejected notification for "
- "~s@~s (~s) temporarily: ~s",
+ ?INFO_MSG("~ts rejected notification for "
+ "~ts@~ts (~ts) temporarily: ~ts",
[jid:encode(PushLJID), LUser,
LServer, Node, Reason]);
{Type, Reason} ->
spawn(?MODULE, delete_session,
[LUser, LServer, TS]),
- ?WARNING_MSG("~s rejected notification for "
- "~s@~s (~s), disabling push: ~s "
- "(~s)",
+ ?WARNING_MSG("~ts rejected notification for "
+ "~ts@~ts (~ts), disabling push: ~ts "
+ "(~ts)",
[jid:encode(PushLJID), LUser,
LServer, Node, Reason, Type])
end;
(timeout) ->
- ?DEBUG("Timeout sending notification for ~s@~s (~s) "
- "to ~s",
+ ?DEBUG("Timeout sending notification for ~ts@~ts (~ts) "
+ "to ~ts",
[LUser, LServer, Node, jid:encode(PushLJID)]),
ok % Hmm.
end,
-spec c2s_handle_info(c2s_state(), any()) -> c2s_state() | {stop, c2s_state()}.
c2s_handle_info(#{push_enabled := true, mgmt_state := pending,
jid := JID} = State, {timeout, _, push_keepalive}) ->
- ?INFO_MSG("Waking ~s before session times out", [jid:encode(JID)]),
+ ?INFO_MSG("Waking ~ts before session times out", [jid:encode(JID)]),
mod_push:notify(State, none, undefined),
{stop, State};
c2s_handle_info(State, _) ->
-spec wake_all(binary()) -> ok.
wake_all(LServer) ->
- ?INFO_MSG("Waking all push clients on ~s", [LServer]),
+ ?INFO_MSG("Waking all push clients on ~ts", [LServer]),
Mod = gen_mod:db_mod(LServer, mod_push),
case Mod:lookup_sessions(LServer) of
{ok, Sessions} ->
{atomic, ok} ->
{ok, {TS, PushLJID, Node, XData}};
{aborted, E} ->
- ?ERROR_MSG("Cannot store push session for ~s@~s: ~p",
+ ?ERROR_MSG("Cannot store push session for ~ts@~ts: ~p",
[LUser, LServer, E]),
{error, db_failure}
end.
[#push_session{timestamp = TS, xml = El}] ->
{ok, {TS, PushLJID, Node, decode_xdata(El)}};
[] ->
- ?DEBUG("No push session found for ~s@~s (~p, ~s)",
+ ?DEBUG("No push session found for ~ts@~ts (~p, ~ts)",
[LUser, LServer, PushJID, Node]),
{error, notfound}
end.
[#push_session{service = PushLJID, node = Node, xml = El}] ->
{ok, {TS, PushLJID, Node, decode_xdata(El)}};
[] ->
- ?DEBUG("No push session found for ~s@~s (~p)",
+ ?DEBUG("No push session found for ~ts@~ts (~p)",
[LUser, LServer, TS]),
{error, notfound}
end.
{atomic, ok} ->
ok;
{aborted, E} ->
- ?ERROR_MSG("Cannot delete push session of ~s@~s: ~p",
+ ?ERROR_MSG("Cannot delete push session of ~ts@~ts: ~p",
[LUser, LServer, E]),
{error, db_failure}
end.
TS1 >= TS2
end, Recs),
OldRecs = lists:nthtail(MaxSessions - 1, Recs1),
- ?INFO_MSG("Disabling old push session(s) of ~s@~s", [U, S]),
+ ?INFO_MSG("Disabling old push session(s) of ~ts@~ts", [U, S]),
lists:foreach(fun(Rec) -> mnesia:delete_object(Rec) end, OldRecs);
_ ->
ok
enforce_max_sessions(LUser, LServer, MaxSessions) ->
case lookup_sessions(LUser, LServer) of
{ok, Sessions} when length(Sessions) >= MaxSessions ->
- ?INFO_MSG("Disabling old push session(s) of ~s@~s",
+ ?INFO_MSG("Disabling old push session(s) of ~ts@~ts",
[LUser, LServer]),
Sessions1 = lists:sort(fun({TS1, _, _, _}, {TS2, _, _, _}) ->
TS1 >= TS2
#xmlel{} = El ->
try xmpp:decode(El)
catch _:{xmpp_codec, Why} ->
- ?ERROR_MSG("Failed to decode ~s for user ~s@~s "
- "from table 'push_session': ~s",
+ ?ERROR_MSG("Failed to decode ~ts for user ~ts@~ts "
+ "from table 'push_session': ~ts",
[XML, LUser, LServer, xmpp:format_error(Why)]),
undefined
end;
Err ->
- ?ERROR_MSG("Failed to decode ~s for user ~s@~s from "
+ ?ERROR_MSG("Failed to decode ~ts for user ~ts@~ts from "
"table 'push_session': ~p",
[XML, LUser, LServer, Err]),
undefined
"with this server")),
URL = mod_register_opt:redirect_url(Server),
if (URL /= undefined) and not IsRegistered ->
- Txt = translate:translate(Lang, ?T("To register, visit ~s")),
+ Txt = translate:translate(Lang, ?T("To register, visit ~ts")),
Desc = str:format(Txt, [URL]),
xmpp:make_iq_result(
IQ, #register{instructions = Desc,
try_set_password(User, Server, Password, #iq{lang = Lang, meta = M} = IQ) ->
case try_set_password(User, Server, Password) of
ok ->
- ?INFO_MSG("~s has changed password from ~s",
+ ?INFO_MSG("~ts has changed password from ~ts",
[jid:encode({User, Server, <<"">>}),
ejabberd_config:may_hide_data(
misc:ip_to_list(maps:get(ip, M, {0,0,0,0})))]),
ok ->
JID = jid:make(User, Server),
Source = may_remove_resource(SourceRaw),
- ?INFO_MSG("The account ~s was registered from IP address ~s",
+ ?INFO_MSG("The account ~ts was registered from IP address ~ts",
[jid:encode({User, Server, <<"">>}),
ejabberd_config:may_hide_data(ip_to_string(Source))]),
send_welcome_message(JID),
[] -> ok;
JIDs when is_list(JIDs) ->
Body =
- (str:format("[~s] The account ~s was registered from "
- "IP address ~s on node ~w using ~p.",
+ (str:format("[~ts] The account ~ts was registered from "
+ "IP address ~ts on node ~w using ~p.",
[get_time_string(),
jid:encode(UJID),
ejabberd_config:may_hide_data(
{ok, Data} ->
{ok, Data};
{error, Why} ->
- ?ERROR_MSG("Failed to read ~s: ~s", [File, file:format_error(Why)]),
+ ?ERROR_MSG("Failed to read ~ts: ~ts", [File, file:format_error(Why)]),
error
end.
end,
SItems)))])]
end,
- PageTitle = str:format(translate:translate(Lang, ?T("Roster of ~s")), [us_to_list(US)]),
+ PageTitle = str:format(translate:translate(Lang, ?T("Roster of ~ts")), [us_to_list(US)]),
(?H1GL(PageTitle, <<"mod-roster">>, <<"mod_roster">>))
++
case Res of
{RUser, RServer, _} = JID,
Jid1string = <<User/binary, "@", Server/binary>>,
Jid2string = <<RUser/binary, "@", RServer/binary>>,
- io:format("Matches: ~s ~s~n", [Jid1string, Jid2string]),
+ io:format("Matches: ~ts ~ts~n", [Jid1string, Jid2string]),
{Jid1string, Jid2string};
apply_action(delete, Key) ->
R = apply_action(list, Key),
subscription = Subscription, ask = Ask,
askmessage = SAskMessage}
catch _:{bad_jid, _} ->
- ?ERROR_MSG("~s", [format_row_error(User, LServer, {jid, SJID})]),
+ ?ERROR_MSG("~ts", [format_row_error(User, LServer, {jid, SJID})]),
error
end.
<<"N">> -> none;
<<"">> -> none;
_ ->
- ?ERROR_MSG("~s", [format_row_error(User, Server, {subscription, S})]),
+ ?ERROR_MSG("~ts", [format_row_error(User, Server, {subscription, S})]),
none
end.
<<"N">> -> none;
<<"">> -> none;
_ ->
- ?ERROR_MSG("~s", [format_row_error(User, Server, {ask, A})]),
+ ?ERROR_MSG("~ts", [format_row_error(User, Server, {ask, A})]),
none
end.
remote_server := RServer} = State, {false, _}) ->
%% SASL authentication has failed, retrying with dialback
%% Sending dialback request, section 2.1.1, step 1
- ?INFO_MSG("(~s) Retrying with s2s dialback authentication: ~s -> ~s (~s)",
+ ?INFO_MSG("(~ts) Retrying with s2s dialback authentication: ~ts -> ~ts (~ts)",
[xmpp_socket:pp(Socket), LServer, RServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
State1 = maps:remove(stop_reason, State#{on_route => queue}),
remote_server := RServer} = State, _) ->
%% non-RFC compliant server detected, send dialback request instantly,
%% section 2.1.1, step 1
- ?INFO_MSG("(~s) Trying s2s dialback authentication with "
- "non-RFC compliant server: ~s -> ~s (~s)",
+ ?INFO_MSG("(~ts) Trying s2s dialback authentication with "
+ "non-RFC compliant server: ~ts -> ~ts (~ts)",
[xmpp_socket:pp(Socket), LServer, RServer,
ejabberd_config:may_hide_data(misc:ip_to_list(IP))]),
{stop, send_db_request(State)};
{stop, ejabberd_s2s_in:send(State, Response)};
s2s_in_packet(State, Pkt) when is_record(Pkt, db_result);
is_record(Pkt, db_verify) ->
- ?WARNING_MSG("Got stray dialback packet:~n~s", [xmpp:pp(Pkt)]),
+ ?WARNING_MSG("Got stray dialback packet:~n~ts", [xmpp:pp(Pkt)]),
State;
s2s_in_packet(State, _) ->
State.
State2 = ejabberd_s2s_out:handle_auth_success(<<"dialback">>, State1),
ejabberd_s2s_out:establish(State2);
_ ->
- Reason = str:format("Peer responded with error: ~s",
+ Reason = str:format("Peer responded with error: ~ts",
[format_error(Result)]),
ejabberd_s2s_out:handle_auth_failure(
<<"dialback">>, {auth, Reason}, State1)
end;
s2s_out_packet(State, Pkt) when is_record(Pkt, db_result);
is_record(Pkt, db_verify) ->
- ?WARNING_MSG("Got stray dialback packet:~n~s", [xmpp:pp(Pkt)]),
+ ?WARNING_MSG("Got stray dialback packet:~n~ts", [xmpp:pp(Pkt)]),
State;
s2s_out_packet(State, _) ->
State.
From, <<"dialback">>, undefined, State1),
ejabberd_s2s_in:establish(State2);
_ ->
- Reason = str:format("Verification failed: ~s",
+ Reason = str:format("Verification failed: ~ts",
[format_error(Response)]),
ejabberd_s2s_in:handle_auth_failure(
From, <<"dialback">>, Reason, State1)
case lists:member(LServer, ejabberd_config:get_option(hosts)) of
true -> add_user_to_group2(Host, US, Group);
false ->
- ?INFO_MSG("Attempted adding to shared roster user of inexistent vhost ~s", [LServer]),
+ ?INFO_MSG("Attempted adding to shared roster user of inexistent vhost ~ts", [LServer]),
error
end.
add_user_to_group2(Host, US, Group) ->
-define(USER_CACHE, shared_roster_ldap_user_cache).
-define(GROUP_CACHE, shared_roster_ldap_group_cache).
-define(LDAP_SEARCH_TIMEOUT, 5). %% Timeout for LDAP search queries in seconds
--define(INVALID_SETTING_MSG, "~s is not properly set! ~s will not function.").
+-define(INVALID_SETTING_MSG, "~ts is not properly set! ~ts will not function.").
-record(state,
{host = <<"">> :: binary(),
addr = {MyIP, MyPort},
peer = {PeerIP, PeerPort}}) ->
?DEBUG(
- "SIP [~p/in] ~s:~p -> ~s:~p:~n~s",
+ "SIP [~p/in] ~ts:~p -> ~ts:~p:~n~ts",
[Transport, inet_parse:ntoa(PeerIP), PeerPort,
inet_parse:ntoa(MyIP), MyPort, Data]).
addr = {MyIP, MyPort},
peer = {PeerIP, PeerPort}}) ->
?DEBUG(
- "SIP [~p/out] ~s:~p -> ~s:~p:~n~s",
+ "SIP [~p/out] ~ts:~p -> ~ts:~p:~n~ts",
[Transport, inet_parse:ntoa(MyIP), MyPort,
inet_parse:ntoa(PeerIP), PeerPort, Data]).
Password when is_binary(Password) ->
esip:check_auth(Auth, Method, Body, Password);
_ScramedPassword ->
- ?ERROR_MSG("Unable to authenticate ~s@~s against SCRAM'ed "
+ ?ERROR_MSG("Unable to authenticate ~ts@~ts against SCRAM'ed "
"password", [LUser, LServer]),
false
end;
[<<"*">>] when Expires == 0 ->
case unregister_session(US, CallID, CSeq) of
{ok, ContactsWithExpires} ->
- ?INFO_MSG("Unregister SIP session for user ~s@~s from ~s",
+ ?INFO_MSG("Unregister SIP session for user ~ts@~ts from ~ts",
[LUser, LServer, inet_parse:ntoa(PeerIP)]),
Cs = prepare_contacts_to_send(ContactsWithExpires),
mod_sip:make_response(
IsOutboundSupported,
ContactsWithExpires) of
{ok, Res} ->
- ?INFO_MSG("~s SIP session for user ~s@~s from ~s",
+ ?INFO_MSG("~ts SIP session for user ~ts@~ts from ~ts",
[Res, LUser, LServer,
inet_parse:ntoa(PeerIP)]),
Cs = prepare_contacts_to_send(ContactsWithExpires),
reload(_Host, NewOpts, _OldOpts) ->
init_cache(NewOpts),
- ?WARNING_MSG("Module ~s is reloaded, but new configuration will take "
+ ?WARNING_MSG("Module ~ts is reloaded, but new configuration will take "
"effect for newly created client connections only", [?MODULE]).
depends(_Host, _Opts) ->
c2s_handle_info(#{mgmt_ack_timer := TRef, jid := JID, mod := Mod} = State,
{timeout, TRef, ack_timeout}) ->
- ?DEBUG("Timed out waiting for stream management acknowledgement of ~s",
+ ?DEBUG("Timed out waiting for stream management acknowledgement of ~ts",
[jid:encode(JID)]),
State1 = Mod:close(State),
State2 = State1#{stop_reason => {socket, ack_timeout}},
c2s_handle_info(#{mgmt_state := pending, lang := Lang,
mgmt_pending_timer := TRef, jid := JID, mod := Mod} = State,
{timeout, TRef, pending_timeout}) ->
- ?DEBUG("Timed out waiting for resumption of stream for ~s",
+ ?DEBUG("Timed out waiting for resumption of stream for ~ts",
[jid:encode(JID)]),
Txt = ?T("Timed out waiting for stream resumption"),
Err = xmpp:serr_connection_timeout(Txt, Lang),
c2s_handle_info(State, {_Ref, {resume, #{jid := JID} = OldState}}) ->
%% This happens if the resume_session/1 request timed out; the new session
%% now receives the late response.
- ?DEBUG("Received old session state for ~s after failed resumption",
+ ?DEBUG("Received old session state for ~ts after failed resumption",
[jid:encode(JID)]),
route_unacked_stanzas(OldState#{mgmt_resend => false}),
{stop, State};
State.
c2s_terminated(#{mgmt_state := resumed, sid := SID, jid := JID} = State, _Reason) ->
- ?DEBUG("Closing former stream of resumed session for ~s",
+ ?DEBUG("Closing former stream of resumed session for ~ts",
[jid:encode(JID)]),
{U, S, R} = jid:tolower(JID),
ejabberd_sm:close_session(SID, U, S, R),
DefaultTimeout
end,
Res = if Timeout > 0 ->
- ?DEBUG("Stream management with resumption enabled for ~s",
+ ?DEBUG("Stream management with resumption enabled for ~ts",
[jid:encode(JID)]),
#sm_enabled{xmlns = Xmlns,
id = make_resume_id(State),
resume = true,
max = Timeout div 1000};
true ->
- ?DEBUG("Stream management without resumption enabled for ~s",
+ ?DEBUG("Stream management without resumption enabled for ~ts",
[jid:encode(JID)]),
#sm_enabled{xmlns = Xmlns}
end,
State3 = resend_unacked_stanzas(State2),
State4 = send(State3, #sm_r{xmlns = AttrXmlns}),
State5 = ejabberd_hooks:run_fold(c2s_session_resumed, LServer, State4, []),
- ?INFO_MSG("(~s) Resumed session for ~s",
+ ?INFO_MSG("(~ts) Resumed session for ~ts",
[xmpp_socket:pp(Socket), jid:encode(JID)]),
{ok, State5};
{error, El, Reason} ->
lserver := LServer, mgmt_timeout := Timeout} = State,
Reason) ->
State1 = cancel_ack_timer(State),
- ?INFO_MSG("(~s) Closing c2s connection for ~s: ~s; "
+ ?INFO_MSG("(~ts) Closing c2s connection for ~ts: ~ts; "
"waiting ~B seconds for stream resumption",
[xmpp_socket:pp(Socket), jid:encode(JID),
format_reason(State, Reason), Timeout div 1000]),
check_h_attribute(#{mgmt_stanzas_out := NumStanzasOut, jid := JID,
lang := Lang} = State, H)
when H > NumStanzasOut ->
- ?WARNING_MSG("~s acknowledged ~B stanzas, but only ~B were sent",
+ ?WARNING_MSG("~ts acknowledged ~B stanzas, but only ~B were sent",
[jid:encode(JID), H, NumStanzasOut]),
State1 = State#{mgmt_resend => false},
Err = xmpp:serr_undefined_condition(
?T("Client acknowledged more stanzas than sent by server"), Lang),
send(State1, Err);
check_h_attribute(#{mgmt_stanzas_out := NumStanzasOut, jid := JID} = State, H) ->
- ?DEBUG("~s acknowledged ~B of ~B stanzas",
+ ?DEBUG("~ts acknowledged ~B of ~B stanzas",
[jid:encode(JID), H, NumStanzasOut]),
mgmt_queue_drop(State, H).
when (MgmtState == active orelse
MgmtState == pending orelse
MgmtState == timeout) andalso ?qlen(Queue) > 0 ->
- ?DEBUG("Resending ~B unacknowledged stanza(s) to ~s",
+ ?DEBUG("Resending ~B unacknowledged stanza(s) to ~ts",
[p1_queue:len(Queue), jid:encode(JID)]),
p1_queue:foldl(
fun({_, Time, Pkt}, AccState) ->
_ -> false
end
end,
- ?DEBUG("Re-routing ~B unacknowledged stanza(s) to ~s",
+ ?DEBUG("Re-routing ~B unacknowledged stanza(s) to ~ts",
[p1_queue:len(Queue), jid:encode(JID)]),
p1_queue:foreach(
fun({_, _Time, #presence{from = From}}) ->
- ?DEBUG("Dropping presence stanza from ~s", [jid:encode(From)]);
+ ?DEBUG("Dropping presence stanza from ~ts", [jid:encode(From)]);
({_, _Time, #iq{} = El}) ->
Txt = ?T("User session terminated"),
ejabberd_router:route_error(
%% any reason, the receiving server MUST NOT forward that error
%% back to the original sender." Resending such a stanza could
%% easily lead to unexpected results as well.
- ?DEBUG("Dropping forwarded message stanza from ~s",
+ ?DEBUG("Dropping forwarded message stanza from ~ts",
[jid:encode(From)]);
({_, Time, #message{} = Msg}) ->
case ejabberd_hooks:run_fold(message_is_archived,
LServer, false,
[State, Msg]) of
true ->
- ?DEBUG("Dropping archived message stanza from ~s",
+ ?DEBUG("Dropping archived message stanza from ~ts",
[jid:encode(xmpp:get_from(Msg))]);
false when ResendOnTimeout ->
NewEl = add_resent_delay_info(State, Msg, Time),
-spec log_resumption_error(binary(), binary(), error_reason()) -> ok.
log_resumption_error(User, Server, Reason)
when Reason == invalid_previd ->
- ?WARNING_MSG("Cannot resume session for ~s@~s: ~s",
+ ?WARNING_MSG("Cannot resume session for ~ts@~ts: ~ts",
[User, Server, format_error(Reason)]);
log_resumption_error(User, Server, Reason) ->
- ?INFO_MSG("Cannot resume session for ~s@~s: ~s",
+ ?INFO_MSG("Cannot resume session for ~ts@~ts: ~ts",
[User, Server, format_error(Reason)]).
%%%===================================================================
case Mod:is_search_supported(Host) of
false ->
?WARNING_MSG("vCard search functionality is "
- "not implemented for ~s backend",
+ "not implemented for ~ts backend",
[mod_vcard_opt:db_type(Opts)]);
true ->
ejabberd_router:register_route(
try route(Packet)
catch ?EX_RULE(Class, Reason, St) ->
StackTrace = ?EX_STACK(St),
- ?ERROR_MSG("Failed to route packet:~n~s~n** ~s",
+ ?ERROR_MSG("Failed to route packet:~n~ts~n** ~ts",
[xmpp:pp(Packet),
misc:format_exception(2, Class, Reason, StackTrace)])
end,
format_error({bad_packet_type, Type}) ->
format("Unexpected packet type: ~B", [Type]);
format_error({bad_packet, Name}) ->
- format("Malformed ~s packet", [string:to_upper(atom_to_list(Name))]);
+ format("Malformed ~ts packet", [string:to_upper(atom_to_list(Name))]);
format_error({unexpected_packet, Name}) ->
- format("Unexpected ~s packet", [string:to_upper(atom_to_list(Name))]);
+ format("Unexpected ~ts packet", [string:to_upper(atom_to_list(Name))]);
format_error({bad_reason_code, Name, Code}) ->
- format("Unexpected reason code in ~s code: ~B",
+ format("Unexpected reason code in ~ts code: ~B",
[string:to_upper(atom_to_list(Name)), Code]);
format_error({bad_properties, Name}) ->
- format("Malformed properties of ~s packet",
+ format("Malformed properties of ~ts packet",
[string:to_upper(atom_to_list(Name))]);
format_error({bad_property, Pkt, Prop}) ->
- format("Malformed property ~s of ~s packet",
+ format("Malformed property ~ts of ~ts packet",
[Prop, string:to_upper(atom_to_list(Pkt))]);
format_error({duplicated_property, Pkt, Prop}) ->
- format("Property ~s is included more than once into ~s packet",
+ format("Property ~ts is included more than once into ~ts packet",
[Prop, string:to_upper(atom_to_list(Pkt))]);
format_error(bad_will_topic_or_message) ->
"Malformed Will Topic or Will Message";
format_error(bad_publish_id_or_payload) ->
"Malformed id or payload of PUBLISH packet";
format_error({bad_topic_filters, Name}) ->
- format("Malformed topic filters of ~s packet",
+ format("Malformed topic filters of ~ts packet",
[string:to_upper(atom_to_list(Name))]);
format_error({bad_qos, Q}) ->
format_got_expected("Malformed QoS value", Q, "0, 1 or 2");
format_got_expected(Txt, Got, Expected) ->
FmtGot = term_format(Got),
FmtExp = term_format(Expected),
- format("~s: " ++ FmtGot ++ " (expected: " ++ FmtExp ++ ")",
+ format("~ts: " ++ FmtGot ++ " (expected: " ++ FmtExp ++ ")",
[Txt, Got, Expected]).
term_format(I) when is_integer(I) ->
term_format(atom_to_list(A));
term_format(T) ->
case io_lib:printable_latin1_list(T) of
- true -> "~s";
+ true -> "~ts";
false -> "~w"
end.
"privacy", "pep", "pubsub"])
end, HostDirs);
{error, Why} = Err ->
- ?ERROR_MSG("Failed to list ~s: ~s",
+ ?ERROR_MSG("Failed to list ~ts: ~ts",
[ProsodyDir, file:format_error(Why)]),
Err
end;
{error, enoent} ->
ok;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to list ~s: ~s",
+ ?ERROR_MSG("Failed to list ~ts: ~ts",
[Path, file:format_error(Why)]),
Err
end.
{ok, _} = Res ->
Res;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to eval ~s: ~p", [Path, Why]),
+ ?ERROR_MSG("Failed to eval ~ts: ~p", [Path, Why]),
Err
end;
{error, Why} = Err ->
- ?ERROR_MSG("Failed to read file ~s: ~s",
+ ?ERROR_MSG("Failed to read file ~ts: ~ts",
[Path, file:format_error(Why)]),
Err
end.
ok ->
ok;
Err ->
- ?ERROR_MSG("Failed to register user ~s@~s: ~p",
+ ?ERROR_MSG("Failed to register user ~ts@~ts: ~p",
[User, Host, Err]),
Err
end;
Error
end;
Error ->
- ?ERROR_MSG("Failed to import pubsub node ~s on ~p:~n~p",
+ ?ERROR_MSG("Failed to import pubsub node ~ts on ~p:~n~p",
[Node, Host, NodeData]),
Error
end;
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]),
+ ?INFO_MSG("Converting '~ts' table from strings to binaries.", [Tab]),
TmpTab = list_to_atom(atom_to_list(Tab) ++ "_tmp_table"),
catch mnesia:delete_table(TmpTab),
case ejabberd_mnesia:create(?MODULE, TmpTab,
report_and_stop(Tab, Err) ->
ErrTxt = lists:flatten(
io_lib:format(
- "Failed to convert '~s' table to binary: ~p",
+ "Failed to convert '~ts' table to binary: ~p",
[Tab, Err])),
?CRITICAL_MSG(ErrTxt, []),
ejabberd:halt().
case catch binary_to_integer(Val) of
N when is_integer(N) -> N;
_ ->
- Txt = {?T("Value of '~s' should be integer"), [Opt]},
+ Txt = {?T("Value of '~ts' should be integer"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end;
val_xfield(expire = Opt, [Val]) ->
try xmpp_util:decode_timestamp(Val)
catch _:{bad_timestamp, _} ->
- Txt = {?T("Value of '~s' should be datetime string"), [Opt]},
+ Txt = {?T("Value of '~ts' should be datetime string"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end;
val_xfield(include_body = Opt, [Val]) -> xopt_to_bool(Opt, Val);
case catch binary_to_integer(Depth) of
N when is_integer(N) -> N;
_ ->
- Txt = {?T("Value of '~s' should be integer"), [Opt]},
+ Txt = {?T("Value of '~ts' should be integer"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end.
xopt_to_bool(_, <<"false">>) -> false;
xopt_to_bool(_, <<"true">>) -> true;
xopt_to_bool(Option, _) ->
- Txt = {?T("Value of '~s' should be boolean"), [Option]},
+ Txt = {?T("Value of '~ts' should be boolean"), [Option]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}.
%% Return a field for an XForm for Key, with data filled in, if
case catch binary_to_integer(Val) of
N when is_integer(N) -> N;
_ ->
- Txt = {?T("Value of '~s' should be integer"), [Opt]},
+ Txt = {?T("Value of '~ts' should be integer"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end;
val_xfield(expire = Opt, [Val]) ->
try xmpp_util:decode_timestamp(Val)
catch _:{bad_timestamp, _} ->
- Txt = {?T("Value of '~s' should be datetime string"), [Opt]},
+ Txt = {?T("Value of '~ts' should be datetime string"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end;
val_xfield(include_body = Opt, [Val]) -> xopt_to_bool(Opt, Val);
case catch binary_to_integer(Depth) of
N when is_integer(N) -> N;
_ ->
- Txt = {?T("Value of '~s' should be integer"), [Opt]},
+ Txt = {?T("Value of '~ts' should be integer"), [Opt]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}
end.
xopt_to_bool(_, <<"false">>) -> false;
xopt_to_bool(_, <<"true">>) -> true;
xopt_to_bool(Option, _) ->
- Txt = {?T("Value of '~s' should be boolean"), [Option]},
+ Txt = {?T("Value of '~ts' should be boolean"), [Option]},
{error, xmpp:err_not_acceptable(Txt, ejabberd_option:language())}.
%% Return a field for an XForm for Key, with data filled in, if
{error, {read_error, {file_error, _, enoent}}} ->
load(MsgFiles, MsgsDir);
{error, {read_error, {file_error, _, Reason}}} ->
- ?WARNING_MSG("Failed to read translation cache from ~s: ~s",
- [unicode:characters_to_binary(CacheFile),
- format_error(Reason)]),
+ ?WARNING_MSG("Failed to read translation cache from ~ts: ~ts",
+ [CacheFile, format_error(Reason)]),
load(MsgFiles, MsgsDir);
{error, Reason} ->
- ?WARNING_MSG("Failed to read translation cache from ~s: ~p",
- [unicode:characters_to_binary(CacheFile),
- Reason]),
+ ?WARNING_MSG("Failed to read translation cache from ~ts: ~p",
+ [CacheFile, Reason]),
load(MsgFiles, MsgsDir)
end
end.
end,
case Files of
[] ->
- ?WARNING_MSG("No translation files found in ~s, "
+ ?WARNING_MSG("No translation files found in ~ts, "
"check directory access",
- [unicode:characters_to_binary(Dir)]);
+ [Dir]);
_ ->
?INFO_MSG("Building language translation cache", []),
Objs = lists:flatten(misc:pmap(fun load_file/1, Files)),
ets:insert(translations, Objs),
?DEBUG("Language translation cache built successfully", []);
{error, File, Reason} ->
- ?ERROR_MSG("Failed to read translation file ~s: ~s",
- [unicode:characters_to_binary(File),
- format_error(Reason)]),
+ ?ERROR_MSG("Failed to read translation file ~ts: ~ts",
+ [File, format_error(Reason)]),
{error, Reason}
end
end.
{ok, #file_info{mtime = MTime}} ->
{MTime, Dir};
{error, Reason} ->
- ?ERROR_MSG("Failed to read directory ~s: ~s",
- [unicode:characters_to_binary(Dir),
- format_error(Reason)]),
+ ?ERROR_MSG("Failed to read directory ~ts: ~ts",
+ [Dir, format_error(Reason)]),
{?ZERO_DATETIME, Dir}
end.
{ok, #file_info{mtime = Time}} ->
{lists:max([MTime, Time]), [File|Files]};
{error, Reason} ->
- ?ERROR_MSG("Failed to read translation file ~s: ~s",
- [unicode:characters_to_binary(File),
- format_error(Reason)]),
+ ?ERROR_MSG("Failed to read translation file ~ts: ~ts",
+ [File, format_error(Reason)]),
Acc
end;
false ->
- ?WARNING_MSG("Ignoring translation file ~s: file name "
+ ?WARNING_MSG("Ignoring translation file ~ts: file name "
"must be a valid language tag",
- [unicode:characters_to_binary(File)]),
+ [File]),
Acc
end
end, {?ZERO_DATETIME, []}),
case file:list_dir(MsgsDir) of
{ok, _} -> ok;
{error, Reason} ->
- ?ERROR_MSG("Failed to read directory ~s: ~s",
- [unicode:characters_to_binary(MsgsDir),
- format_error(Reason)])
+ ?ERROR_MSG("Failed to read directory ~ts: ~ts",
+ [MsgsDir, format_error(Reason)])
end;
_ ->
ok
case ets:tab2file(translations, CacheFile) of
ok -> ok;
{error, Reason} ->
- ?WARNING_MSG("Failed to create translation cache in ~s: ~p",
- [unicode:characters_to_binary(CacheFile), Reason])
+ ?WARNING_MSG("Failed to create translation cache in ~ts: ~p",
+ [CacheFile, Reason])
end.
-spec lang_of_file(file:filename()) -> binary().