• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

processone / ejabberd / 1258

12 Dec 2025 03:57PM UTC coverage: 33.638% (-0.006%) from 33.644%
1258

push

github

badlop
Container: Apply commit a22c88a

ejabberdctl.template: Show meaningful error when ERL_DIST_PORT is in use

15554 of 46240 relevant lines covered (33.64%)

1078.28 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

32.1
/src/ejabberd_ctl.erl
1
%%%----------------------------------------------------------------------
2
%%% File    : ejabberd_ctl.erl
3
%%% Author  : Alexey Shchepin <alexey@process-one.net>
4
%%% Purpose : ejabberd command line admin tool
5
%%% Created : 11 Jan 2004 by Alexey Shchepin <alexey@process-one.net>
6
%%%
7
%%%
8
%%% ejabberd, Copyright (C) 2002-2025   ProcessOne
9
%%%
10
%%% This program is free software; you can redistribute it and/or
11
%%% modify it under the terms of the GNU General Public License as
12
%%% published by the Free Software Foundation; either version 2 of the
13
%%% License, or (at your option) any later version.
14
%%%
15
%%% This program is distributed in the hope that it will be useful,
16
%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
17
%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
%%% General Public License for more details.
19
%%%
20
%%% You should have received a copy of the GNU General Public License along
21
%%% with this program; if not, write to the Free Software Foundation, Inc.,
22
%%% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
23
%%%
24
%%%----------------------------------------------------------------------
25

26
-module(ejabberd_ctl).
27

28
-behaviour(gen_server).
29
-author('alexey@process-one.net').
30

31
-export([start/0, start_link/0, process/1, process/2, process2/2]).
32
%% gen_server callbacks
33
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
34
         terminate/2, code_change/3]).
35
-export([get_commands_spec/0, format_arg/2,
36
         get_usage_command/4]).
37

38
-include("ejabberd_ctl.hrl").
39
-include("ejabberd_commands.hrl").
40
-include("ejabberd_http.hrl").
41
-include("logger.hrl").
42

43

44
-define(DEFAULT_VERSION, 1000000).
45

46
-record(state, {}).
47

48
%%-----------------------------
49
%% Module
50
%%-----------------------------
51

52
start() ->
53
    logger:set_primary_config(level, none),
×
54
    [SNode, Timeout, Args] = case init:get_plain_arguments() of
×
55
                                 [SNode2, "--no-timeout" | Args2] ->
56
                                     [SNode2, infinity, Args2];
×
57
                                 [SNode3 | Args3] ->
58
                                     [SNode3, 60000, Args3];
×
59
                                 _ ->
60
                                     print_usage(?DEFAULT_VERSION),
×
61
                                     halt(?STATUS_USAGE)
×
62
                             end,
63
    SNode1 = case string:tokens(SNode, "@") of
×
64
                 [_Node, _Server] ->
65
                     SNode;
×
66
                 _ ->
67
                     case net_kernel:longnames() of
×
68
                         true ->
69
                             lists:flatten([SNode, "@", inet_db:gethostname(),
×
70
                                            ".", inet_db:res_option(domain)]);
71
                         false ->
72
                             lists:flatten([SNode, "@", inet_db:gethostname()]);
×
73
                         _ ->
74
                             SNode
×
75
                     end
76
             end,
77
    Node = list_to_atom(SNode1),
×
78
    Status = case ejabberd_cluster:call(Node, ?MODULE, process, [Args], Timeout) of
×
79
                 {badrpc, Reason} ->
80
                     print("Failed RPC connection to the node ~p: ~p~n",
×
81
                           [Node, Reason]),
82
                     %% TODO: show minimal start help
83
                     ?STATUS_BADRPC;
×
84
                 {invalid_version, V} ->
85
                     print("Invalid API version number: ~p~n", [V]),
×
86
                     ?STATUS_ERROR;
×
87
                 S ->
88
                     S
×
89
             end,
90
    halt(Status).
×
91

92
start_link() ->
93
    gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
11✔
94

95
init([]) ->
96
    ejabberd_commands:register_commands(?MODULE, get_commands_spec()),
