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

processone / ejabberd / 14

16 Jan 2026 03:45PM UTC coverage: 33.468% (-0.1%) from 33.564%
14

push

github

badlop
mod_http_fileserver: Reduce system menu name, sort them alphabetically

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

1 existing line in 1 file now uncovered.

15665 of 46806 relevant lines covered (33.47%)

1898.89 hits per line

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

6.06
/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-2026   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, build_list_content_types/1]).
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
        [{<<".avi">>, <<"video/avi">>},
78
         {<<".bmp">>, <<"image/bmp">>},
79
         {<<".bz2">>, <<"application/x-bzip2">>},
80
         {<<".css">>, <<"text/css">>},
81
         {<<".gif">>, <<"image/gif">>},
82
         {<<".gz">>, <<"application/x-gzip">>},
83
         {<<".html">>, <<"text/html">>},
84
         {<<".jar">>, <<"application/java-archive">>},
85
         {<<".jpeg">>, <<"image/jpeg">>},
86
         {<<".jpg">>, <<"image/jpeg">>},
87
         {<<".js">>, <<"text/javascript">>},
88
         {<<".m4a">>, <<"audio/mp4">>},
89
         {<<".mp3">>, <<"audio/mpeg">>},
90
         {<<".mp4">>, <<"video/mp4">>},
91
         {<<".mpeg">>, <<"video/mpeg">>},
92
         {<<".mpg">>, <<"video/mpeg">>},
93
         {<<".ogg">>, <<"application/ogg">>},
94
         {<<".pdf">>, <<"application/pdf">>},
95
         {<<".png">>, <<"image/png">>},
96
         {<<".rtf">>, <<"application/rtf">>},
97
         {<<".svg">>, <<"image/svg+xml">>},
98
         {<<".tiff">>, <<"image/tiff">>},
99
         {<<".txt">>, <<"text/plain">>},
100
         {<<".wav">>, <<"audio/wav">>},
101
         {<<".webp">>, <<"image/webp">>},
102
         {<<".xml">>, <<"application/xml">>},
103
         {<<".xpi">>, <<"application/x-xpinstall">>},
104
         {<<".xul">>, <<"application/vnd.mozilla.xul+xml">>},
105
         {<<".xz">>, <<"application/x-xz">>},
106
         {<<".zip">>, <<"application/zip">>}]).
107

108
%%====================================================================
109
%% gen_mod callbacks
110
%%====================================================================
111

112
start(Host, Opts) ->
NEW
113
    ejabberd_hooks:add(webadmin_menu_system_post, global, ?MODULE, web_menu_system, 1000-$f),
×
114
    gen_mod:start_child(?MODULE, Host, Opts).
×
115

116
stop(Host) ->
NEW
117
    ejabberd_hooks:delete(webadmin_menu_system_post, global, ?MODULE, web_menu_system, 1000-$f),
×
118
    gen_mod:stop_child(?MODULE, Host).
×
119

120
reload(Host, NewOpts, OldOpts) ->
121
    Proc = get_proc_name(Host),
×
122
    gen_server:cast(Proc, {reload, Host, NewOpts, OldOpts}).
×
123

124
depends(_Host, _Opts) ->
125
    [].
×
126

127
%%====================================================================
128
%% gen_server callbacks
129
%%====================================================================
130
%%--------------------------------------------------------------------
131
%% Function: init(Args) -> {ok, State} |
132
%%                         {ok, State, Timeout} |
133
%%                         ignore               |
134
%%                         {stop, Reason}
135
%% Description: Initiates the server
136
%%--------------------------------------------------------------------
137
init([Host|_]) ->
138
    Opts = gen_mod:get_module_opts(Host, ?MODULE),
×
139
    try initialize(Host, Opts) of
×
140
        State ->
141
            process_flag(trap_exit, true),
×
142
            {ok, State}
×
143
    catch
144
        throw:Reason ->
145
            {stop, Reason}
×
146
    end.
147

148
initialize(Host, Opts) ->
149
    DocRoot = mod_http_fileserver_opt:docroot(Opts),
