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

processone / ejabberd / 1212

18 Nov 2025 12:37PM UTC coverage: 33.784% (+0.003%) from 33.781%
1212

push

github

badlop
mod_conversejs: Improve link to conversejs in WebAdmin (#4495)

Until now, the WebAdmin menu included a link to the first request handler
with mod_conversejs that the admin configured in ejabberd.yml
That link included the authentication credentials hashed as URI arguments
if using HTTPS. Then process/2 extracted those arguments and passed them
as autologin options to Converse.

From now, mod_conversejs automatically adds a request_handler nested in
webadmin subpath. The webadmin menu links to that converse URI; this allows
to access the HTTP auth credentials, no need to explicitly pass them.
process/2 extracts this HTTP auth and passes autologin options to Converse.
Now scram password storage is supported too.

This minimum configuration allows WebAdmin to access Converse:

listen:
  -
    port: 5443
    module: ejabberd_http
    tls: true
    request_handlers:
      /admin: ejabberd_web_admin
      /ws: ejabberd_http_ws
modules:
  mod_conversejs:
    conversejs_resources: "/home/conversejs/12.0.0/dist"

0 of 12 new or added lines in 1 file covered. (0.0%)

11290 existing lines in 174 files now uncovered.

15515 of 45924 relevant lines covered (33.78%)

1277.8 hits per line

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

1.94
/src/mod_http_fileserver.erl
1
%%%-------------------------------------------------------------------
2
%%% File    : mod_http_fileserver.erl
3
%%% Author  : Massimiliano Mirra <mmirra [at] process-one [dot] net>
4
%%% Purpose : Simple file server plugin for embedded ejabberd web server
5
%%% Created :
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(mod_http_fileserver).
27

28
-author('mmirra@process-one.net').
29

30
-behaviour(gen_mod).
31
-behaviour(gen_server).
32

33
%% gen_mod callbacks
34
-export([start/2, stop/1, reload/3]).
35

36
%% gen_server callbacks
37
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
38
         terminate/2, code_change/3]).
39

40
%% request_handlers callbacks
41
-export([process/2]).
42

43
%% utility for other http modules
44
-export([content_type/3]).
45

46
-export([reopen_log/0, mod_opt_type/1, mod_options/1, depends/2, mod_doc/0]).
47

48
-include("logger.hrl").
49
-include("ejabberd_http.hrl").
50
-include_lib("kernel/include/file.hrl").
51
-include("translate.hrl").
52

53
-record(state,
54
        {host, docroot, accesslog, accesslogfd,
55
         directory_indices, custom_headers, default_content_type,
56
         content_types = [], user_access = none}).
57

58
%% Response is {DataSize, Code, [{HeaderKey, HeaderValue}], Data}
59
-define(HTTP_ERR_FILE_NOT_FOUND,
60
        {-1, 404, [], <<"Not found">>}).
61

62
-define(REQUEST_AUTH_HEADERS,
63
        [{<<"WWW-Authenticate">>, <<"Basic realm=\"ejabberd\"">>}]).
64

65
-define(HTTP_ERR_FORBIDDEN,
66
        {-1, 403, [], <<"Forbidden">>}).
67
-define(HTTP_ERR_REQUEST_AUTH,
68
        {-1, 401, ?REQUEST_AUTH_HEADERS, <<"Unauthorized">>}).
69
-define(HTTP_ERR_HOST_UNKNOWN,
70
        {-1, 410, [], <<"Host unknown">>}).
71

72
-define(DEFAULT_CONTENT_TYPES,
73
        [{<<".css">>, <<"text/css">>},
74
         {<<".gif">>, <<"image/gif">>},
75
         {<<".html">>, <<"text/html">>},
76
         {<<".jar">>, <<"application/java-archive">>},
77
         {<<".jpeg">>, <<"image/jpeg">>},
78
         {<<".jpg">>, <<"image/jpeg">>},
79
         {<<".js">>, <<"text/javascript">>},
80
         {<<".png">>, <<"image/png">>},
81
         {<<".svg">>, <<"image/svg+xml">>},
82
         {<<".txt">>, <<"text/plain">>},
83
         {<<".xml">>, <<"application/xml">>},
84
         {<<".xpi">>, <<"application/x-xpinstall">>},
85
         {<<".xul">>, <<"application/vnd.mozilla.xul+xml">>}]).