11✔
97
    {ok, #state{}}.
11✔
98

99
handle_call(Request, From, State) ->
100
    ?WARNING_MSG("Unexpected call from ~p: ~p", [From, Request]),
×
101
    {noreply, State}.
×
102

103
handle_cast(Msg, State) ->
104
    ?WARNING_MSG("Unexpected cast: ~p", [Msg]),
×
105
    {noreply, State}.
×
106

107
handle_info(Info, State) ->
108
    ?WARNING_MSG("Unexpected info: ~p", [Info]),
×
109
    {noreply, State}.
×
110

111
terminate(_Reason, _State) ->
112
    ejabberd_commands:unregister_commands(get_commands_spec()),
×
113
    ok.
×
114

115
code_change(_OldVsn, State, _Extra) ->
116
    {ok, State}.
×
117

118
%%-----------------------------
119
%% Process http
120
%%-----------------------------
121

122
-spec process_http([binary()], tuple()) -> {non_neg_integer(), [{binary(), binary()}], string()}.
123

124
process_http([_Call], #request{data = Data, path = [<<"ctl">> | _]}) ->
125
    Args = [binary_to_list(E) || E <- misc:json_decode(Data)],
×
126
    process_http2(Args, ?DEFAULT_VERSION).
×
127

128
process_http2(["--version", Arg | Args], _) ->
129
    Version =
×
130
        try
131
            list_to_integer(Arg)
×
132
        catch _:_ ->
133
                throw({invalid_version, Arg})
×
134
        end,
135
    process_http2(Args, Version);
×
136

137
process_http2(Args, Version) ->
138
    {String, Code} = process2(Args, [], Version),
×
139
    String2 = case String of
×
140
                  [] -> String;
×
141
                  _ -> [String, "\n"]
×
142
              end,
143
    {200, [{<<"status-code">>, integer_to_binary(Code)}], String2}.
×
144

145
%%-----------------------------
146
%% Process command line
147
%%-----------------------------
148

149
-spec process([string()]) -> non_neg_integer().
150
process(Args) ->
151
    process(Args, ?DEFAULT_VERSION).
1✔
152

153
-spec process([string() | binary()], non_neg_integer() | tuple()) -> non_neg_integer().
154

155
process([Call], Request) when is_binary(Call) and is_record(Request, request) ->
156
    process_http([Call], Request);
×
157

158
%% The commands status, stop and restart are defined here to ensure
159
%% they are usable even if ejabberd is completely stopped.
160
process(["status"], _Version) ->
161
    {InternalStatus, ProvidedStatus} = init:get_status(),
×
162
    print("The node ~p is ~p with status: ~p~n",
×
163
           [node(), InternalStatus, ProvidedStatus]),
164
    case lists:keymember(ejabberd, 1, application:which_applications()) of
×
165
        false ->
166
            EjabberdLogPath = ejabberd_logger:get_log_path(),
×
167
            print("ejabberd is not running in that node~n"
×
168
                   "Check for error messages: ~ts~n"
169
                   "or other files in that directory.~n", [EjabberdLogPath]),
170
            ?STATUS_ERROR;
×
171
        true ->
172
            print("ejabberd ~ts is running in that node~n", [ejabberd_option:version()]),
×
173
            ?STATUS_SUCCESS
×
174
    end;
175

176
%% TODO: Mnesia operations should not be hardcoded in ejabberd_ctl module.
177
%% For now, I leave them there to avoid breaking those commands for people that
178
%% may be using it (as format of response is going to change).
179
process(["mnesia_info_ctl"], _Version) ->
180
    mnesia:info(),
×
181
    ?STATUS_SUCCESS;
×
182

183
process(["print_sql_schema", DBType, DBVersion, NewSchema], _Version) ->
184
    ejabberd_sql_schema:print_schema(DBType, DBVersion, NewSchema);
×
185

186
%% The arguments --long and --dual are not documented because they are
187
%% automatically selected depending in the number of columns of the shell
188
process(["help" | Mode], Version) ->
189
    {MaxC, ShCode} = get_shell_info(),
×
190
    case Mode of
×
191
        [] ->
192
            print_usage_help(MaxC, ShCode),
×
193
            ?STATUS_SUCCESS;
×
194
        ["--dual"] ->
195
            print_usage(dual, MaxC, ShCode, Version),
×
196
            ?STATUS_USAGE;
×
197
        ["--long"] ->
198
            print_usage(long, MaxC, ShCode, Version),
×
199
            ?STATUS_USAGE;
×
200
        ["tags"] ->
201
            print_usage_tags(MaxC, ShCode, Version),
×
202
            ?STATUS_SUCCESS;
×
203
        ["--tags"] -> % deprecated in favor of "tags"
204
            print_usage_tags(MaxC, ShCode, Version),
×
205
            ?STATUS_SUCCESS;
×
206
        ["commands"] ->
207
            print_usage_tags_long(MaxC, ShCode, Version),
×
208
            ?STATUS_SUCCESS;
×
209
        ["--tags", Tag] -> % deprecated in favor of simply "Tag"
210
            print_usage_tags(Tag, MaxC, ShCode, Version),
×
211
            ?STATUS_SUCCESS;
×
212
        [String | _] ->
213
            case determine_string_type(String, Version) of
×
214
                no_idea ->
215
                    io:format("No tag or command matches '~ts'~n", [String]);
×
216
                both ->
217
                    print_usage_tags(String, MaxC, ShCode, Version),
×
218
                    print_usage_commands2(String, MaxC, ShCode, Version);
×
219
                tag ->
220
                    print_usage_tags(String, MaxC, ShCode, Version);
×
221
                command ->
222
                    print_usage_commands2(String, MaxC, ShCode, Version)
×
223
            end,
224
            ?STATUS_SUCCESS
×
225
    end;
226

227
process(["--version", Arg | Args], _) ->
228
    Version =
×
229
        try
230
            list_to_integer(Arg)
×
231
        catch _:_ ->
232
                throw({invalid_version, Arg})
×
233
        end,
234
    process(Args, Version);
×
235

236
process(Args, Version) ->
237
    {String, Code} = process2(Args, [], Version),
1✔
238
    case String of
1✔
239
        [] -> ok;
×
240
        _ ->
241
            io:format("~ts~n", [String])
1✔
242
    end,
243
    Code.
1✔
244

245
-spec process2(Args::[string()], AccessCommands::any()) ->
246
    {String::string(), Code::integer()}.
247
process2(Args, AccessCommands) ->
248
    process2(Args, AccessCommands, ?DEFAULT_VERSION).
×
249

250
process2(["--auth", User, Server, Pass | Args], AccessCommands, Version) ->
251
    process2(Args, AccessCommands, {list_to_binary(User), list_to_binary(Server),
×
252
                                    list_to_binary(Pass), true}, Version);
253
process2(Args, AccessCommands, Version) ->
254
    process2(Args, AccessCommands, noauth, Version).
1✔
255

256

257

258
process2(Args, AccessCommands, Auth, Version) ->
259
    case try_run_ctp(Args, Auth, AccessCommands, Version) of
1✔
260
        {String, wrong_command_arguments}
261
          when is_list(String) ->
262
            io:format(lists:flatten(["\n" | String]++["\n"])),
×
263
            [CommandString | _] = Args,
×
264
            process(["help" | [CommandString]], Version),
×
265
            {lists:flatten(String), ?STATUS_USAGE};
×
266
        {String, Code}
267
          when is_list(String) and is_integer(Code) ->
268
            {lists:flatten(String), Code};
×
269
        String
270
          when is_list(String) ->
271
            {lists:flatten(String), ?STATUS_SUCCESS};
1✔
272
        Code
273
          when is_integer(Code) ->
274
            {"", Code};
×
275
        Other ->
276
            {"Erroneous result: " ++ io_lib:format("~p", [Other]), ?STATUS_ERROR}
×
277
    end.
278

279
determine_string_type(String, Version) ->
280
    TagsCommands = ejabberd_commands:get_tags_commands(Version),
×
281
    CommandsNames = case lists:keysearch(String, 1, TagsCommands) of
×
282
                        {value, {String, CNs}} -> CNs;
×
283
                        false -> []
×
284
                    end,
285
    AllCommandsNames = [atom_to_list(Name) || {Name, _, _} <- ejabberd_commands:list_commands(Version)],
×
286
    Cmds = filter_commands(AllCommandsNames, String),
×
287
    case {CommandsNames, Cmds} of
×
288
        {[], []} -> no_idea;
×
289
        {[], _} -> command;
×
290
        {_, []} -> tag;
×
291
        {_, _} -> both
×
292
    end.
293

294
%%-----------------------------
295
%% Command calling
296
%%-----------------------------
297

298
try_run_ctp(Args, Auth, AccessCommands, Version) ->
299
    try ejabberd_hooks:run_fold(ejabberd_ctl_process, false, [Args]) of
1✔
300
        false when Args /= [] ->
301
            try_call_command(Args, Auth, AccessCommands, Version);
1✔
302
        false ->
303
            print_usage(Version),
×
304
            {"", ?STATUS_BADRPC};
×
305
        Status ->
306
            {"", Status}
×
307
    catch
308
        exit:Why ->
309
            print_usage(Version),
×
310
            {io_lib:format("Error in ejabberd ctl process: ~p", [Why]), ?STATUS_USAGE};
×
311
        Error:Why ->
312
            %% In this case probably ejabberd is not started, so let's show Status
313
            process(["status"], Version),
×
314
            print("~n", []),
×
315
            {io_lib:format("Error in ejabberd ctl process: '~p' ~p", [Error, Why]), ?STATUS_USAGE}
×
316
    end.
317

318
try_call_command(Args, Auth, AccessCommands, Version) ->
319
    try call_command(Args, Auth, AccessCommands, Version) of
1✔
320
        {Reason, wrong_command_arguments} ->
321
            {Reason, ?STATUS_USAGE};
×
322
        Res ->
323
            Res
1✔
324
    catch
325
        throw:{error, unknown_command} ->
326
            KnownCommands = [Cmd || {Cmd, _, _} <- ejabberd_commands:list_commands(Version)],
×
327
            UnknownCommand = list_to_atom(hd(Args)),
×
328
            {io_lib:format(
×
329
               "Error: unknown command '~ts'. Did you mean '~ts'?",
330
               [hd(Args), misc:best_match(UnknownCommand, KnownCommands)]),
331
             ?STATUS_ERROR};
332
        throw:Error ->
333
            {io_lib:format("~p", [Error]), ?STATUS_ERROR};
×
334
        A:Why:StackTrace ->
335
            {io_lib:format("Unhandled exception occurred executing the command:~n** ~ts",
×
336
                           [misc:format_exception(2, A, Why, StackTrace)]),
337
             ?STATUS_ERROR}
338
    end.
339

340
-spec call_command(Args::[string()],
341
                   Auth::noauth | {binary(), binary(), binary(), true},
342
                   AccessCommands::[any()],
343
                   Version::integer()) ->
344
    string() | integer() | {string(), integer()} | {error, ErrorType::any()}.
345
call_command([CmdString | Args], Auth, _AccessCommands, Version) ->
346
    CmdStringU = ejabberd_regexp:greplace(
1✔
347
                   list_to_binary(CmdString), <<"-">>, <<"_">>),
348
    Command = list_to_atom(binary_to_list(CmdStringU)),
1✔
349
    {ArgsFormat, _, ResultFormat} = ejabberd_commands:get_command_format(Command, Auth, Version),
1✔
350
    case (catch format_args(Args, ArgsFormat)) of
1✔
351
        ArgsFormatted when is_list(ArgsFormatted) ->
352
            CI = case Auth of
1✔
353
                     {U, S, _, _} -> #{usr => {U, S, <<"">>}, caller_host => S};
×
354
                     _ -> #{}
1✔
355
                 end,
356
            CI2 = CI#{caller_module => ?MODULE},
1✔
357
            Result = ejabberd_commands:execute_command2(Command,
1✔
358
                                                        ArgsFormatted,
359
                                                        CI2,
360
                                                        Version),
361
            format_result_preliminary(Result, ResultFormat, Version);
1✔
362
        {'EXIT', {function_clause,[{lists,zip,[A1,A2|_], _} | _]}} ->
363
            {NumCompa, TextCompa} =
×
364
                case {length(A1), length(A2)} of
365
                    {L1, L2} when L1 < L2 -> {L2-L1, "less argument"};
×
366
                    {L1, L2} when L1 > L2 -> {L1-L2, "more argument"}
×
367
                end,
368
            process(["help" | [CmdString]], Version),
×
369
            {io_lib:format("Error: the command '~ts' requires ~p ~ts.",
×
370
                           [CmdString, NumCompa, TextCompa]),
371
             wrong_command_arguments}
372
    end.
373

374

375
%%-----------------------------
376
%% Format arguments
377
%%-----------------------------
378

379
format_args(Args, ArgsFormat) ->
380
    lists:foldl(
1✔
381
      fun({{_ArgName, ArgFormat}, Arg}, Res) ->
382
              Formatted = format_arg(Arg, ArgFormat),
×
383
              Res ++ [Formatted]
×
384
      end,
385
      [],
386
      lists:zip(ArgsFormat, Args)).
387

388
format_arg(Arg, integer) ->
389
    format_arg2(Arg, "~d");
×
390
format_arg(Arg, binary) ->
391
    unicode:characters_to_binary(Arg, utf8);
×
392
format_arg(Arg, binary_or_list) ->
393
    [unicode:characters_to_binary(Arg, utf8)];
×
394
format_arg("", string) ->
395
    "";
×
396
format_arg(Arg, string) ->
397
    NumChars = integer_to_list(length(Arg)),
×
398
    Parse = "~" ++ NumChars ++ "c",
×
399
    format_arg2(Arg, Parse);
×
400
format_arg(Arg, {list, {_ArgName, ArgFormat}}) ->
401
    [format_arg(string:trim(Element), ArgFormat) || Element <- string:tokens(Arg, ",")];
×
402
format_arg(Arg, {list, ArgFormat}) ->
403
    [format_arg(string:trim(Element), ArgFormat) || Element <- string:tokens(Arg, ",")];
×
404
format_arg(Arg, {tuple, Elements}) ->
405
    Args = string:tokens(Arg, ":"),
×
406
    list_to_tuple(format_args(Args, Elements));
×
407
format_arg(Arg, Format) ->
408
    S = unicode:characters_to_binary(Arg, utf8),
×
409
    JSON = misc:json_decode(S),
×
410
    mod_http_api:format_arg(JSON, Format).
×
411

412
format_arg2(Arg, Parse)->
413
    {ok, [Arg2], _RemainingArguments} = io_lib:fread(Parse, Arg),
×
414
    Arg2.
×
415

416
%%-----------------------------
417
%% Format result
418
%%-----------------------------
419

420
format_result_preliminary(Result, {A, {list, B}}, Version) ->
421
    format_result(Result, {A, {top_result_list, B}}, Version);
1✔
422
format_result_preliminary(Result, ResultFormat, Version) ->
423
    format_result(Result, ResultFormat, Version).
×
424

425
format_result({error, ErrorAtom}, _, _Version) ->
426
    {io_lib:format("Error: ~p", [ErrorAtom]), make_status(error)};
×
427

428
%% An error should always be allowed to return extended error to help with API.
429
%% Extended error is of the form:
430
%%  {error, type :: atom(), code :: int(), Desc :: string()}
431
format_result({error, ErrorAtom, Code, Msg}, _, _Version) ->
432
    {io_lib:format("Error: ~p: ~s", [ErrorAtom, Msg]), make_status(Code)};
×
433

434
format_result(Atom, {_Name, atom}, _Version) ->
435
    io_lib:format("~p", [Atom]);
1✔
436

437
format_result(Int, {_Name, integer}, _Version) ->
438
    io_lib:format("~p", [Int]);
×
439

440
format_result([A|_]=String, {_Name, string}, _Version) when is_list(String) and is_integer(A) ->
441
    io_lib:format("~ts", [String]);
1✔
442

443
format_result(Binary, {_Name, binary}, _Version) when is_binary(Binary) ->
444
    io_lib:format("~ts", [Binary]);
×
445

446
format_result(String, {_Name, binary}, _Version) when is_list(String) ->
447
    io_lib:format("~ts", [String]);
×
448

449
format_result(Binary, {_Name, string}, _Version) when is_binary(Binary) ->
450
    io_lib:format("~ts", [Binary]);
×
451

452
format_result(Atom, {_Name, string}, _Version) when is_atom(Atom) ->
453
    io_lib:format("~ts", [atom_to_list(Atom)]);
×
454

455
format_result(Integer, {_Name, string}, _Version) when is_integer(Integer) ->
456
    io_lib:format("~ts", [integer_to_list(Integer)]);
×
457

458
format_result(Other, {_Name, string}, _Version)  ->
459
    io_lib:format("~p", [Other]);
×
460

461
format_result(Code, {_Name, rescode}, _Version) ->
462
    make_status(Code);
×
463

464
format_result({Code, Text}, {_Name, restuple}, _Version) ->
465
    {io_lib:format("~ts", [Text]), make_status(Code)};
×
466

467
format_result([], {_Name, {top_result_list, _ElementsDef}}, _Version) ->
468
    "";
×
469
format_result([FirstElement | Elements], {_Name, {top_result_list, ElementsDef}}, Version) ->
470
    [format_result(FirstElement, ElementsDef, Version) |
1✔
471
     lists:map(
472
       fun(Element) ->
473
               ["\n" | format_result(Element, ElementsDef, Version)]
×
474
       end,
475
       Elements)];
476

477
%% The result is a list of something: [something()]
478
format_result([], {_Name, {list, _ElementsDef}}, _Version) ->
479
    "";
×
480
format_result([FirstElement | Elements], {_Name, {list, ElementsDef}}, Version) ->
481
    Separator = case Version of
×
482
                    0 -> ";";
×
483
                    _ -> ","
×
484
                end,
485
    %% Start formatting the first element
486
    [format_result(FirstElement, ElementsDef, Version) |
×
487
     %% If there are more elements, put always first a newline character
488
     lists:map(
489
       fun(Element) ->
490
               [Separator | format_result(Element, ElementsDef, Version)]
×
491
       end,
492
       Elements)];
493

494
%% The result is a tuple with several elements: {something1(), something2(),...}
495
%% NOTE: the elements in the tuple are separated with tabular characters,
496
%% if a string is empty, it will be difficult to notice in the shell,
497
%% maybe a different separation character should be used, like ;;?
498
format_result(ElementsTuple, {_Name, {tuple, ElementsDef}}, Version) ->
499
    ElementsList = tuple_to_list(ElementsTuple),
1✔
500
    [{FirstE, FirstD} | ElementsAndDef] = lists:zip(ElementsList, ElementsDef),
1✔
501
    [format_result(FirstE, FirstD, Version) |
1✔
502
     lists:map(
503
       fun({Element, ElementDef}) ->
504
               ["\t" | format_result(Element, ElementDef, Version)]
1✔
505
       end,
506
       ElementsAndDef)];
507

508
format_result(404, {_Name, _}, _Version) ->
509
    make_status(not_found).
×
510

511
make_status(ok) -> ?STATUS_SUCCESS;
×
512
make_status(true) -> ?STATUS_SUCCESS;
×
513
make_status(Code) when is_integer(Code), Code > 255 -> ?STATUS_ERROR;
×
514
make_status(Code) when is_integer(Code), Code > 0 -> Code;
×
515
make_status(Error) ->
516
    io:format("Error: ~p~n", [Error]),
×
517
    ?STATUS_ERROR.
×
518

519
get_list_commands(Version) ->
520
    try ejabberd_commands:list_commands(Version) of
×
521
        Commands ->
522
            [tuple_command_help(Command) || Command <- Commands]
×
523
    catch
524
        exit:_ ->
525
            []
×
526
    end.
527

528
%% Return: {string(), [string()], string()}
529
tuple_command_help({Name, _Args, Desc}) ->
530
    {Args, _, _} = ejabberd_commands:get_command_format(Name, admin),
×
531
    Arguments = [atom_to_list(ArgN) || {ArgN, _ArgF} <- Args],
×
532
    CallString = atom_to_list(Name),
×
533
    {CallString, Arguments, Desc}.
×
534

535
has_tuple_args(Args) ->
536
    lists:any(
480✔
537
      fun({_Name, tuple}) -> true;
×
538
         ({_Name, {tuple, _}}) -> true;
×
539
         ({_Name, {list, SubArg}}) ->
540
            has_tuple_args([SubArg]);
×
541
         (_) -> false
576✔
542
      end,
543
      Args).
544

545
has_list_args(Args) ->
546
    lists:any(
480✔
547
      fun({_Name, list}) -> true;
×
548
         ({_Name, {list, _}}) -> true;
×
549
         (_) -> false
576✔
550
      end,
551
      Args).
552

553
%%-----------------------------
554
%% Print help
555
%%-----------------------------
556

557
%% Commands are Bold
558
-define(B1, "\e[1m").
559
-define(B2, "\e[22m").
560
-define(C(S), case ShCode of true -> [?B1, S, ?B2]; false -> S end).
561

562
%% Arguments are Dim
563
-define(D1, "\e[2m").
564
-define(D2, "\e[22m").
565
-define(A(S), case ShCode of true -> [?D1, S, ?D2]; false -> S end).
566

567
%% Tags are Underline
568
-define(U1, "\e[4m").
569
-define(U2, "\e[24m").
570
-define(G(S), case ShCode of true -> [?U1, S, ?U2]; false -> S end).
571

572
%% B are Nothing
573
-define(N1, "\e[0m").
574
-define(N2, "\e[0m").
575
-define(B(S), case ShCode of true -> [?N1, S, ?N2]; false -> S end).
576

577
print_usage(Version) ->
578
    {MaxC, ShCode} = get_shell_info(),
×
579
    print_usage(dual, MaxC, ShCode, Version).
×
580
print_usage(HelpMode, MaxC, ShCode, Version) ->
581
    AllCommands = get_list_commands(Version),
×
582

583
    print(
×
584
       ["Usage: ", "ejabberdctl", " [--no-timeout] [--node ", ?A("name"), "] [--version ", ?A("apiv"), "] ",
×
585
        "[--auth ", ?A("user host pass"), "] ",
×
586
        ?C("command"), " [", ?A("arguments"), "]\n"
×
587
        "\n"
588
        "Available commands in this ejabberd node:\n"], []),
589
    print_usage_commands(HelpMode, MaxC, ShCode, AllCommands).
×
590

591
print_usage_commands(HelpMode, MaxC, ShCode, Commands) ->
592
    CmdDescsSorted = lists:keysort(1, Commands),
×
593

594
    %% What is the length of the largest command?
595
    {CmdArgsLenDescsSorted, Lens} =
×
596
        lists:mapfoldl(
597
          fun({Cmd, Args, Desc}, Lengths) ->
598
                  Len =
×
599
                      length(Cmd) +
600
                      lists:foldl(fun(Arg, R) ->
601
                                          R + 1 + length(Arg)
×
602
                                  end,
603
                                  0,
604
                                  Args),
605
                  {{Cmd, Args, Len, Desc}, [Len | Lengths]}
×
606
          end,
607
          [],
608
          CmdDescsSorted),
609
    MaxCmdLen = case Lens of
×
610
                    [] -> 80;
×
611
                    _ -> lists:max(Lens)
×
612
                end,
613

614
    %% For each command in the list of commands
615
    %% Convert its definition to a line
616
    FmtCmdDescs = format_command_lines(CmdArgsLenDescsSorted, MaxCmdLen, MaxC, ShCode, HelpMode),
×
617

618
    print([FmtCmdDescs], []).
×
619

620

621
%% Get some info about the shell:
622
%% how many columns of width
623
%% and guess if it supports text formatting codes.
624
get_shell_info() ->
625
    %% This function was introduced in OTP R12B-0
626
    try io:columns() of
×
627
        {ok, C} -> {C-2, true};
×
628
        {error, enotsup} -> {78, false}
×
629
    catch
630
        _:_ -> {78, false}
×
631
    end.
632

633
%% Split this command description in several lines of proper length
634
prepare_description(DescInit, MaxC, Desc) ->
635
    case string:find(Desc, "\n") of
616✔
636
        nomatch ->
637
            prepare_description2(DescInit, MaxC, Desc);
616✔
638
        _ ->
639
            Desc
×
640
    end.
641

642
prepare_description2(DescInit, MaxC, Desc) ->
643
    Words = string:tokens(Desc, " "),
616✔
644
    prepare_long_line(DescInit, MaxC, Words).
616✔
645

646
prepare_long_line(DescInit, MaxC, Words) ->
647
    MaxSegmentLen = MaxC - DescInit,
1,096✔
648
    MarginString = lists:duplicate(DescInit, $\s), % Put spaces
1,096✔
649
    [FirstSegment | MoreSegments] = split_desc_segments(MaxSegmentLen, Words),
1,096✔
650
    MoreSegmentsMixed = mix_desc_segments(MarginString, MoreSegments),
1,096✔
651
    [FirstSegment | MoreSegmentsMixed].
1,096✔
652

653
mix_desc_segments(MarginString, Segments) ->
654
    [["\n", MarginString, Segment] || Segment <- Segments].
1,096✔
655

656
split_desc_segments(MaxL, Words) ->
657
    join(MaxL, Words).
1,096✔
658

659
%% Join words in a segment,
660
%% but stop adding to a segment if adding this word would pass L
661
join(L, Words) ->
662
    join(L, Words, 0, [], []).
1,096✔
663

664
join(_Len, [], _CurSegLen, CurSeg, AllSegs) ->
665
    lists:reverse([CurSeg | AllSegs]);
1,096✔
666
join(Len, [Word | Tail], CurSegLen, CurSeg, AllSegs) ->
667
    WordLen = length(Word),
5,224✔
668
    SegSize = WordLen + CurSegLen + 1,
5,224✔
669
    {NewCurSeg, NewAllSegs, NewCurSegLen} =
5,224✔
670
        if SegSize < Len ->
671
                {[CurSeg, " ", Word], AllSegs, SegSize};
5,136✔
672
           true ->
673
                {Word, [CurSeg | AllSegs], WordLen}
88✔
674
        end,
675
    NewLen = case string:str(Word, "\n") of
5,224✔
676
                 0 ->
677
                     NewCurSegLen;
5,224✔
678
                 _ ->
679
                     0
×
680
             end,
681
    join(Len, Tail, NewLen, NewCurSeg, NewAllSegs).
5,224✔
682

683

684
format_command_lines(CALD, MaxCmdLen, MaxC, ShCode, dual)
685
  when MaxC - MaxCmdLen < 40 ->
686
    %% If the space available for descriptions is too narrow, enforce long help mode
687
    format_command_lines(CALD, MaxCmdLen, MaxC, ShCode, long);
×
688

689
format_command_lines(CALD, _MaxCmdLen, _MaxC, ShCode, short) ->
690
    lists:map(
×
691
      fun({Cmd, Args, _CmdArgsL, _Desc}) ->
692
              ["    ", ?C(Cmd), [[" ", ?A(Arg)] || Arg <- Args], "\n"]
×
693
      end, CALD);
694

695
format_command_lines(CALD, MaxCmdLen, MaxC, ShCode, dual) ->
696
    lists:map(
×
697
      fun({Cmd, Args, CmdArgsL, Desc}) ->
698
              DescFmt = prepare_description(MaxCmdLen+4, MaxC, Desc),
×
699
              ["  ", ?C(Cmd), [[" ", ?A(Arg)] || Arg <- Args],
×
700
               lists:duplicate(MaxCmdLen - CmdArgsL + 1, $\s),
701
               DescFmt, "\n"]
702
      end, CALD);
703

704
format_command_lines(CALD, _MaxCmdLen, MaxC, ShCode, long) ->
705
    lists:map(
×
706
      fun({Cmd, Args, _CmdArgsL, Desc}) ->
707
              DescFmt = prepare_description(13, MaxC, Desc),
×
708
              ["  ", ?C(Cmd), [[" ", ?A(Arg)] || Arg <- Args], "\n",
×
709
               "            ", DescFmt, "\n"]
710
      end, CALD).
711

712

713
%%-----------------------------
714
%% Print Tags
715
%%-----------------------------
716

717
print_usage_tags(MaxC, ShCode, Version) ->
718
    print("Available tags and list of commands:", []),
×
719
    TagsCommands = ejabberd_commands:get_tags_commands(Version),
×
720
    lists:foreach(
×
721
      fun({Tag, Commands} = _TagCommands) ->
722
              print(["\n\n  ", ?G(Tag), "\n    "], []),
×
723
              Words = lists:sort(Commands),
×
724
              Desc = prepare_long_line(5, MaxC, Words),
×
725
              print(?C(Desc), [])
×
726
      end,
727
      TagsCommands),
728
    print("\n\n", []).
×
729

730
print_usage_tags_long(MaxC, ShCode, Version) ->
731
    print("Available tags and commands details:", []),
×
732
    TagsCommands = ejabberd_commands:get_tags_commands(Version),
×
733
    print("\n", []),
×
734
    lists:foreach(
×
735
      fun({Tag, CommandsNames} = _TagCommands) ->
736
              print(["\n  ", ?G(Tag), "\n"], []),
×
737
                CommandsList = lists:map(
×
738
                                 fun(NameString) ->
739
                                         C = ejabberd_commands:get_command_definition(
×
740
                                               list_to_atom(NameString), Version),
741
                                         #ejabberd_commands{name = Name,
×
742
                                                            args = Args,
743
                                                            desc = Desc} = C,
744
                                         tuple_command_help({Name, Args, Desc})
×
745
                                 end,
746
                                 CommandsNames),
747
                print_usage_commands(short, MaxC, ShCode, CommandsList)
×
748
      end,
749
      TagsCommands),
750
    print("\n", []).
×
751

752
print_usage_tags(Tag, MaxC, ShCode, Version) ->
753
    print(["Available commands with tag ", ?G(Tag), ":", "\n", "\n"], []),
×
754
    HelpMode = long,
×
755
    TagsCommands = ejabberd_commands:get_tags_commands(Version),
×
756
    CommandsNames = case lists:keysearch(Tag, 1, TagsCommands) of
×
757
                        {value, {Tag, CNs}} -> CNs;
×
758
                        false -> []
×
759
                    end,
760
    CommandsList = lists:map(
×
761
                     fun(NameString) ->
762
                             C = ejabberd_commands:get_command_definition(
×
763
                                   list_to_atom(NameString), Version),
764
                             #ejabberd_commands{name = Name,
×
765
                                                args = Args,
766
                                                desc = Desc} = C,
767
                             tuple_command_help({Name, Args, Desc})
×
768
                     end,
769
                     CommandsNames),
