• 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

1.89
/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
-export([web_menu_system/3]).
49

50
-include_lib("xmpp/include/xmpp.hrl").
51
-include("logger.hrl").
52
-include("ejabberd_http.hrl").
53
-include("ejabberd_web_admin.hrl").
54
-include_lib("kernel/include/file.hrl").
55
-include("translate.hrl").
56

57
-record(state,
58
        {host, docroot, accesslog, accesslogfd,
59
         directory_indices, custom_headers, default_content_type,
60
         content_types = [], user_access = none}).
61

62
%% Response is {DataSize, Code, [{HeaderKey, HeaderValue}], Data}
63
-define(HTTP_ERR_FILE_NOT_FOUND,
64
        {-1, 404, [], <<"Not found">>}).
65

66
-define(REQUEST_AUTH_HEADERS,
67
        [{<<"WWW-Authenticate">>, <<"Basic realm=\"ejabberd\"">>}]).
68

69
-define(HTTP_ERR_FORBIDDEN,
70
        {-1, 403, [], <<"Forbidden">>}).
71
-define(HTTP_ERR_REQUEST_AUTH,
72
        {-1, 401, ?REQUEST_AUTH_HEADERS, <<"Unauthorized">>}).
73
-define(HTTP_ERR_HOST_UNKNOWN,
74
        {-1, 410, [], <<"Host unknown">>}).
75

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

91
%%====================================================================
92
%% gen_mod callbacks
93
%%====================================================================
94

95
start(Host, Opts) ->
96
    ejabberd_hooks:add(webadmin_menu_system_post, global, ?MODULE, web_menu_system, 896),
×
97
    gen_mod:start_child(?MODULE, Host, Opts).
×
98

99
stop(Host) ->
100
    ejabberd_hooks:delete(webadmin_menu_system_post, global, ?MODULE, web_menu_system, 896),
×
101
    gen_mod:stop_child(?MODULE, Host).
×
102

103
reload(Host, NewOpts, OldOpts) ->
104
    Proc = get_proc_name(Host),
×
105
    gen_server:cast(Proc, {reload, Host, NewOpts, OldOpts}).
×
106

107
depends(_Host, _Opts) ->
108
    [].
×
109

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

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

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

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

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

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

239
%%--------------------------------------------------------------------
240
%% Function: handle_info(Info, State) -> {noreply, State} |
241
%%                                       {noreply, State, Timeout} |
242
%%                                       {stop, Reason, State}
243
%% Description: Handling all non call/cast messages
244
%%--------------------------------------------------------------------
245
handle_info(Info, State) ->
246
    ?WARNING_MSG("Unexpected info: ~p", [Info]),
×
247
    {noreply, State}.
×
248

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

265
%%--------------------------------------------------------------------
266
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
267
%% Description: Convert process state when code is changed
268
%%--------------------------------------------------------------------
269
code_change(_OldVsn, State, _Extra) ->
270
    {ok, State}.
×
271

272
%%====================================================================
273
%% request_handlers callbacks
274
%%====================================================================
275

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

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

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

354
serve_not_modified(FileInfo, FileName, CustomHeaders) ->
355
    ?DEBUG("Delivering not modified: ~ts", [FileName]),
×
356
    {0, 304,
×
357
     ejabberd_http:apply_custom_headers(
358
         [{<<"Server">>, <<"ejabberd">>},
359
          {<<"Last-Modified">>, last_modified(FileInfo)}],
360
         CustomHeaders), <<>>}.
361

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

376
%%----------------------------------------------------------------------
377
%% Log file
378
%%----------------------------------------------------------------------
379

380
open_log(FN) ->
381
    case file:open(FN, [append]) of
×
382
        {ok, FD} ->
383
            FD;
×
384
        {error, Reason} ->
385
            throw({cannot_open_accesslog, FN, Reason})
×
386
    end.
387

388
close_log(FD) ->
389
    file:close(FD).
×
390

391
reopen_log(undefined, undefined) ->
392
    ok;
×
393
reopen_log(FN, FD) ->
394
    close_log(FD),