86

87
%%====================================================================
88
%% gen_mod callbacks
89
%%====================================================================
90

91
start(Host, Opts) ->
92
    gen_mod:start_child(?MODULE, Host, Opts).
×
93

94
stop(Host) ->
95
    gen_mod:stop_child(?MODULE, Host).
×
96

97
reload(Host, NewOpts, OldOpts) ->
98
    Proc = get_proc_name(Host),
×
99
    gen_server:cast(Proc, {reload, Host, NewOpts, OldOpts}).
×
100

101
depends(_Host, _Opts) ->
102
    [].
×
103

104
%%====================================================================
105
%% gen_server callbacks
106
%%====================================================================
107
%%--------------------------------------------------------------------
108
%% Function: init(Args) -> {ok, State} |
109
%%                         {ok, State, Timeout} |
110
%%                         ignore               |
111
%%                         {stop, Reason}
112
%% Description: Initiates the server
113
%%--------------------------------------------------------------------
114
init([Host|_]) ->
115
    Opts = gen_mod:get_module_opts(Host, ?MODULE),
×
116
    try initialize(Host, Opts) of
×
117
        State ->
118
            process_flag(trap_exit, true),
×
119
            {ok, State}
×
120
    catch
121
        throw:Reason ->
122
            {stop, Reason}
×
123
    end.
124

125
initialize(Host, Opts) ->
126
    DocRoot = mod_http_fileserver_opt:docroot(Opts),
×
127
    AccessLog = mod_http_fileserver_opt:accesslog(Opts),
×
128
    AccessLogFD = try_open_log(AccessLog, Host),
×
129
    DirectoryIndices = mod_http_fileserver_opt:directory_indices(Opts),
×
130
    CustomHeaders = mod_http_fileserver_opt:custom_headers(Opts),
×
131
    DefaultContentType = mod_http_fileserver_opt:default_content_type(Opts),
×
132
    UserAccess0 = mod_http_fileserver_opt:must_authenticate_with(Opts),
×
133
    UserAccess = case UserAccess0 of
×
134
                     [] -> none;
×
135
                     _ ->
136
                         maps:from_list(UserAccess0)
×
137
                 end,
138
    ContentTypes = build_list_content_types(
×
139
                     mod_http_fileserver_opt:content_types(Opts),
140
                     ?DEFAULT_CONTENT_TYPES),
141
    ?DEBUG("Known content types: ~ts",
×
142
           [str:join([[$*, K, " -> ", V] || {K, V} <- ContentTypes],
×
143
                     <<", ">>)]),
×
144
    #state{host = Host,
×
145
           accesslog = AccessLog,
146
           accesslogfd = AccessLogFD,
147
           docroot = DocRoot,
148
           directory_indices = DirectoryIndices,
149
           custom_headers = CustomHeaders,
150
           default_content_type = DefaultContentType,
151
           content_types = ContentTypes,
152
           user_access = UserAccess}.
153

154
-spec build_list_content_types(AdminCTs::[{binary(), binary()|undefined}],
155
                               Default::[{binary(), binary()|undefined}]) ->
156
    [{string(), string()|undefined}].
157
%% where CT = {Extension::string(), Value}
158
%%       Value = string() | undefined
159
%% @doc Return a unified list without duplicates.
160
%% Elements of AdminCTs have more priority.
161
%% If a CT is declared as 'undefined', then it is not included in the result.
162
build_list_content_types(AdminCTsUnsorted, DefaultCTsUnsorted) ->
163
    AdminCTs = lists:ukeysort(1, AdminCTsUnsorted),
×
164
    DefaultCTs = lists:ukeysort(1, DefaultCTsUnsorted),
×
165
    CTsUnfiltered = lists:ukeymerge(1, AdminCTs,
×
166
                                    DefaultCTs),