770
    print_usage_commands(HelpMode, MaxC, ShCode, CommandsList),
×
771
    print("\n", []).
×
772

773

774
%%-----------------------------
775
%% Print usage of 'help' command
776
%%-----------------------------
777

778
print_usage_help(MaxC, ShCode) ->
779
    LongDesc =
×
780
        ["This special ", ?C("help"), " command provides help of ejabberd commands.\n\n"
×
781
         "The format is:\n  ", ?B("ejabberdctl"), " ", ?C("help"),
×
782
         " [", ?A("tags"), " | ", ?A("commands"), " | ", ?G("tag"), " | ", ?C("command"), " | ", ?C("com?*"), "]\n\n"
×
783
         "The optional arguments:\n"
784
         "  ",?A("tags"),"         Show all tags and commands names in each tag\n"
×
785
         "  ",?A("commands"),"     Show all tags and commands details in each tag\n"
×
786
         "  ",?G("tag"),"          Show commands related to this tag\n"
×
787
         "  ",?C("command"),"      Show detailed description of this command\n"
×
788
         "  ",?C("com?*"),"        Show commands that match this glob.\n"
×
789
         "               (? will match a simple character, and\n"
790
         "                * will match several characters)\n"
791
         "\n",
792
         "Some example usages:\n",
793
         "  ejabberdctl ", ?C("help"), "\n",
×
794
         "  ejabberdctl ", ?C("help"), " ", ?A("tags"), "\n",
×
795
         "  ejabberdctl ", ?C("help"), " ", ?A("commands"), "\n",
×
796
         "  ejabberdctl ", ?C("help"), " ", ?G("accounts"), "\n",
×
797
         "  ejabberdctl ", ?C("help"), " ", ?C("register"), "\n",
×
798
         "  ejabberdctl ", ?C("help"), " ", ?C("regist*"), "\n",
×
799
         "\n",
800
         "Some command arguments are lists or tuples, like add_rosteritem and create_room_with_opts.\n",
801
         "Separate the elements in a list with the , character.\n",
802
         "Separate the elements in a tuple with the : character.\n",
803
         "\n",
804
         "Some commands results are lists or tuples, like get_roster and get_user_subscriptions.\n",
805
         "The elements in a list are separated with a , character.\n",
806
         "The elements in a tuple are separated with a tabular character.\n"],