×
150
    AccessLog = mod_http_fileserver_opt:accesslog(Opts),
×
151
    AccessLogFD = try_open_log(AccessLog, Host),
×
152
    DirectoryIndices = mod_http_fileserver_opt:directory_indices(Opts),
×
153
    CustomHeaders = mod_http_fileserver_opt:custom_headers(Opts),
×
154
    DefaultContentType = mod_http_fileserver_opt:default_content_type(Opts),
×
155
    UserAccess0 = mod_http_fileserver_opt:must_authenticate_with(Opts),
×
156
    UserAccess = case UserAccess0 of
×
157
                     [] -> none;
×
158
                     _ ->
159
                         maps:from_list(UserAccess0)
×
160
                 end,
161
    ContentTypes = build_list_content_types(
×
162
                     mod_http_fileserver_opt:content_types(Opts)),
163
    ?DEBUG("Known content types: ~ts",
×
164
           [str:join([[$*, K, " -> ", V] || {K, V} <- ContentTypes],
×
165
                     <<", ">>)]),
×
166
    #state{host = Host,
×
167
           accesslog = AccessLog,
168
           accesslogfd = AccessLogFD,
169
           docroot = DocRoot,
170
           directory_indices = DirectoryIndices,
171
           custom_headers = CustomHeaders,
172
           default_content_type = DefaultContentType,
173
           content_types = ContentTypes,
174
           user_access = UserAccess}.
175

176
build_list_content_types(AdminCTs) ->
177
    build_list_content_types(AdminCTs, ?DEFAULT_CONTENT_TYPES).
9✔
178

179
-spec build_list_content_types(AdminCTs::[{binary(), binary()|undefined}],
180
                               Default::[{binary(), binary()|undefined}]) ->
181
    [{string(), string()|undefined}].
182
%% where CT = {Extension::string(), Value}
183
%%       Value = string() | undefined
184
%% @doc Return a unified list without duplicates.
185
%% Elements of AdminCTs have more priority.
186
%% If a CT is declared as 'undefined', then it is not included in the result.
187
build_list_content_types(AdminCTsUnsorted, DefaultCTsUnsorted) ->
188
    AdminCTs = lists:ukeysort(1, AdminCTsUnsorted),
9✔
189
    DefaultCTs = lists:ukeysort(1, DefaultCTsUnsorted),
9✔
190
    CTsUnfiltered = lists:ukeymerge(1, AdminCTs,
9✔
191
                                    DefaultCTs),
192
    [{Extension, Value}
9✔
193
     || {Extension, Value} <- CTsUnfiltered,
9✔
194
        Value /= undefined].
270✔
195

196
try_open_log(undefined, _Host) ->
197
    undefined;
×
198
try_open_log(FN, _Host) ->
199
    FD = try open_log(FN) of
×
200
             FD1 -> FD1
×
201
         catch
202
             throw:{cannot_open_accesslog, FN, Reason} ->
203
                 ?ERROR_MSG("Cannot open access log file: ~p~nReason: ~p", [FN, Reason]),
×
204
                 undefined
×
205
         end,
206
    ejabberd_hooks:add(reopen_log_hook, ?MODULE, reopen_log, 50),
×
207
    FD.
×
208

209
%%--------------------------------------------------------------------
210
%% Function: handle_call(Request, From, State) -> {reply, Reply, State} |
211
%%                                      {reply, Reply, State, Timeout} |
212
%%                                      {noreply, State} |
213
%%                                      {noreply, State, Timeout} |
214
%%                                      {stop, Reason, Reply, State} |
215
%%                                      {stop, Reason, State}
216
%% Description: Handling call messages
217
%%--------------------------------------------------------------------
218
handle_call({serve, RawPath, LocalPath, Auth, RHeaders}, _From, State) ->
219
    IfModifiedSince = case find_header('If-Modified-Since', RHeaders, bad_date) of
×
220
                          bad_date ->
221
                              bad_date;
×
222
                          Val ->
223
                              httpd_util:convert_request_date(binary_to_list(Val))
×
224
                      end,