167
    [{Extension, Value}
×
168
     || {Extension, Value} <- CTsUnfiltered,
×
169
        Value /= undefined].
×
170

171
try_open_log(undefined, _Host) ->
172
    undefined;
×
173
try_open_log(FN, _Host) ->
174
    FD = try open_log(FN) of
×
175
             FD1 -> FD1
×
176
         catch
177
             throw:{cannot_open_accesslog, FN, Reason} ->
178
                 ?ERROR_MSG("Cannot open access log file: ~p~nReason: ~p", [FN, Reason]),
×
179
                 undefined
×
180
         end,
181
    ejabberd_hooks:add(reopen_log_hook, ?MODULE, reopen_log, 50),
×
182
    FD.
×
183

184
%%--------------------------------------------------------------------
185
%% Function: handle_call(Request, From, State) -> {reply, Reply, State} |
186
%%                                      {reply, Reply, State, Timeout} |
187
%%                                      {noreply, State} |
188
%%                                      {noreply, State, Timeout} |
189
%%                                      {stop, Reason, Reply, State} |
190
%%                                      {stop, Reason, State}
191
%% Description: Handling call messages
192
%%--------------------------------------------------------------------
193
handle_call({serve, LocalPath, Auth, RHeaders}, _From, State) ->
194
    IfModifiedSince = case find_header('If-Modified-Since', RHeaders, bad_date) of
×
195
                          bad_date ->
196
                              bad_date;
×
197
                          Val ->
198
                              httpd_util:convert_request_date(binary_to_list(Val))
×
199
                      end,