807
    ArgsDef = [],
×
808
    C = #ejabberd_commands{
×
809
           name = help,
810
           desc = "Show help of ejabberd commands",
811
           longdesc = lists:flatten(LongDesc),
812
           args = ArgsDef,
813
           result = {help, string}},
814
    print(get_usage_command2("help", C, MaxC, ShCode), []).
×
815

816

817
%%-----------------------------
818
%% Print usage command
819
%%-----------------------------
820

821
-spec print_usage_commands2(CmdSubString::string(), MaxC::integer(),
822
                            ShCode::boolean(), Version::integer()) -> ok.
823
print_usage_commands2(CmdSubString, MaxC, ShCode, Version) ->
824
    %% Get which command names match this substring
825
    AllCommandsNames = [atom_to_list(Name) || {Name, _, _} <- ejabberd_commands:list_commands(Version)],
×
826
    Cmds = filter_commands(AllCommandsNames, CmdSubString),
×
827
    case Cmds of
×
828
        [] -> io:format("Error: no command found that match '~ts'~n", [CmdSubString]);
×
829
        _ -> print_usage_commands3(lists:sort(Cmds), MaxC, ShCode, Version)
×
830
    end.
831

832
print_usage_commands3([Cmd], MaxC, ShCode, Version) ->
833
    print_usage_command(Cmd, MaxC, ShCode, Version);