225
    DocRootBased = pick_docroot_based(RawPath, State#state.docroot),
×
226
    Reply = serve(LocalPath, Auth, DocRootBased, State#state.directory_indices,
×
227
                  State#state.custom_headers,
228
                  State#state.default_content_type, State#state.content_types,
229
                  State#state.user_access, IfModifiedSince),
230
    {reply, Reply, State};
×
231
handle_call(Request, From, State) ->
232
    ?WARNING_MSG("Unexpected call from ~p: ~p", [From, Request]),
×
233
    {noreply, State}.
×
234

235
pick_docroot_based(RawPath, DocRootList) when is_list(DocRootList) ->
236
    [{_, PathDir} | _] = lists:dropwhile(fun({Dr, _PathDir}) ->
×
237
                                     nomatch == binary:match(RawPath, Dr)
×
238
                             end,
239
                             DocRootList),
240
    PathDir;
×
241
pick_docroot_based(_RawPath, DocRoot) ->
242
    DocRoot.
×
243

244
%%--------------------------------------------------------------------
245
%% Function: handle_cast(Msg, State) -> {noreply, State} |
246
%%                                      {noreply, State, Timeout} |
247
%%                                      {stop, Reason, State}
248
%% Description: Handling cast messages
249
%%--------------------------------------------------------------------
250
handle_cast({add_to_log, FileSize, Code, Request}, State) ->
251
    add_to_log(State#state.accesslogfd, FileSize, Code, Request),
×
252
    {noreply, State};
×
253
handle_cast(reopen_log, State) ->
254
    FD2 = reopen_log(State#state.accesslog, State#state.accesslogfd),
×
255
    {noreply, State#state{accesslogfd = FD2}};
×
256
handle_cast({reload, Host, NewOpts, _OldOpts}, OldState) ->
257
    try initialize(Host, NewOpts) of
×
258
        NewState ->
259
            FD = reopen_log(NewState#state.accesslog, OldState#state.accesslogfd),
×
260
            {noreply, NewState#state{accesslogfd = FD}}
×
261
    catch throw:_ ->
262
            {noreply, OldState}
×
263
    end;
264
handle_cast(Msg, State) ->
265
    ?WARNING_MSG("Unexpected cast: ~p", [Msg]),
×
266
    {noreply, State}.
×
267

268
%%--------------------------------------------------------------------
269
%% Function: handle_info(Info, State) -> {noreply, State} |
270
%%                                       {noreply, State, Timeout} |
271
%%                                       {stop, Reason, State}
272
%% Description: Handling all non call/cast messages
273
%%--------------------------------------------------------------------
274
handle_info(Info, State) ->
275
    ?WARNING_MSG("Unexpected info: ~p", [Info]),
×
276
    {noreply, State}.
×
277

278
%%--------------------------------------------------------------------
279
%% Function: terminate(Reason, State) -> void()
280
%% Description: This function is called by a gen_server when it is about to
281
%% terminate. It should be the opposite of Module:init/1 and do any necessary
282
%% cleaning up. When it returns, the gen_server terminates with Reason.
283
%% The return value is ignored.
284
%%--------------------------------------------------------------------
285
terminate(_Reason, #state{host = Host} = State) ->
286
    close_log(State#state.accesslogfd),
×
287
    case gen_mod:is_loaded_elsewhere(Host, ?MODULE) of
×
288
        false ->
289
            ejabberd_hooks:delete(reopen_log_hook, ?MODULE, reopen_log, 50);
×
290
        true ->
291
            ok
×
292
    end.
293

294
%%--------------------------------------------------------------------
295
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
296
%% Description: Convert process state when code is changed
297
%%--------------------------------------------------------------------
298
code_change(_OldVsn, State, _Extra) ->
299
    {ok, State}.
×
300

301
%%====================================================================
302
%% request_handlers callbacks
303
%%====================================================================
304

305
-spec process(LocalPath::[binary()], #request{}) ->
306
    {HTTPCode::integer(), [{binary(), binary()}], Page::string()}.
307
%% @doc Handle an HTTP request.
308
%% LocalPath is the part of the requested URL path that is "local to the module".
309
%% Returns the page to be sent back to the client and/or HTTP status code.
310
process(LocalPath, #request{host = Host, auth = Auth, headers = RHeaders, raw_path = RawPath} = Request) ->
311
    ?DEBUG("Requested ~p", [LocalPath]),
×
312
    try
×
313
        VHost = ejabberd_router:host_of_route(Host),
×
314
        {FileSize, Code, Headers, Contents} =
×
315
            gen_server:call(get_proc_name(VHost),
316
                            {serve, RawPath, LocalPath, Auth, RHeaders}),
317
        add_to_log(FileSize, Code, Request#request{host = VHost}),
×
318
        {Code, Headers, Contents}
×
319
    catch _:{Why, _} when Why == noproc; Why == invalid_domain; Why == unregistered_route ->
320
            ?DEBUG("Received an HTTP request with Host: ~ts, "
×
321
                   "but couldn't find the related "
322
                   "ejabberd virtual host", [Host]),
×
323
            {FileSize1, Code1, Headers1, Contents1} = ?HTTP_ERR_HOST_UNKNOWN,
×
324
            add_to_log(FileSize1, Code1, Request#request{host = ejabberd_config:get_myname()}),
×
325
            {Code1, Headers1, Contents1}
×
326
    end.
327

328
serve(LocalPath, Auth, DocRoot, DirectoryIndices, CustomHeaders, DefaultContentType,
329
    ContentTypes, UserAccess, IfModifiedSince) ->
330
    CanProceed = case {UserAccess, Auth} of
×
331
                     {none, _} -> true;
×
332
                     {_, {User, Pass}} ->
333
                         case maps:find(User, UserAccess) of
×
334
                             {ok, Pass} -> true;
×
335
                             _ -> false
×
336
                         end;
337
                     _ ->
338
                         false
×
339
                 end,
340
    case CanProceed of
×
341
        false ->
342
            ?HTTP_ERR_REQUEST_AUTH;
×
343
        true ->
344
            FileName = filename:join(filename:split(DocRoot) ++ LocalPath),
×
345
            case file:read_file_info(FileName) of
×
346
                {error, enoent} ->
347
                    ?HTTP_ERR_FILE_NOT_FOUND;
×
348
                {error, enotdir} ->
349
                    ?HTTP_ERR_FILE_NOT_FOUND;
×
350
                {error, eacces} ->
351
                    ?HTTP_ERR_FORBIDDEN;
×
352
                {ok, #file_info{type = directory}} -> serve_index(FileName,
×
353
                                                                  DirectoryIndices,
354
                                                                  CustomHeaders,
355
                                                                  DefaultContentType,
356
                                                                  ContentTypes);
357
                {ok, #file_info{mtime = MTime} = FileInfo} ->
358
                    case calendar:local_time_to_universal_time_dst(MTime) of
×
359
                        [IfModifiedSince | _] ->
360
                            serve_not_modified(FileInfo, FileName,
×
361
                                               CustomHeaders);
362
                        _ ->
363
                            serve_file(FileInfo, FileName,
×
364
                                       CustomHeaders,
365
                                       DefaultContentType,
366
                                       ContentTypes)
367
                    end
368
            end
369
    end.
370

371
%% Troll through the directory indices attempting to find one which
372
%% works, if none can be found, return a 404.
373
serve_index(_FileName, [], _CH, _DefaultContentType, _ContentTypes) ->
374
    ?HTTP_ERR_FILE_NOT_FOUND;
×
375
serve_index(FileName, [Index | T], CH, DefaultContentType, ContentTypes) ->
376
    IndexFileName = filename:join([FileName] ++ [Index]),
×
377
    case file:read_file_info(IndexFileName) of
×
378
        {error, _Error}                    -> serve_index(FileName, T, CH, DefaultContentType, ContentTypes);
×
379
        {ok, #file_info{type = directory}} -> serve_index(FileName, T, CH, DefaultContentType, ContentTypes);
×
380
        {ok, FileInfo}                     -> serve_file(FileInfo, IndexFileName, CH, DefaultContentType, ContentTypes)
×
381
    end.
382

383
serve_not_modified(FileInfo, FileName, CustomHeaders) ->
384
    ?DEBUG("Delivering not modified: ~ts", [FileName]),
×
385
    {0, 304,
×
386
     ejabberd_http:apply_custom_headers(
387
         [{<<"Server">>, <<"ejabberd">>},
388
          {<<"Last-Modified">>, last_modified(FileInfo)}],
389
         CustomHeaders), <<>>}.
390

391
%% Assume the file exists if we got this far and attempt to read it in
392
%% and serve it up.
393
serve_file(FileInfo, FileName, CustomHeaders, DefaultContentType, ContentTypes) ->
394
    ?DEBUG("Delivering: ~ts", [FileName]),
×
395
    ContentType = content_type(FileName, DefaultContentType,
×
396
                               ContentTypes),
397
    {FileInfo#file_info.size, 200,
×
398
     ejabberd_http:apply_custom_headers(
399
         [{<<"Server">>, <<"ejabberd">>},
400
          {<<"Last-Modified">>, last_modified(FileInfo)},
401
          {<<"Content-Type">>, ContentType}],
402
         CustomHeaders),
403
     {file, FileName}}.
404

405
%%----------------------------------------------------------------------
406
%% Log file
407
%%----------------------------------------------------------------------
408

409
open_log(FN) ->
410
    case file:open(FN, [append]) of
×
411
        {ok, FD} ->
412
            FD;
×
413
        {error, Reason} ->
414
            throw({cannot_open_accesslog, FN, Reason})
×
415
    end.
416

417
close_log(FD) ->
418
    file:close(FD).
×
419

420
reopen_log(undefined, undefined) ->
421
    ok;
×
422
reopen_log(FN, FD) ->
423
    close_log(FD),
×
424
    open_log(FN).
×
425

426
reopen_log() ->
427
    lists:foreach(
×
428
      fun(Host) ->
429
              gen_server:cast(get_proc_name(Host), reopen_log)
×
430
      end, ejabberd_option:hosts()).
431

432
add_to_log(FileSize, Code, Request) ->
433
    gen_server:cast(get_proc_name(Request#request.host),
×
434
                    {add_to_log, FileSize, Code, Request}).
435

436
add_to_log(undefined, _FileSize, _Code, _Request) ->
437
    ok;
×
438
add_to_log(File, FileSize, Code, Request) ->
439
    {{Year, Month, Day}, {Hour, Minute, Second}} = calendar:local_time(),
×
440
    IP = ip_to_string(element(1, Request#request.ip)),
×
441
    Path = join(Request#request.path, "/"),
×
442
    Query = case stringify_query(Request#request.q) of
×
443
                <<"">> ->
444
                    "";
×
445
                String ->
446
                    [$? | String]
×
447
            end,
448
    UserAgent = find_header('User-Agent', Request#request.headers, "-"),
×
449
    Referer = find_header('Referer', Request#request.headers, "-"),
×
450
    %% Pseudo Combined Apache log format:
451
    %% 127.0.0.1 - - [28/Mar/2007:18:41:55 +0200] "GET / HTTP/1.1" 302 303 "-" "tsung"
452
    %% TODO some fields are hardcoded/missing:
453
    %%   The date/time integers should have always 2 digits. For example day "7" should be "07"
454
    %%   Month should be 3*letter, not integer 1..12
455
    %%   Missing time zone = (`+' | `-') 4*digit
456
    %%   Missing protocol version: HTTP/1.1
457
    %% For reference: http://httpd.apache.org/docs/2.2/logs.html
458
    io:format(File, "~ts - - [~p/~p/~p:~p:~p:~p] \"~ts /~ts~ts\" ~p ~p ~p ~p~n",
×
459
              [IP, Day, Month, Year, Hour, Minute, Second, Request#request.method, Path, Query, Code,
460
               FileSize, Referer, UserAgent]).
461

462
stringify_query(Q) ->
463
    stringify_query(Q, []).
×
464
stringify_query([], Res) ->
465
    join(lists:reverse(Res), "&");
×
466
stringify_query([{nokey, _B} | Q], Res) ->
467
    stringify_query(Q, Res);
×
468
stringify_query([{A, B} | Q], Res) ->
469
    stringify_query(Q, [join([A,B], "=") | Res]).
×
470

471
find_header(Header, Headers, Default) ->
472
    case lists:keysearch(Header, 1, Headers) of
×
473
      {value, {_, Value}} -> Value;
×
474
      false -> Default
×
475
    end.
476

477
%%----------------------------------------------------------------------
478
%% Utilities
479
%%----------------------------------------------------------------------
480

481
get_proc_name(Host) -> gen_mod:get_module_proc(Host, ?MODULE).
×
482

483
join([], _) ->
484
    <<"">>;
×
485
join([E], _) ->
486
    E;
×
487
join([H | T], Separator) ->
488
    [H2 | T2] = case is_binary(H) of true -> [binary_to_list(I)||I<-[H|T]]; false -> [H | T] end,
×
489
    Res=lists:foldl(fun(E, Acc) -> lists:concat([Acc, Separator, E]) end, H2, T2),
×
490
    case is_binary(H) of true -> list_to_binary(Res); false -> Res end.
×
491

492
content_type(Filename, DefaultContentType, ContentTypes) ->
493
    Extension = str:to_lower(filename:extension(Filename)),
9✔
494
    case lists:keysearch(Extension, 1, ContentTypes) of
9✔
495
      {value, {_, ContentType}} -> ContentType;
9✔
496
      false -> DefaultContentType
×
497
    end.
498

499
last_modified(FileInfo) ->
500
    Then = FileInfo#file_info.mtime,
×
501
    httpd_util:rfc1123_date(Then).
×
502

503
%% Convert IP address tuple to string representation. Accepts either
504
%% IPv4 or IPv6 address tuples.
505
ip_to_string(Address) when size(Address) == 4 ->
506
    join(tuple_to_list(Address), ".");
×
507
ip_to_string(Address) when size(Address) == 8 ->
508
    Parts = lists:map(fun (Int) -> io_lib:format("~.16B", [Int]) end, tuple_to_list(Address)),
×
509
    string:to_lower(lists:flatten(join(Parts, ":"))).
×
510

511
%%----------------------------------------------------------------------
512
%% WebAdmin
513
%%----------------------------------------------------------------------
514

515
web_menu_system(Result, _Request, _Level) ->
NEW
516
    Els = ejabberd_web_admin:make_menu_system(?MODULE, "📁", "Fileserver: {URLPATH}", ""),
×
517
    Els ++ Result.
×
518

519
%%----------------------------------------------------------------------
520

521
mod_opt_type(accesslog) ->
522
    econf:file(write);
×
523
mod_opt_type(content_types) ->
524
    econf:map(econf:binary(), econf:binary());
×
525
mod_opt_type(custom_headers) ->
526
    econf:map(econf:binary(), econf:binary());
×
527
mod_opt_type(default_content_type) ->
528
    econf:binary();
×
529
mod_opt_type(directory_indices) ->
530
    econf:list(econf:binary());
×
531
mod_opt_type(docroot) ->
532
    econf:either(
×
533
      econf:directory(write),
534
      econf:map(econf:binary(), econf:binary())
535
    );
536
mod_opt_type(must_authenticate_with) ->
537
    econf:list(
×
538
      econf:and_then(
539
        econf:and_then(
540
          econf:binary("^[^:]+:[^:]+$"),
541
          econf:binary_sep(":")),
542
        fun([K, V]) -> {K, V} end)).
×
543

544
-spec mod_options(binary()) -> [{must_authenticate_with, [{binary(), binary()}]} |
545
                                {atom(), any()}].
546
mod_options(_) ->
547
    [{accesslog, undefined},
×
548
     {content_types, []},
549
     {default_content_type, <<"application/octet-stream">>},
550
     {custom_headers, []},
551
     {directory_indices, []},
552
     {must_authenticate_with, []},
553
     %% Required option
554
     docroot].
555

556
mod_doc() ->
557
    #{desc =>
×
558
          ?T("This simple module serves files from the local disk over HTTP."),
559
      note => "improved 'docroot' in 26.xx",
560
      opts =>
561
          [{accesslog,
562
            #{value => ?T("Path"),
563
              desc =>
564
                  ?T("File to log accesses using an Apache-like format. "
565
                     "No log will be recorded if this option is not specified.")}},
566
           {docroot,
567
            #{value => ?T("PathDir | {PathURL, PathDir}"),
568
              note => "improved in 26.xx",
569
              desc =>
570
                  ?T("Directory to serve the files from, "
571
                     "or a map with several URL path "
572
                     "(as specified in _`listen-options.md#request_handlers|request_handlers`_) "
573
                     "and their corresponding directory. "
574
                     "This is a mandatory option."),
575
              example =>
576
                   ["listen:",
577
                   "  -",
578
                   "    port: 5280",
579
                   "    module: ejabberd_http",
580
                   "    request_handlers:",
581
                   "      /pub/content: mod_http_fileserver",
582
                   "      /share: mod_http_fileserver",
583
                   "      /: mod_http_fileserver",
584
                   "modules:",
585
                   "  mod_http_fileserver:",
586
                   "    docroot:",
587
                   "      /pub/content: /var/service/www",
588
                   "      /share: /usr/share/javascript",
589
                   "      /: /var/www"]}},
590
           {content_types,
591
            #{value => "{Extension: Type}",
592
              desc =>
593
                  ?T("Specify mappings of extension to content type. "
594
                     "There are several content types already defined. "
595
                     "With this option you can add new definitions "
596
                     "or modify existing ones. The default values are:"),
597
              example =>
598
                  ["content_types:"|
599
                     ["  " ++ binary_to_list(E) ++ ": " ++ binary_to_list(T)
×
600
                      || {E, T} <- ?DEFAULT_CONTENT_TYPES]]}},
×
601
           {default_content_type,
602
            #{value => ?T("Type"),
603
              desc =>
604
                  ?T("Specify the content type to use for unknown extensions. "
605
                     "The default value is 'application/octet-stream'.")}},
606
           {custom_headers,
607
            #{value => "{Name: Value}",
608
              desc =>
609
                  ?T("Indicate custom HTTP headers to be included in all responses. "
610
                     "There are no custom headers by default.")}},
611
           {directory_indices,
612
            #{value => "[Index, ...]",
613
              desc =>
614
                  ?T("Indicate one or more directory index files, "
615
                     "similarly to Apache's 'DirectoryIndex' variable. "
616
                     "When an HTTP request hits a directory instead of a "
617
                     "regular file, those directory indices are looked in order, "
618
                     "and the first one found is returned. "
619
                     "The default value is an empty list.")}},
620
           {must_authenticate_with,
621
            #{value => ?T("[{Username, Hostname}, ...]"),
622
              desc =>
623
                  ?T("List of accounts that are allowed to use this service. "
624
                     "Default value: '[]'.")}}],
625
      example =>
626
          [{?T("This example configuration will serve the files from the "
627
               "local directory '/var/www' in the address "
628
               "'http://example.org:5280/pub/content/'. In this example a new "
629
               "content type 'ogg' is defined, 'png' is redefined, and 'jpg' "
630
               "definition is deleted:"),
631
           ["listen:",
632
           "  -",
633
           "    port: 5280",
634
           "    module: ejabberd_http",
635
           "    request_handlers:",
636
           "      /pub/content: mod_http_fileserver",
637
           "",
638
           "modules:",
639
           "  mod_http_fileserver:",
640
           "    docroot: /var/www",
641
           "    accesslog: /var/log/ejabberd/access.log",
642
           "    directory_indices:",
643
           "      - index.html",
644
           "      - main.htm",
645
           "    custom_headers:",
646
           "      X-Powered-By: Erlang/OTP",
647
           "      X-Fry: \"It's a widely-believed fact!\"",
648
           "    content_types:",
649
           "      .ogg: audio/ogg",
650
           "      .png: image/png",
651
           "    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

© 2026 Coveralls, Inc