200
    Reply = serve(LocalPath, Auth, State#state.docroot, State#state.directory_indices,
×
201
                  State#state.custom_headers,
202
                  State#state.default_content_type, State#state.content_types,
203
                  State#state.user_access, IfModifiedSince),
204
    {reply, Reply, State};
×
205
handle_call(Request, From, State) ->
206
    ?WARNING_MSG("Unexpected call from ~p: ~p", [From, Request]),
×
207
    {noreply, State}.
×
208

209
%%--------------------------------------------------------------------
210
%% Function: handle_cast(Msg, State) -> {noreply, State} |
211
%%                                      {noreply, State, Timeout} |
212
%%                                      {stop, Reason, State}
213
%% Description: Handling cast messages
214
%%--------------------------------------------------------------------
215
handle_cast({add_to_log, FileSize, Code, Request}, State) ->
216
    add_to_log(State#state.accesslogfd, FileSize, Code, Request),
×
217
    {noreply, State};
×
218
handle_cast(reopen_log, State) ->
219
    FD2 = reopen_log(State#state.accesslog, State#state.accesslogfd),
×
220
    {noreply, State#state{accesslogfd = FD2}};
×
221
handle_cast({reload, Host, NewOpts, _OldOpts}, OldState) ->
222
    try initialize(Host, NewOpts) of
×
223
        NewState ->
224
            FD = reopen_log(NewState#state.accesslog, OldState#state.accesslogfd),
×
225
            {noreply, NewState#state{accesslogfd = FD}}
×
226
    catch throw:_ ->
227
            {noreply, OldState}
×
228
    end;
229
handle_cast(Msg, State) ->
230
    ?WARNING_MSG("Unexpected cast: ~p", [Msg]),
×
231
    {noreply, State}.
×
232

233
%%--------------------------------------------------------------------
234
%% Function: handle_info(Info, State) -> {noreply, State} |
235
%%                                       {noreply, State, Timeout} |
236
%%                                       {stop, Reason, State}
237
%% Description: Handling all non call/cast messages
238
%%--------------------------------------------------------------------
239
handle_info(Info, State) ->
240
    ?WARNING_MSG("Unexpected info: ~p", [Info]),
×
241
    {noreply, State}.
×
242

243
%%--------------------------------------------------------------------
244
%% Function: terminate(Reason, State) -> void()
245
%% Description: This function is called by a gen_server when it is about to
246
%% terminate. It should be the opposite of Module:init/1 and do any necessary
247
%% cleaning up. When it returns, the gen_server terminates with Reason.
248
%% The return value is ignored.
249
%%--------------------------------------------------------------------
250
terminate(_Reason, #state{host = Host} = State) ->
251
    close_log(State#state.accesslogfd),
×
252
    case gen_mod:is_loaded_elsewhere(Host, ?MODULE) of
×
253
        false ->
254
            ejabberd_hooks:delete(reopen_log_hook, ?MODULE, reopen_log, 50);
×
255
        true ->
256
            ok
×
257
    end.
258

259
%%--------------------------------------------------------------------
260
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
261
%% Description: Convert process state when code is changed
262
%%--------------------------------------------------------------------
263
code_change(_OldVsn, State, _Extra) ->
264
    {ok, State}.
×
265

266
%%====================================================================
267
%% request_handlers callbacks
268
%%====================================================================
269

270
-spec process(LocalPath::[binary()], #request{}) ->
271
    {HTTPCode::integer(), [{binary(), binary()}], Page::string()}.
272
%% @doc Handle an HTTP request.
273
%% LocalPath is the part of the requested URL path that is "local to the module".
274
%% Returns the page to be sent back to the client and/or HTTP status code.
275
process(LocalPath, #request{host = Host, auth = Auth, headers = RHeaders} = Request) ->
276
    ?DEBUG("Requested ~p", [LocalPath]),
×
277
    try
×
278
        VHost = ejabberd_router:host_of_route(Host),
×
279
        {FileSize, Code, Headers, Contents} =
×
280
            gen_server:call(get_proc_name(VHost),
281
                            {serve, LocalPath, Auth, RHeaders}),
282
        add_to_log(FileSize, Code, Request#request{host = VHost}),
×
283
        {Code, Headers, Contents}
×
284
    catch _:{Why, _} when Why == noproc; Why == invalid_domain; Why == unregistered_route ->
285
            ?DEBUG("Received an HTTP request with Host: ~ts, "
×
286
                   "but couldn't find the related "
287
                   "ejabberd virtual host", [Host]),
×
288
            {FileSize1, Code1, Headers1, Contents1} = ?HTTP_ERR_HOST_UNKNOWN,
×
289
            add_to_log(FileSize1, Code1, Request#request{host = ejabberd_config:get_myname()}),
×
290
            {Code1, Headers1, Contents1}
×
291
    end.
292

293
serve(LocalPath, Auth, DocRoot, DirectoryIndices, CustomHeaders, DefaultContentType,
294
    ContentTypes, UserAccess, IfModifiedSince) ->
295
    CanProceed = case {UserAccess, Auth} of
×
296
                     {none, _} -> true;
×
297
                     {_, {User, Pass}} ->
298
                         case maps:find(User, UserAccess) of
×
299
                             {ok, Pass} -> true;
×
300
                             _ -> false
×
301
                         end;
302
                     _ ->
303
                         false
×
304
                 end,
305
    case CanProceed of
×
306
        false ->
307
            ?HTTP_ERR_REQUEST_AUTH;
×
308
        true ->
309
            FileName = filename:join(filename:split(DocRoot) ++ LocalPath),
×
310
            case file:read_file_info(FileName) of
×
311
                {error, enoent} ->
312
                    ?HTTP_ERR_FILE_NOT_FOUND;
×
313
                {error, enotdir} ->
314
                    ?HTTP_ERR_FILE_NOT_FOUND;
×
315
                {error, eacces} ->
316
                    ?HTTP_ERR_FORBIDDEN;
×
317
                {ok, #file_info{type = directory}} -> serve_index(FileName,
×
318
                                                                  DirectoryIndices,
319
                                                                  CustomHeaders,
320
                                                                  DefaultContentType,
321
                                                                  ContentTypes);
322
                {ok, #file_info{mtime = MTime} = FileInfo} ->
323
                    case calendar:local_time_to_universal_time_dst(MTime) of
×
324
                        [IfModifiedSince | _] ->
325
                            serve_not_modified(FileInfo, FileName,
×
326
                                               CustomHeaders);
327
                        _ ->
328
                            serve_file(FileInfo, FileName,
×
329
                                       CustomHeaders,
330
                                       DefaultContentType,
331
                                       ContentTypes)
332
                    end
333
            end
334
    end.
335

336
%% Troll through the directory indices attempting to find one which
337
%% works, if none can be found, return a 404.
338
serve_index(_FileName, [], _CH, _DefaultContentType, _ContentTypes) ->
339
    ?HTTP_ERR_FILE_NOT_FOUND;
×
340
serve_index(FileName, [Index | T], CH, DefaultContentType, ContentTypes) ->
341
    IndexFileName = filename:join([FileName] ++ [Index]),
×
342
    case file:read_file_info(IndexFileName) of
×
343
        {error, _Error}                    -> serve_index(FileName, T, CH, DefaultContentType, ContentTypes);
×
344
        {ok, #file_info{type = directory}} -> serve_index(FileName, T, CH, DefaultContentType, ContentTypes);
×
345
        {ok, FileInfo}                     -> serve_file(FileInfo, IndexFileName, CH, DefaultContentType, ContentTypes)
×
346
    end.
347

348
serve_not_modified(FileInfo, FileName, CustomHeaders) ->
349
    ?DEBUG("Delivering not modified: ~ts", [FileName]),
×
350
    {0, 304,
×
351
     ejabberd_http:apply_custom_headers(
352
         [{<<"Server">>, <<"ejabberd">>},
353
          {<<"Last-Modified">>, last_modified(FileInfo)}],
354
         CustomHeaders), <<>>}.
355

356
%% Assume the file exists if we got this far and attempt to read it in
357
%% and serve it up.
358
serve_file(FileInfo, FileName, CustomHeaders, DefaultContentType, ContentTypes) ->
359
    ?DEBUG("Delivering: ~ts", [FileName]),
×
360
    ContentType = content_type(FileName, DefaultContentType,
×
361
                               ContentTypes),
362
    {FileInfo#file_info.size, 200,
×
363
     ejabberd_http:apply_custom_headers(
364
         [{<<"Server">>, <<"ejabberd">>},
365
          {<<"Last-Modified">>, last_modified(FileInfo)},
366
          {<<"Content-Type">>, ContentType}],
367
         CustomHeaders),
368
     {file, FileName}}.
369

370
%%----------------------------------------------------------------------
371
%% Log file
372
%%----------------------------------------------------------------------
373

374
open_log(FN) ->
375
    case file:open(FN, [append]) of
×
376
        {ok, FD} ->
377
            FD;
×
378
        {error, Reason} ->
379
            throw({cannot_open_accesslog, FN, Reason})
×
380
    end.
381

382
close_log(FD) ->
383
    file:close(FD).
×
384

385
reopen_log(undefined, undefined) ->
386
    ok;
×
387
reopen_log(FN, FD) ->
388
    close_log(FD),
×
389
    open_log(FN).
×
390

391
reopen_log() ->
392
    lists:foreach(
×
393
      fun(Host) ->
394
              gen_server:cast(get_proc_name(Host), reopen_log)
×
395
      end, ejabberd_option:hosts()).
396

397
add_to_log(FileSize, Code, Request) ->
398
    gen_server:cast(get_proc_name(Request#request.host),
×
399
                    {add_to_log, FileSize, Code, Request}).
400

401
add_to_log(undefined, _FileSize, _Code, _Request) ->
402
    ok;
×
403
add_to_log(File, FileSize, Code, Request) ->
404
    {{Year, Month, Day}, {Hour, Minute, Second}} = calendar:local_time(),
×
405
    IP = ip_to_string(element(1, Request#request.ip)),
×
406
    Path = join(Request#request.path, "/"),
×
407
    Query = case stringify_query(Request#request.q) of
×
408
                <<"">> ->
409
                    "";
×
410
                String ->
411
                    [$? | String]
×
412
            end,
413
    UserAgent = find_header('User-Agent', Request#request.headers, "-"),
×
414
    Referer = find_header('Referer', Request#request.headers, "-"),
×
415
    %% Pseudo Combined Apache log format:
416
    %% 127.0.0.1 - - [28/Mar/2007:18:41:55 +0200] "GET / HTTP/1.1" 302 303 "-" "tsung"
417
    %% TODO some fields are hardcoded/missing:
418
    %%   The date/time integers should have always 2 digits. For example day "7" should be "07"
419
    %%   Month should be 3*letter, not integer 1..12
420
    %%   Missing time zone = (`+' | `-') 4*digit
421
    %%   Missing protocol version: HTTP/1.1
422
    %% For reference: http://httpd.apache.org/docs/2.2/logs.html
423
    io:format(File, "~ts - - [~p/~p/~p:~p:~p:~p] \"~ts /~ts~ts\" ~p ~p ~p ~p~n",
×
424
              [IP, Day, Month, Year, Hour, Minute, Second, Request#request.method, Path, Query, Code,
425
               FileSize, Referer, UserAgent]).
426

427
stringify_query(Q) ->
428
    stringify_query(Q, []).
×
429
stringify_query([], Res) ->
430
    join(lists:reverse(Res), "&");
×
431
stringify_query([{nokey, _B} | Q], Res) ->
432
    stringify_query(Q, Res);
×
433
stringify_query([{A, B} | Q], Res) ->
434
    stringify_query(Q, [join([A,B], "=") | Res]).
×
435

436
find_header(Header, Headers, Default) ->
437
    case lists:keysearch(Header, 1, Headers) of
×
438
      {value, {_, Value}} -> Value;
×
439
      false -> Default
×
440
    end.
441

442
%%----------------------------------------------------------------------
443
%% Utilities
444
%%----------------------------------------------------------------------
445

446
get_proc_name(Host) -> gen_mod:get_module_proc(Host, ?MODULE).
×
447

448
join([], _) ->
449
    <<"">>;
×
450
join([E], _) ->
451
    E;
×
452
join([H | T], Separator) ->
453
    [H2 | T2] = case is_binary(H) of true -> [binary_to_list(I)||I<-[H|T]]; false -> [H | T] end,
×
454
    Res=lists:foldl(fun(E, Acc) -> lists:concat([Acc, Separator, E]) end, H2, T2),
×
455
    case is_binary(H) of true -> list_to_binary(Res); false -> Res end.
×
456

457
content_type(Filename, DefaultContentType, ContentTypes) ->
UNCOV
458
    Extension = str:to_lower(filename:extension(Filename)),
6✔
UNCOV
459
    case lists:keysearch(Extension, 1, ContentTypes) of
6✔
UNCOV
460
      {value, {_, ContentType}} -> ContentType;
6✔
461
      false -> DefaultContentType
×
462
    end.
463

464
last_modified(FileInfo) ->
465
    Then = FileInfo#file_info.mtime,
×
466
    httpd_util:rfc1123_date(Then).
×
467

468
%% Convert IP address tuple to string representation. Accepts either
469
%% IPv4 or IPv6 address tuples.
470
ip_to_string(Address) when size(Address) == 4 ->
471
    join(tuple_to_list(Address), ".");
×
472
ip_to_string(Address) when size(Address) == 8 ->
473
    Parts = lists:map(fun (Int) -> io_lib:format("~.16B", [Int]) end, tuple_to_list(Address)),
×
474
    string:to_lower(lists:flatten(join(Parts, ":"))).
×
475

476
mod_opt_type(accesslog) ->
477
    econf:file(write);
×
478
mod_opt_type(content_types) ->
479
    econf:map(econf:binary(), econf:binary());
×
480
mod_opt_type(custom_headers) ->
481
    econf:map(econf:binary(), econf:binary());
×
482
mod_opt_type(default_content_type) ->
483
    econf:binary();
×
484
mod_opt_type(directory_indices) ->
485
    econf:list(econf:binary());
×
486
mod_opt_type(docroot) ->
487
    econf:directory(write);
×
488
mod_opt_type(must_authenticate_with) ->
489
    econf:list(
×
490
      econf:and_then(
491
        econf:and_then(
492
          econf:binary("^[^:]+:[^:]+$"),
493
          econf:binary_sep(":")),
494
        fun([K, V]) -> {K, V} end)).
×
495

496
-spec mod_options(binary()) -> [{must_authenticate_with, [{binary(), binary()}]} |
497
                                {atom(), any()}].
498
mod_options(_) ->
499
    [{accesslog, undefined},
×
500
     {content_types, []},
501
     {default_content_type, <<"application/octet-stream">>},
502
     {custom_headers, []},
503
     {directory_indices, []},
504
     {must_authenticate_with, []},
505
     %% Required option
506
     docroot].
507

508
mod_doc() ->
509
    #{desc =>
×
510
          ?T("This simple module serves files from the local disk over HTTP."),
511
      opts =>
512
          [{accesslog,
513
            #{value => ?T("Path"),
514
              desc =>
515
                  ?T("File to log accesses using an Apache-like format. "
516
                     "No log will be recorded if this option is not specified.")}},
517
           {docroot,
518
            #{value => ?T("Path"),
519
              desc =>
520
                  ?T("Directory to serve the files from. "
521
                     "This is a mandatory option.")}},
522
           {content_types,
523
            #{value => "{Extension: Type}",
524
              desc =>
525
                  ?T("Specify mappings of extension to content type. "
526
                     "There are several content types already defined. "
527
                     "With this option you can add new definitions "
528
                     "or modify existing ones. The default values are:"),
529
              example =>
530
                  ["content_types:"|
531
                     ["  " ++ binary_to_list(E) ++ ": " ++ binary_to_list(T)
×
532
                      || {E, T} <- ?DEFAULT_CONTENT_TYPES]]}},
×
533
           {default_content_type,
534
            #{value => ?T("Type"),
535
              desc =>
536
                  ?T("Specify the content type to use for unknown extensions. "
537
                     "The default value is 'application/octet-stream'.")}},
538
           {custom_headers,
539
            #{value => "{Name: Value}",
540
              desc =>
541
                  ?T("Indicate custom HTTP headers to be included in all responses. "
542
                     "There are no custom headers by default.")}},
543
           {directory_indices,
544
            #{value => "[Index, ...]",
545
              desc =>
546
                  ?T("Indicate one or more directory index files, "
547
                     "similarly to Apache's 'DirectoryIndex' variable. "
548
                     "When an HTTP request hits a directory instead of a "
549
                     "regular file, those directory indices are looked in order, "
550
                     "and the first one found is returned. "
551
                     "The default value is an empty list.")}},
552
           {must_authenticate_with,
553
            #{value => ?T("[{Username, Hostname}, ...]"),
554
              desc =>
555
                  ?T("List of accounts that are allowed to use this service. "
556
                     "Default value: '[]'.")}}],
557
      example =>
558
          [{?T("This example configuration will serve the files from the "
559
               "local directory '/var/www' in the address "
560
               "'http://example.org:5280/pub/content/'. In this example a new "
561
               "content type 'ogg' is defined, 'png' is redefined, and 'jpg' "
562
               "definition is deleted:"),
563
           ["listen:",
564
           "  -",
565
           "    port: 5280",
566
           "    module: ejabberd_http",
567
           "    request_handlers:",
568
           "      /pub/content: mod_http_fileserver",
569
           "",
570
           "modules:",
571
           "  mod_http_fileserver:",
572
           "    docroot: /var/www",
573
           "    accesslog: /var/log/ejabberd/access.log",
574
           "    directory_indices:",
575
           "      - index.html",
576
           "      - main.htm",
577
           "    custom_headers:",
578
           "      X-Powered-By: Erlang/OTP",
579
           "      X-Fry: \"It's a widely-believed fact!\"",
580
           "    content_types:",
581
           "      .ogg: audio/ogg",
582
           "      .png: image/png",
583
           "    default_content_type: text/html"]}]}.
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

© 2025 Coveralls, Inc