×
834
print_usage_commands3(Cmds, MaxC, ShCode, Version) ->
835
        CommandsList = lists:map(
×
836
                     fun(NameString) ->
837
                             C = ejabberd_commands:get_command_definition(
×
838
                                   list_to_atom(NameString), Version),
839
                             #ejabberd_commands{name = Name,
×
840
                                                args = Args,
841
                                                desc = Desc} = C,
842
                             tuple_command_help({Name, Args, Desc})
×
843
                     end,
844
                     Cmds),
845

846
              print_usage_commands(long, MaxC, ShCode, CommandsList), %% que aqui solo muestre un par de lineas
×
847
              ok.
×
848

849
filter_commands(All, SubString) ->
850
    case lists:member(SubString, All) of
×
851
        true -> [SubString];
×
852
        false -> filter_commands_regexp(All, SubString)
×
853
    end.
854

855
filter_commands_regexp(All, Glob) ->
856
    RegExp = ejabberd_regexp:sh_to_awk(list_to_binary(Glob)),
×
857
    lists:filter(
×
858
      fun(Command) ->
859
              case ejabberd_regexp:run(list_to_binary(Command), RegExp) of
×
860
                  match ->
861
                      true;
×
862
                  nomatch ->
863
                      false
×
864
              end
865
      end,
866
      All).