×
395
    open_log(FN).
×
396

397
reopen_log() ->
398
    lists:foreach(
×
399
      fun(Host) ->
400
              gen_server:cast(get_proc_name(Host), reopen_log)
×
401
      end, ejabberd_option:hosts()).
402

403
add_to_log(FileSize, Code, Request) ->
404
    gen_server:cast(get_proc_name(Request#request.host),
×
405
                    {add_to_log, FileSize, Code, Request}).
406

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

433
stringify_query(Q) ->
434
    stringify_query(Q, []).
×
435
stringify_query([], Res) ->
436
    join(lists:reverse(Res), "&");
×
437
stringify_query([{nokey, _B} | Q], Res) ->
438
    stringify_query(Q, Res);
×
439
stringify_query([{A, B} | Q], Res) ->
440
    stringify_query(Q, [join([A,B], "=") | Res]).
×
441

442
find_header(Header, Headers, Default) ->
443
    case lists:keysearch(Header, 1, Headers) of
×
444
      {value, {_, Value}} -> Value;
×
445
      false -> Default
×
446
    end.
447

448
%%----------------------------------------------------------------------
449
%% Utilities
450
%%----------------------------------------------------------------------
451

452
get_proc_name(Host) -> gen_mod:get_module_proc(Host, ?MODULE).
×
453

454
join([], _) ->
455
    <<"">>;
×
456
join([E], _) ->
457
    E;
×
458
join([H | T], Separator) ->
459
    [H2 | T2] = case is_binary(H) of true -> [binary_to_list(I)||I<-[H|T]]; false -> [H | T] end,
×
460
    Res=lists:foldl(fun(E, Acc) -> lists:concat([Acc, Separator, E]) end, H2, T2),
×
461
    case is_binary(H) of true -> list_to_binary(Res); false -> Res end.
×
462

463
content_type(Filename, DefaultContentType, ContentTypes) ->
464
    Extension = str:to_lower(filename:extension(Filename)),
3✔
465
    case lists:keysearch(Extension, 1, ContentTypes) of
3✔
466
      {value, {_, ContentType}} -> ContentType;
3✔
467
      false -> DefaultContentType
×
468
    end.
469

470
last_modified(FileInfo) ->
471
    Then = FileInfo#file_info.mtime,
×
472
    httpd_util:rfc1123_date(Then).
×
473

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

482
%%----------------------------------------------------------------------
483
%% WebAdmin
484
%%----------------------------------------------------------------------
485

486
web_menu_system(Result, _Request, _Level) ->
487
    Els = ejabberd_web_admin:make_menu_system(?MODULE, "📁", "HTTP Fileserver", ""),
×
488
    Els ++ Result.
×
489

490
%%----------------------------------------------------------------------
491

492
mod_opt_type(accesslog) ->
493
    econf:file(write);
×
494
mod_opt_type(content_types) ->
495
    econf:map(econf:binary(), econf:binary());
×
496
mod_opt_type(custom_headers) ->
497
    econf:map(econf:binary(), econf:binary());
×
498
mod_opt_type(default_content_type) ->
499
    econf:binary();
×
500
mod_opt_type(directory_indices) ->
501
    econf:list(econf:binary());
×
502
mod_opt_type(docroot) ->
503
    econf:directory(write);
×
504
mod_opt_type(must_authenticate_with) ->
505
    econf:list(
×
506
      econf:and_then(
507
        econf:and_then(
508
          econf:binary("^[^:]+:[^:]+$"),
509
          econf:binary_sep(":")),
510
        fun([K, V]) -> {K, V} end)).
×
511

512
-spec mod_options(binary()) -> [{must_authenticate_with, [{binary(), binary()}]} |
513
                                {atom(), any()}].
514
mod_options(_) ->
515
    [{accesslog, undefined},
×
516
     {content_types, []},
517
     {default_content_type, <<"application/octet-stream">>},
518
     {custom_headers, []},
519
     {directory_indices, []},
520
     {must_authenticate_with, []},
521
     %% Required option
522
     docroot].
523

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