867

868
maybe_add_policy_arguments(Args, user) ->
869
    [{user, binary}, {host, binary} | Args];
168✔
870
maybe_add_policy_arguments(Args, _) ->
871
    Args.
312✔
872

873
-spec print_usage_command(Cmd::string(), MaxC::integer(),
874
                          ShCode::boolean(), Version::integer()) -> ok.
875
print_usage_command(Cmd, MaxC, ShCode, Version) ->
876
    print(get_usage_command(Cmd, MaxC, ShCode, Version), []).
×
877

878
get_usage_command(Cmd, MaxC, ShCode, Version) ->
879
    Name = list_to_atom(Cmd),
480✔
880
    C = ejabberd_commands:get_command_definition(Name, Version),
480✔
881
    get_usage_command2(Cmd, C, MaxC, ShCode).
480✔
882

883
get_usage_command2(Cmd, C, MaxC, ShCode) ->
884
    #ejabberd_commands{
480✔
885
                     tags = TagsAtoms,
886
                     definer = Definer,
887
                     desc = Desc,
888
                     args = ArgsDefPreliminary,
889
                     args_desc = ArgsDesc,
890
                     args_example = ArgsExample,
891
                     result_example = ResultExample,
892
                     policy = Policy,
893
                     longdesc = LongDesc,
894
                     note = Note,
895
                     result = ResultDef} = C,
896

897
    NameFmt = ["  ", ?B("Command Name"), ": ", ?C(Cmd), "\n"],
480✔
898

899
    %% Initial indentation of result is 13 = length("  Arguments: ")
900
    ArgsDef = maybe_add_policy_arguments(ArgsDefPreliminary, Policy),
480✔
901
    ArgsDetailed = add_args_desc(ArgsDef, ArgsDesc),
480✔
902
    Args = [format_usage_ctype1(ArgDetailed, 13, ShCode) || ArgDetailed <- ArgsDetailed],
480✔
903

904
    ArgsMargin = lists:duplicate(13, $\s),
480✔
905
    ArgsListFmt = case Args of
480✔
906
                      [] -> "\n";
×
907
                      _ -> [ [Arg, "\n", ArgsMargin] || Arg <- Args]
480✔
908
                  end,
909
    ArgsFmt = ["  ", ?B("Arguments"), ": ", ArgsListFmt],
480✔
910

911
    %% Initial indentation of result is 11 = length("  Returns: ")
912
    ResultFmt = format_usage_ctype(ResultDef, 11),
480✔
913
    ReturnsFmt = ["  ",?B("Result"),": ", ResultFmt],
480✔
914

915
    ExampleMargin = lists:duplicate(11, $\s),
480✔
916
    Example = format_usage_example(Cmd, ArgsExample, ResultExample, ExampleMargin),
480✔
917
    ExampleFmt = case Example of
480✔
918
                      [] ->
919
                            "";
168✔
920
                      _ ->
921
                            ExampleListFmt = [ [Ex, "\n", ExampleMargin] || Ex <- Example],
312✔
922
                            ["  ",?B("Example"),": ", ExampleListFmt, "\n"]
312✔
923
                  end,
924

925
    TagsFmt = ["  ",?B("Tags"),":", prepare_long_line(8, MaxC, [?G(atom_to_list(TagA)) || TagA <- TagsAtoms])],
480✔
926

927
    IsDefinerMod = case Definer of
480✔
928
                     unknown -> true;
152✔
929
                     _ -> lists:member([gen_mod], proplists:get_all_values(behaviour, Definer:module_info(attributes)))
328✔
930
                 end,
931
    ModuleFmt = case IsDefinerMod of
480✔
932
                    true -> ["  ",?B("Module"),": ", atom_to_list(Definer), "\n\n"];
480✔
933
                    false -> []
×
934
                end,
935

936
    NoteFmt = case Note of
480✔
937
                    "" -> [];
368✔
938
                    _ -> ["  ",?B("Note"),": ", Note, "\n\n"]
112✔
939
                end,
940

941
    DescFmt = ["  ",?B("Description"),":", prepare_description(15, MaxC, Desc)],
480✔
942

943
    LongDescFmt = case LongDesc of
480✔
944
                      "" -> "";
344✔
945
                      _ -> ["", prepare_description(0, MaxC, LongDesc), "\n\n"]
136✔
946
                  end,
947

948
    NoteEjabberdctlList = case has_list_args(ArgsDefPreliminary) of
480✔
949
                          true -> ["  ", ?B("Note:"), " In a list argument, separate the elements using the , character for example: one,two,three\n\n"];
×
950
                          false -> ""
480✔
951
                      end,
952
    NoteEjabberdctlTuple = case has_tuple_args(ArgsDefPreliminary) of
480✔
953
                          true -> ["  ", ?B("Note:"), " In a tuple argument, separate the elements using the : character for example: members_only:true\n\n"];
×
954
                          false -> ""
480✔
955
                      end,
956

957
    First = case Cmd of
480✔
958
        "help" -> "";
×
959
        _ -> [NameFmt, "\n", ArgsFmt, "\n", ReturnsFmt,
480✔
960
                    "\n\n", ExampleFmt, TagsFmt, "\n\n", ModuleFmt, NoteFmt, DescFmt, "\n\n"]
961
    end,
962
    [First, LongDescFmt, NoteEjabberdctlList, NoteEjabberdctlTuple].
480✔
963

964
%%-----------------------------
965
%% Format Arguments Help
966
%%-----------------------------
967

968
add_args_desc(Definitions, none) ->
969
    Descriptions = lists:duplicate(length(Definitions), ""),
168✔
970
    add_args_desc(Definitions, Descriptions);
168✔
971
add_args_desc(Definitions, Descriptions) ->
972
    lists:zipwith(fun({Name, Type}, Description) ->
480✔
973
                          {Name, Type, Description} end,
912✔
974
                  Definitions,
975
                  Descriptions).
976

977
format_usage_ctype1({_Name, _Type} = Definition, Indentation, ShCode) ->
978
    [Arg] = add_args_desc([Definition], none),
×
979
    format_usage_ctype1(Arg, Indentation, ShCode);
×
980
format_usage_ctype1({Name, Type, Description}, Indentation, ShCode) ->
981
    TypeString = case Type of
912✔
982
        {list, ElementDef} ->
983
            NameFmt = atom_to_list(Name),
×
984
            Indentation2 = Indentation + length(NameFmt) + 4,
×
985
            ElementFmt = format_usage_ctype1(ElementDef, Indentation2, ShCode),
×
986
            io_lib:format("[ ~s ]", [lists:flatten(ElementFmt)]);
×
987
        {tuple, ElementsDef} ->
988
            NameFmt = atom_to_list(Name),
×
989
            Indentation2 = Indentation + length(NameFmt) + 4,
×
990
            ElementsFmt = format_usage_tuple(ElementsDef, Indentation2),
×
991
            io_lib:format("{ ~s }", [lists:flatten(ElementsFmt)]);
×
992
        _ ->
993
            Type
912✔
994
    end,
995
    DescriptionText = case Description of
912✔
996
                          "" -> "";
336✔
997
                          Description -> " : "++Description
576✔
998
                      end,
999
    io_lib:format("~p::~s~s", [Name, TypeString, DescriptionText]).
912✔
1000

1001

1002
format_usage_ctype(Type, _Indentation)
1003
  when (Type==atom) or (Type==integer) or (Type==string) or (Type==binary)
1004
       or (Type==rescode) or (Type==restuple) or (Type==binary_or_list) ->
1005
    io_lib:format("~p", [Type]);
×
1006

1007
format_usage_ctype({Name, Type}, _Indentation)
1008
  when (Type==atom) or (Type==integer) or (Type==string) or (Type==binary)
1009
       or (Type==rescode) or (Type==restuple) or (Type==binary_or_list)
1010
       or (Type==any) ->
1011
    io_lib:format("~p::~p", [Name, Type]);
752✔
1012

1013
format_usage_ctype({Name, {list, ElementDef}}, Indentation) ->
1014
    NameFmt = atom_to_list(Name),
40✔
1015
    Indentation2 = Indentation + length(NameFmt) + 4,
40✔
1016
    ElementFmt = format_usage_ctype(ElementDef, Indentation2),
40✔
1017
    [NameFmt, "::[ ", ElementFmt, " ]"];
40✔
1018

1019
format_usage_ctype({Name, {tuple, ElementsDef}}, Indentation) ->
1020
    NameFmt = atom_to_list(Name),
104✔
1021
    Indentation2 = Indentation + length(NameFmt) + 4,
104✔
1022
    ElementsFmt = format_usage_tuple(ElementsDef, Indentation2),
104✔
1023
    [NameFmt, "::{ "] ++ ElementsFmt ++ [" }"].
104✔
1024

1025

1026
format_usage_tuple([], _Indentation) ->
1027
    [];
×
1028
format_usage_tuple([ElementDef], Indentation) ->
1029
    format_usage_ctype(ElementDef, Indentation);
104✔
1030
format_usage_tuple([ElementDef | ElementsDef], Indentation) ->
1031
    ElementFmt = format_usage_ctype(ElementDef, Indentation),
272✔
1032
    MarginString = lists:duplicate(Indentation, $\s), % Put spaces
272✔
1033
    [ElementFmt, ",\n", MarginString, format_usage_tuple(ElementsDef, Indentation)].
272✔
1034

1035
print(Format, Args) ->
1036
    io:format(lists:flatten(Format), Args).
×
1037

1038
%%-----------------------------
1039
%% Format Example Help
1040
%%-----------------------------
1041

1042
format_usage_example(_Cmd, none, _ResultExample, _Indentation) ->
1043
    "";
168✔
1044
format_usage_example(Cmd, ArgsExample, ResultExample, Indentation) ->
1045
    Arguments = format_usage_arguments(ArgsExample, []),
312✔
1046
    Result = format_usage_result([ResultExample], [], Indentation),
312✔
1047
    [lists:join(" ", ["ejabberdctl", Cmd] ++ Arguments) | Result].
312✔
1048

1049
format_usage_arguments([], R) ->
1050
    lists:reverse(R);
312✔
1051

1052
format_usage_arguments([Argument | Arguments], R)
1053
  when is_integer(Argument) ->
1054
    format_usage_arguments(Arguments, [integer_to_list(Argument) | R]);
24✔
1055

1056
format_usage_arguments([[Integer|_] = Argument | Arguments], R)
1057
  when is_list(Argument) and is_integer(Integer) ->
1058
    Result = case contains_more_than_letters(Argument) of
×
1059
                 true -> ["\"", Argument, "\""];
×
1060
                 false -> [Argument]
×
1061
             end,
1062
    format_usage_arguments(Arguments, [Result | R]);
×
1063

1064
format_usage_arguments([[Element | _] = Argument | Arguments], R)
1065
  when is_list(Argument) and is_tuple(Element) ->
1066
    ArgumentFmt = format_usage_arguments(Argument, []),
×
1067
    format_usage_arguments(Arguments, [lists:join(",", ArgumentFmt) | R]);
×
1068

1069
format_usage_arguments([Argument | Arguments], R)
1070
  when is_list(Argument) ->
1071
    Result = format_usage_arguments(Argument, []),
×
1072
    format_usage_arguments(Arguments, [lists:join(",", Result) | R]);
×
1073

1074
format_usage_arguments([Argument | Arguments], R)
1075
  when is_tuple(Argument) ->
1076
    Result = format_usage_arguments(tuple_to_list(Argument), []),
×
1077
    format_usage_arguments(Arguments, [lists:join(":", Result) | R]);
×
1078

1079
format_usage_arguments([Argument | Arguments], R)
1080
  when is_binary(Argument) ->
1081
    Result = case contains_more_than_letters(binary_to_list(Argument)) of
552✔
1082
                 true -> ["\"", Argument, "\""];
416✔
1083
                 false -> [Argument]
136✔
1084
             end,
1085
    format_usage_arguments(Arguments, [Result | R]);
552✔
1086

1087
format_usage_arguments([Argument | Arguments], R) ->
1088
    format_usage_arguments(Arguments, [Argument | R]).
×
1089

1090
format_usage_result([none], _R, _Indentation) ->
1091
    "";
56✔
1092
format_usage_result([], R, _Indentation) ->
1093
    lists:reverse(R);
384✔
1094

1095
format_usage_result([{Code, Text} | Arguments], R, Indentation)
1096
  when is_atom(Code) and is_binary(Text) ->
1097
    format_usage_result(Arguments, [Text | R], Indentation);
×
1098

1099
format_usage_result([Argument | Arguments], R, Indentation)
1100
  when is_atom(Argument) ->
1101
    format_usage_result(Arguments, [["\'", atom_to_list(Argument), "\'"] | R], Indentation);
24✔
1102

1103
format_usage_result([Argument | Arguments], R, Indentation)
1104
  when is_integer(Argument) ->
1105
    format_usage_result(Arguments, [integer_to_list(Argument) | R], Indentation);
80✔
1106

1107
format_usage_result([[Integer|_] = Argument | Arguments], R, Indentation)
1108
  when is_list(Argument) and is_integer(Integer) ->
1109
    format_usage_result(Arguments, [Argument | R], Indentation);
256✔
1110

1111
format_usage_result([[Element | _] = Argument | Arguments], R, Indentation)
1112
  when is_list(Argument) and is_tuple(Element) ->
1113
    ArgumentFmt = format_usage_result(Argument, [], Indentation),
24✔
1114
    format_usage_result(Arguments, [lists:join("\n"++Indentation, ArgumentFmt) | R], Indentation);
24✔
1115

1116
format_usage_result([Argument | Arguments], R, Indentation)
1117
  when is_list(Argument) ->
1118
    format_usage_result(Arguments, [lists:join("\n"++Indentation, Argument) | R], Indentation);
16✔
1119

1120
format_usage_result([Argument | Arguments], R, Indentation)
1121
  when is_tuple(Argument) ->
1122
    Result = format_usage_result(tuple_to_list(Argument), [], Indentation),
104✔
1123
    format_usage_result(Arguments, [lists:join("\t", Result) | R], Indentation);
104✔
1124

1125
format_usage_result([Argument | Arguments], R, Indentation) ->
1126
    format_usage_result(Arguments, [Argument | R], Indentation).
152✔
1127

1128
contains_more_than_letters(Argument) ->
1129
    lists:any(fun(I) when (I < $A) -> true;
552✔
1130
                 (I) when (I > $z) -> true;
×
1131
                 (_) -> false end,
3,264✔
1132
              Argument).
1133

1134
%%-----------------------------
1135
%% Register commands
1136
%%-----------------------------
1137

1138
get_commands_spec() ->
1139
    [
1140
     #ejabberd_commands{name = help, tags = [ejabberdctl],
11✔
1141
                        desc = "Get list of commands, or help of a command (only ejabberdctl)",
1142
                        longdesc = "This command is exclusive for the ejabberdctl command-line script, "
1143
                        "don't attempt to execute it using any other API frontend."},
1144
     #ejabberd_commands{name = mnesia_change, tags = [ejabberdctl, mnesia],
1145
                        desc = "Change the erlang node name in the mnesia database (only ejabberdctl)",
1146
                        longdesc = "This command internally calls the _`mnesia_change_nodename`_ API. "
1147
                        "This is a special command that starts and stops ejabberd several times: "
1148
                        "do not attempt to run this command when ejabberd is running. "
1149
                        "This command is exclusive for the ejabberdctl command-line script, "
1150
                        "don't attempt to execute it using any other API frontend.",
1151
                        note = "added in 25.08",
1152
                        args = [{old_node_name, string}],
1153
                        args_desc = ["Old erlang node name"],
1154
                        args_example = ["ejabberd@oldmachine"]},
1155
     #ejabberd_commands{name = mnesia_info_ctl, tags = [ejabberdctl, mnesia],
1156
                        desc = "Show information of Mnesia system (only ejabberdctl)",
1157
                        note = "renamed in 24.02",
1158
                        longdesc = "This command is exclusive for the ejabberdctl command-line script, "
1159
                        "don't attempt to execute it using any other API frontend."},
1160
     #ejabberd_commands{name = print_sql_schema, tags = [ejabberdctl, sql],
1161
                        desc = "Print SQL schema for the given RDBMS (only ejabberdctl)",
1162
                        longdesc = "This command is exclusive for the ejabberdctl command-line script, "
1163
                        "don't attempt to execute it using any other API frontend.",
1164
                        note = "added in 24.02",
1165
                        args = [{db_type, string}, {db_version, string}, {multihost_schema, string}],
1166
                        args_desc = ["Database type: pgsql | mysql | sqlite",
1167
                                     "Your database version: 16.1, 8.2.0...",
1168
                                     "Use multihost schema: 0, false, 1 or true"],
1169
                        args_example = ["pgsql", "16.1", "true"]}
1170
    ].
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc