1%%%----------------------------------------------------------------------
2%%% File    : yaws_config.erl
3%%% Author  : Claes Wikstrom <klacke@bluetail.com>
4%%% Purpose :
5%%% Created : 16 Jan 2002 by Claes Wikstrom <klacke@bluetail.com>
6%%%----------------------------------------------------------------------
7
8-module(yaws_config).
9-author('klacke@bluetail.com').
10
11
12-include("../include/yaws.hrl").
13-include("../include/yaws_api.hrl").
14-include("yaws_debug.hrl").
15
16-include_lib("kernel/include/file.hrl").
17
18-define(NEXTLINE, io_get_line(FD, '', [])).
19
20-export([load/1,
21         make_default_gconf/2, make_default_sconf/0, make_default_sconf/3,
22         add_sconf/1,
23         add_yaws_auth/1,
24         add_yaws_soap_srv/1, add_yaws_soap_srv/2,
25         load_mime_types_module/2,
26         compile_and_load_src_dir/1,
27         search_sconf/3, search_group/3,
28         update_sconf/4, delete_sconf/3,
29         eq_sconfs/2, soft_setconf/4, hard_setconf/2,
30         can_hard_gc/2, can_soft_setconf/4,
31         can_soft_gc/2, verify_upgrade_args/2, toks/2]).
32
33%% where to look for yaws.conf
34paths() ->
35    case application:get_env(yaws, config) of
36        undefined ->
37            case yaws:getuid() of
38                {ok, "0"} ->    %% root
39                    [yaws_generated:etcdir() ++ "/yaws/yaws.conf"];
40                _ -> %% developer
41                    [filename:join([yaws:home(), "yaws.conf"]),
42                     "./yaws.conf",
43                     yaws_generated:etcdir() ++ "/yaws/yaws.conf"]
44            end;
45        {ok, File} ->
46            [File]
47    end.
48
49
50
51%% load the config
52
53load(E = #env{conf = false}) ->
54    case yaws:first(fun(F) -> yaws:exists(F) end, paths()) of
55        false ->
56            {error, "Can't find any config file "};
57        {ok, _, File} ->
58            load(E#env{conf = {file, File}})
59    end;
60load(E) ->
61    {file, File} = E#env.conf,
62    error_logger:info_msg("Yaws: Using config file ~s~n", [File]),
63    case file:open(File, [read, {encoding, E#env.encoding}]) of
64        {ok, FD} ->
65            GC = make_default_gconf(E#env.debug, E#env.id),
66            GC1 = if E#env.traceoutput == undefined ->
67                          GC;
68                     true ->
69                          ?gc_set_tty_trace(GC, E#env.traceoutput)
70                  end,
71            GC2 =  ?gc_set_debug(GC1, E#env.debug),
72            GC3 = GC2#gconf{trace = E#env.trace},
73            R = fload(FD, GC3),
74            ?Debug("FLOAD(~s): ~p", [File, R]),
75            case R of
76                {ok, GC4, Cs} ->
77                    yaws:mkdir(yaws:tmpdir()),
78                    Cs1 = add_yaws_auth(Cs),
79                    add_yaws_soap_srv(GC4),
80                    validate_cs(GC4, Cs1);
81                Err ->
82                    Err
83            end;
84        Err ->
85            {error, ?F("Can't open config file ~s: ~p", [File, Err])}
86    end.
87
88
89add_yaws_soap_srv(GC) when GC#gconf.enable_soap == true ->
90    add_yaws_soap_srv(GC, true);
91add_yaws_soap_srv(_GC) ->
92    [].
93add_yaws_soap_srv(GC, false) when GC#gconf.enable_soap == true ->
94    [{yaws_soap_srv, {yaws_soap_srv, start_link, [GC#gconf.soap_srv_mods]},
95      permanent, 5000, worker, [yaws_soap_srv]}];
96add_yaws_soap_srv(GC, true) when GC#gconf.enable_soap == true ->
97    Spec = add_yaws_soap_srv(GC, false),
98    case whereis(yaws_soap_srv) of
99        undefined ->
100            spawn(fun() -> supervisor:start_child(yaws_sup, hd(Spec)) end);
101        _ ->
102            ok
103    end,
104    Spec;
105add_yaws_soap_srv(_GC, _Start) ->
106    [].
107
108
109add_yaws_auth(#sconf{}=SC) ->
110    SC#sconf{authdirs = setup_auth(SC)};
111add_yaws_auth(SCs) ->
112    [SC#sconf{authdirs = setup_auth(SC)} || SC <- SCs].
113
114
115%% We search and setup www authenticate for each directory
116%% specified as an auth directory or containing a .yaws_auth file.
117%% These are merged with server conf.
118setup_auth(#sconf{docroot = Docroot, xtra_docroots = XtraDocroots,
119                  authdirs = Authdirs}=SC) ->
120    [begin
121         Authdirs1 = load_yaws_auth_from_docroot(D, ?sc_auth_skip_docroot(SC)),
122         Authdirs2 = load_yaws_auth_from_authdirs(Authdirs, D, []),
123         Authdirs3 = [A || A <- Authdirs1,
124                           not lists:keymember(A#auth.dir,#auth.dir,Authdirs2)],
125         Authdirs4 = ensure_auth_headers(Authdirs3 ++ Authdirs2),
126         start_pam(Authdirs4),
127         {D, Authdirs4}
128     end || D <- [Docroot|XtraDocroots] ].
129
130
131load_yaws_auth_from_docroot(_, true) ->
132    [];
133load_yaws_auth_from_docroot(undefined, _) ->
134    [];
135load_yaws_auth_from_docroot(Docroot, _) ->
136    Fun = fun (Path, Acc) ->
137                  %% Strip Docroot and then filename
138                  SP  = string:sub_string(Path, length(Docroot)+1),
139                  Dir = filename:dirname(SP),
140                  A = #auth{docroot=Docroot, dir=Dir},
141                  case catch load_yaws_auth_file(Path, A) of
142                      {ok, L} -> L ++ Acc;
143                      _Other  -> Acc
144                  end
145          end,
146    filelib:fold_files(Docroot, "^.yaws_auth$", true, Fun, []).
147
148
149load_yaws_auth_from_authdirs([], _, Acc) ->
150    lists:reverse(Acc);
151load_yaws_auth_from_authdirs([Auth = #auth{dir=Dir}| Rest], Docroot, Acc) ->
152    if
153        Auth#auth.docroot /= [] andalso Auth#auth.docroot /= Docroot ->
154            load_yaws_auth_from_authdirs(Rest, Docroot, Acc);
155        Auth#auth.docroot == [] ->
156            Auth1 = Auth#auth{dir=filename:nativename(Dir)},
157            F = fun(A) ->
158                        (A#auth.docroot == Docroot andalso
159                         A#auth.dir == Auth1#auth.dir)
160                end,
161            case lists:any(F, Acc) of
162                true ->
163                    load_yaws_auth_from_authdirs(Rest, Docroot, Acc);
164                false ->
165                    Acc1 = Acc ++ load_yaws_auth_from_authdir(Docroot, Auth1),
166                    load_yaws_auth_from_authdirs(Rest, Docroot, Acc1)
167            end;
168        true -> %% #auth.docroot == Docroot
169            Auth1 = Auth#auth{docroot=Docroot, dir=filename:nativename(Dir)},
170            F = fun(A) ->
171                        not (A#auth.docroot == [] andalso
172                             A#auth.dir == Auth1#auth.dir)
173                end,
174            Acc1 = lists:filter(F, Acc),
175            Acc2 = Acc1 ++ load_yaws_auth_from_authdir(Docroot, Auth1),
176            load_yaws_auth_from_authdirs(Rest, Docroot, Acc2)
177    end;
178load_yaws_auth_from_authdirs([{Docroot, Auths}|_], Docroot, Acc) ->
179    load_yaws_auth_from_authdirs(Auths, Docroot, Acc);
180load_yaws_auth_from_authdirs([_| Rest], Docroot, Acc) ->
181    load_yaws_auth_from_authdirs(Rest, Docroot, Acc).
182
183
184load_yaws_auth_from_authdir(Docroot, Auth) ->
185    Dir = case Auth#auth.dir of
186              "/" ++ R -> R;
187              _        -> Auth#auth.dir
188          end,
189    Path = filename:join([Docroot, Dir, ".yaws_auth"]),
190    case catch load_yaws_auth_file(Path, Auth) of
191        {ok, Auths} -> Auths;
192        _           -> [Auth]
193    end.
194
195
196load_yaws_auth_file(Path, Auth) ->
197    case file:consult(Path) of
198        {ok, TermList} ->
199            error_logger:info_msg("Reading .yaws_auth ~s~n", [Path]),
200            parse_yaws_auth_file(TermList, Auth);
201        {error, enoent} ->
202            {error, enoent};
203        Error ->
204            error_logger:format("Bad .yaws_auth file ~s ~p~n", [Path, Error]),
205            Error
206    end.
207
208
209ensure_auth_headers(Authdirs) ->
210    [add_auth_headers(Auth) || Auth <- Authdirs].
211
212add_auth_headers(Auth = #auth{headers = []}) ->
213    %% Headers needs to be set
214    Realm   = Auth#auth.realm,
215    Headers = yaws:make_www_authenticate_header({realm, Realm}),
216    Auth#auth{headers = Headers};
217add_auth_headers(Auth) ->
218    Auth.
219
220
221start_pam([]) ->
222    ok;
223start_pam([#auth{pam = false}|T]) ->
224    start_pam(T);
225start_pam([A|T]) ->
226    case whereis(yaws_pam) of
227        undefined ->    % pam not started
228            Spec = {yaws_pam, {yaws_pam, start_link,
229                               [yaws:to_list(A#auth.pam),undefined,undefined]},
230                    permanent, 5000, worker, [yaws_pam]},
231            spawn(fun() -> supervisor:start_child(yaws_sup, Spec) end);
232        _ ->
233            start_pam(T)
234    end.
235
236
237parse_yaws_auth_file([], Auth=#auth{files=[]}) ->
238    {ok, [Auth]};
239parse_yaws_auth_file([], Auth=#auth{dir=Dir, files=Files}) ->
240    {ok, [Auth#auth{dir=filename:join(Dir, F), files=[F]} || F <- Files]};
241
242parse_yaws_auth_file([{realm, Realm}|T], Auth0) ->
243    parse_yaws_auth_file(T, Auth0#auth{realm = Realm});
244
245parse_yaws_auth_file([{pam, Pam}|T], Auth0)
246  when is_atom(Pam) ->
247    parse_yaws_auth_file(T, Auth0#auth{pam = Pam});
248
249parse_yaws_auth_file([{authmod, Authmod0}|T], Auth0)
250  when is_atom(Authmod0)->
251    Headers = try
252                  Authmod0:get_header() ++ Auth0#auth.headers
253              catch
254                  _:_ ->
255                      error_logger:format("Failed to ~p:get_header() \n",
256                                          [Authmod0]),
257                      Auth0#auth.headers
258              end,
259    parse_yaws_auth_file(T, Auth0#auth{mod = Authmod0, headers = Headers});
260
261parse_yaws_auth_file([{file, File}|T], Auth0) ->
262    Files = case File of
263                "/" ++ F -> [F|Auth0#auth.files];
264                _        -> [File|Auth0#auth.files]
265            end,
266    parse_yaws_auth_file(T, Auth0#auth{files=Files});
267
268parse_yaws_auth_file([{User, Password}|T], Auth0)
269  when is_list(User), is_list(Password) ->
270    Salt = crypto:strong_rand_bytes(32),
271    Hash = crypto:hash(sha256, [Salt, Password]),
272    Users = case lists:member({User, sha256, Salt, Hash}, Auth0#auth.users) of
273                true  -> Auth0#auth.users;
274                false -> [{User, sha256, Salt, Hash} | Auth0#auth.users]
275            end,
276    parse_yaws_auth_file(T, Auth0#auth{users = Users});
277
278parse_yaws_auth_file([{User, Algo, B64Hash}|T], Auth0)
279  when is_list(User), is_list(Algo), is_list(B64Hash) ->
280    case parse_auth_user(User, Algo, "", B64Hash) of
281        {ok, Res} ->
282            Users = case lists:member(Res, Auth0#auth.users) of
283                        true  -> Auth0#auth.users;
284                        false -> [Res | Auth0#auth.users]
285                    end,
286            parse_yaws_auth_file(T, Auth0#auth{users = Users});
287        {error, Reason} ->
288            error_logger:format("Failed to parse user line ~p: ~p~n",
289                                [{User, Algo, B64Hash}, Reason]),
290            parse_yaws_auth_file(T, Auth0)
291    end;
292
293parse_yaws_auth_file([{User, Algo, B64Salt, B64Hash}|T], Auth0)
294  when is_list(User), is_list(Algo), is_list(B64Salt), is_list(B64Hash) ->
295    case parse_auth_user(User, Algo, B64Salt, B64Hash) of
296        {ok, Res} ->
297            Users = case lists:member(Res, Auth0#auth.users) of
298                        true  -> Auth0#auth.users;
299                        false -> [Res | Auth0#auth.users]
300                    end,
301            parse_yaws_auth_file(T, Auth0#auth{users = Users});
302        {error, Reason} ->
303            error_logger:format("Failed to parse user line ~p: ~p~n",
304                                [{User, Algo, B64Hash, B64Hash}, Reason]),
305            parse_yaws_auth_file(T, Auth0)
306    end;
307
308parse_yaws_auth_file([{allow, all}|T], Auth0) ->
309    Auth1 = case Auth0#auth.acl of
310                none    -> Auth0#auth{acl={all, [], deny_allow}};
311                {_,D,O} -> Auth0#auth{acl={all, D, O}}
312            end,
313    parse_yaws_auth_file(T, Auth1);
314
315parse_yaws_auth_file([{allow, IPs}|T], Auth0) when is_list(IPs) ->
316    Auth1 = case Auth0#auth.acl of
317                none ->
318                    AllowIPs = parse_auth_ips(IPs, []),
319                    Auth0#auth{acl={AllowIPs, [], deny_allow}};
320                {all, _, _} ->
321                    Auth0;
322                {AllowIPs, DenyIPs, Order} ->
323                    AllowIPs2 = parse_auth_ips(IPs, []) ++ AllowIPs,
324                    Auth0#auth{acl={AllowIPs2, DenyIPs, Order}}
325            end,
326    parse_yaws_auth_file(T, Auth1);
327
328parse_yaws_auth_file([{deny, all}|T], Auth0) ->
329    Auth1 = case Auth0#auth.acl of
330                none    -> Auth0#auth{acl={[], all, deny_allow}};
331                {A,_,O} -> Auth0#auth{acl={A, all, O}}
332            end,
333    parse_yaws_auth_file(T, Auth1);
334
335parse_yaws_auth_file([{deny, IPs}|T], Auth0) when is_list(IPs) ->
336    Auth1 = case Auth0#auth.acl of
337                none ->
338                    DenyIPs = parse_auth_ips(IPs, []),
339                    Auth0#auth{acl={[], DenyIPs, deny_allow}};
340                {_, all, _} ->
341                    Auth0;
342                {AllowIPs, DenyIPs, Order} ->
343                    DenyIPs2 = parse_auth_ips(IPs, []) ++ DenyIPs,
344                    Auth0#auth{acl={AllowIPs, DenyIPs2, Order}}
345            end,
346    parse_yaws_auth_file(T, Auth1);
347
348parse_yaws_auth_file([{order, O}|T], Auth0)
349  when O == allow_deny; O == deny_allow ->
350    Auth1 = case Auth0#auth.acl of
351                none    -> Auth0#auth{acl={[], [], O}};
352                {A,D,_} -> Auth0#auth{acl={A, D, O}}
353            end,
354    parse_yaws_auth_file(T, Auth1).
355
356
357
358%% Create mime_types.erl, compile it and load it. If everything is ok,
359%% reload groups.
360%%
361%% If an error occured, the previously-loaded version (the first time, it's the
362%% static version) is kept.
363load_mime_types_module(GC, Groups) ->
364    GInfo  = GC#gconf.mime_types_info,
365    SInfos = [{{SC#sconf.servername, SC#sconf.port}, SC#sconf.mime_types_info}
366              || SC <- lists:flatten(Groups),
367                 SC#sconf.mime_types_info /= undefined],
368
369    case {is_dir(yaws:id_dir(GC#gconf.id)), is_dir(yaws:tmpdir("/tmp"))} of
370        {true, _} ->
371            File = filename:join(yaws:id_dir(GC#gconf.id), "mime_types.erl"),
372            load_mime_types_module(File, GInfo, SInfos);
373        {_, true} ->
374            File = filename:join(yaws:tmpdir("/tmp"), "mime_types.erl"),
375            load_mime_types_module(File, GInfo, SInfos);
376        _ ->
377            error_logger:format("Cannot write module mime_types.erl~n"
378                                "Keep the previously-loaded version~n", [])
379    end,
380    lists:map(fun(Gp) ->
381                      [begin
382                           F   = fun(X) when is_atom(X) -> X;
383                                    (X) -> element(1, mime_types:t(SC, X))
384                                 end,
385                           TAS = SC#sconf.tilde_allowed_scripts,
386                           AS  = SC#sconf.allowed_scripts,
387                           SC#sconf{tilde_allowed_scripts=lists:map(F, TAS),
388                                    allowed_scripts=lists:map(F, AS)}
389                       end || SC <- Gp]
390              end, Groups).
391
392load_mime_types_module(_, undefined, []) ->
393    ok;
394load_mime_types_module(File, undefined, SInfos) ->
395    load_mime_types_module(File, #mime_types_info{}, SInfos);
396load_mime_types_module(File, GInfo, SInfos) ->
397    case mime_type_c:generate(File, GInfo, SInfos) of
398        ok ->
399            case compile:file(File, [binary]) of
400                {ok, ModName, Binary} ->
401                    case code:load_binary(ModName, [], Binary) of
402                        {module, ModName} ->
403                            ok;
404                        {error, What} ->
405                            error_logger:format(
406                              "Cannot load module '~p': ~p~n"
407                              "Keep the previously-loaded version~n",
408                              [ModName, What]
409                             )
410                    end;
411                _ ->
412                    error_logger:format("Compilation of '~p' failed~n"
413                                        "Keep the previously-loaded version~n",
414                                        [File])
415            end;
416        {error, Reason} ->
417            error_logger:format("Cannot write module ~p: ~p~n"
418                                "Keep the previously-loaded version~n",
419                                [File, Reason])
420    end.
421
422
423%% Compile modules found in the configured source directories, recursively.
424compile_and_load_src_dir(GC) ->
425    Incs = lists:map(fun(Dir) -> {i, Dir} end, GC#gconf.include_dir),
426    Opts = [binary, return] ++ Incs,
427    lists:foreach(fun(D) -> compile_and_load_src_dir([], [D], Opts) end,
428                  GC#gconf.src_dir).
429
430compile_and_load_src_dir(_Dir, [], _Opts) ->
431    ok;
432compile_and_load_src_dir(Dir, [Entry0|Rest], Opts) ->
433    Entry1 = case Dir of
434                 [] -> Entry0;
435                 _  -> filename:join(Dir, Entry0)
436             end,
437    case filelib:is_dir(Entry1) of
438        true ->
439            case file:list_dir(Entry1) of
440                {ok, Files} ->
441                    compile_and_load_src_dir(Entry1, Files, Opts);
442                {error, Reason} ->
443                    error_logger:format("Failed to compile modules in ~p: ~s~n",
444                                        [Entry1, file:format_error(Reason)])
445            end;
446        false ->
447            case filename:extension(Entry0) of
448                ".erl" -> compile_module_src_dir(Entry1, Opts);
449                _      -> ok
450            end
451    end,
452    compile_and_load_src_dir(Dir, Rest, Opts).
453
454
455compile_module_src_dir(File, Opts) ->
456    case catch compile:file(File, Opts) of
457        {ok, Mod, Bin} ->
458            error_logger:info_msg("Compiled ~p~n", [File]),
459            load_src_dir(File, Mod, Bin);
460        {ok, Mod, Bin, []} ->
461            error_logger:info_msg("Compiled ~p [0 Errors - 0 Warnings]~n", [File]),
462            load_src_dir(File, Mod, Bin);
463        {ok, Mod, Bin, Warnings} ->
464            WsMsg = [format_compile_warns(W,[]) || W <- Warnings],
465            error_logger:warning_msg("Compiled ~p [~p Errors - ~p Warnings]~n~s",
466                                     [File,0,length(WsMsg),WsMsg]),
467            load_src_dir(File, Mod, Bin);
468        {error, [], Warnings} ->
469            WsMsg = [format_compile_warns(W,[]) || W <- Warnings],
470            error_logger:format("Failed to compile ~p "
471                                "[~p Errors - ~p Warnings]~n~s"
472                                "*** warnings being treated as errors~n",
473                                [File,0,length(WsMsg),WsMsg]);
474        {error, Errors, Warnings} ->
475            WsMsg = [format_compile_warns(W,[]) || W <- Warnings],
476            EsMsg = [format_compile_errs(E,[])  || E <- Errors],
477            error_logger:format("Failed to compile ~p "
478                                "[~p Errors - ~p Warnings]~n~s~s",
479                                [File,length(EsMsg),length(WsMsg),EsMsg,WsMsg]);
480        error ->
481            error_logger:format("Failed to compile ~p~n", [File]);
482        {'EXIT', Reason} ->
483            error_logger:format("Failed to compile ~p: ~p~n", [File, Reason])
484    end.
485
486
487load_src_dir(File, Mod, Bin) ->
488    case code:load_binary(Mod, File, Bin) of
489        {module, Mod}   -> ok;
490        {error, Reason} -> error_logger:format("Cannot load module ~p: ~p~n",
491                                               [Mod, Reason])
492    end.
493
494format_compile_warns({_, []}, Acc) ->
495    lists:reverse(Acc);
496format_compile_warns({File, [{L,M,E}|Rest]}, Acc) ->
497    Msg = io_lib:format("    ~s:~w: Warning: ~s~n", [File,L,M:format_error(E)]),
498    format_compile_warns({File, Rest}, [Msg|Acc]).
499
500format_compile_errs({_, []}, Acc) ->
501    lists:reverse(Acc);
502format_compile_errs({File, [{L,M,E}|Rest]}, Acc) ->
503    Msg = io_lib:format("    ~s:~w: ~s~n", [File,L,M:format_error(E)]),
504    format_compile_errs({File, Rest}, [Msg|Acc]).
505
506
507
508%% This is the function that arranges sconfs into
509%% different server groups
510validate_cs(GC, Cs) ->
511    L = lists:map(fun(#sconf{listen=IP0}=SC0) ->
512                          SC = case is_tuple(IP0) of
513                                   false ->
514                                       {ok, IP} = inet_parse:address(IP0),
515                                       SC0#sconf{listen=IP};
516                                   true ->
517                                       SC0
518                               end,
519                              {{SC#sconf.listen, SC#sconf.port}, SC}
520                  end, Cs),
521    L2 = lists:map(fun(X) -> element(2, X) end, lists:keysort(1,L)),
522    L3 = arrange(L2, start, [], []),
523    case validate_groups(GC, L3) of
524        ok ->
525            {ok, GC, L3};
526        Err ->
527            Err
528    end.
529
530
531validate_groups(_, []) ->
532    ok;
533validate_groups(GC, [H|T]) ->
534    case (catch validate_group(GC, H)) of
535        ok ->
536            validate_groups(GC, T);
537        Err ->
538            Err
539    end.
540
541validate_group(GC, List) ->
542    [SC0|SCs] = List,
543
544    %% all servers with the same IP/Port must share the same tcp configuration
545    case lists:all(fun(SC) ->
546                           lists:keyfind(listen_opts, 1, SC#sconf.soptions) ==
547                               lists:keyfind(listen_opts, 1, SC0#sconf.soptions)
548                   end, SCs) of
549        true ->
550            ok;
551        false ->
552            throw({error, ?F("Servers in the same group must share the same tcp"
553                             " configuration: ~p", [SC0#sconf.servername])})
554    end,
555
556    %% If the default servers (the first one) is not an SSL server:
557    %%    all servers  with the same IP/Port must be non-SSL server
558    %% If SNI is disabled or not supported:
559    %%    all servers with the same IP/Port must share the same SSL config
560    %% If SNI is enabled:
561    %%    TLS protocol must be supported by the default servers (the first one)
562    if
563        SC0#sconf.ssl == undefined ->
564            case lists:all(fun(SC) -> SC#sconf.ssl == SC0#sconf.ssl end, SCs) of
565                true  -> ok;
566                false ->
567                    throw({error, ?F("All servers in the same group than"
568                                     " ~p must have no SSL configuration",
569                                     [SC0#sconf.servername])})
570            end;
571        GC#gconf.sni == disable ->
572            case lists:all(fun(SC) -> SC#sconf.ssl == SC0#sconf.ssl end, SCs) of
573                true  -> ok;
574                false ->
575                    throw({error, ?F("SNI is disabled, all servers in the same"
576                                     " group than ~p must share the same ssl"
577                                     " configuration",
578                                     [SC0#sconf.servername])})
579            end;
580
581        true ->
582            Vs = case (SC0#sconf.ssl)#ssl.protocol_version of
583                     undefined -> proplists:get_value(available,ssl:versions());
584                     L         -> L
585                 end,
586            F = fun(V) -> lists:member(V, ['tlsv1.2','tlsv1.1',tlsv1]) end,
587            case lists:any(F, Vs) of
588                true -> ok;
589                false ->
590                    throw({error, ?F("SNI is enabled, the server ~p must enable"
591                                     " TLS protocol", [SC0#sconf.servername])})
592            end
593    end,
594
595    %% all servernames in a group must be unique
596    SN = lists:sort([yaws:to_lower(X#sconf.servername) || X <- List]),
597    no_two_same(SN).
598
599no_two_same([H,H|_]) ->
600    throw({error,
601           ?F("Two servers in the same group cannot have same name ~p",[H])});
602no_two_same([_H|T]) ->
603    no_two_same(T);
604no_two_same([]) ->
605    ok.
606
607
608
609arrange([C|Tail], start, [], B) ->
610    C1 = set_server(C),
611    arrange(Tail, {in, C1}, [C1], B);
612arrange([], _, [], B) ->
613    B;
614arrange([], _, A, B) ->
615    [lists:reverse(A) | B];
616arrange([C|Tail], {in, C0}, A, B) ->
617    C1 = set_server(C),
618    if
619        C1#sconf.listen == C0#sconf.listen,
620        C1#sconf.port == C0#sconf.port ->
621            arrange(Tail, {in, C0}, [C1|A], B);
622        true ->
623            arrange(Tail, {in, C1}, [C1], [lists:reverse(A)|B])
624    end.
625
626
627set_server(SC) ->
628    SC1 = if
629              SC#sconf.port == 0 ->
630                  {ok, P} = yaws:find_private_port(),
631                  SC#sconf{port=P};
632              true ->
633                  SC
634          end,
635    case {SC1#sconf.ssl, SC1#sconf.port, ?sc_has_add_port(SC1)} of
636        {undefined, 80, _} ->
637            SC1;
638        {undefined, Port, true} ->
639            add_port(SC1, Port);
640        {_SSL, 443, _} ->
641            SC1;
642        {_SSL, Port, true} ->
643            add_port(SC1, Port);
644        {_,_,_} ->
645            SC1
646    end.
647
648
649add_port(SC, Port) ->
650    case string:tokens(SC#sconf.servername, ":") of
651        [Srv, Prt] ->
652            case (catch list_to_integer(Prt)) of
653                {'EXIT', _} ->
654                    SC#sconf{servername =
655                                 Srv ++ [$:|integer_to_list(Port)]};
656                _Int ->
657                    SC
658            end;
659        [Srv] ->
660            SC#sconf{servername =   Srv ++ [$:|integer_to_list(Port)]}
661    end.
662
663
664make_default_gconf(Debug, Id) ->
665    Y = yaws_dir(),
666    Flags = case yaws_sendfile:have_sendfile() of
667                true ->
668                    (?GC_COPY_ERRLOG bor ?GC_FAIL_ON_BIND_ERR bor
669                         ?GC_PICK_FIRST_VIRTHOST_ON_NOMATCH bor
670                         ?GC_USE_YAWS_SENDFILE);
671                false ->
672                    (?GC_COPY_ERRLOG bor ?GC_FAIL_ON_BIND_ERR bor
673                         ?GC_PICK_FIRST_VIRTHOST_ON_NOMATCH)
674            end,
675    #gconf{yaws_dir = Y,
676           ebin_dir = [filename:join([Y, "examples/ebin"])],
677           include_dir = [filename:join([Y, "examples/include"])],
678           trace = false,
679           logdir = ".",
680           cache_refresh_secs = if
681                                    Debug == true ->
682                                        0;
683                                    true ->
684                                        30
685                                end,
686           flags = if Debug -> Flags bor ?GC_DEBUG;
687                      true  -> Flags
688                   end,
689
690           yaws = "Yaws " ++ yaws_generated:version(),
691           id = Id
692          }.
693
694%% Keep this function for backward compatibility. But no one is supposed to use
695%% it (yaws_config is an internal module, its api is private).
696make_default_sconf() ->
697    make_default_sconf([], undefined, undefined).
698
699make_default_sconf([], Servername, Port) ->
700    make_default_sconf(filename:join([yaws_dir(), "www"]), Servername, Port);
701make_default_sconf(DocRoot, undefined, Port) ->
702    make_default_sconf(DocRoot, "localhost", Port);
703make_default_sconf(DocRoot, Servername, undefined) ->
704    make_default_sconf(DocRoot, Servername, 8000);
705make_default_sconf(DocRoot, Servername, Port) ->
706    AbsDocRoot = filename:absname(DocRoot),
707    case is_dir(AbsDocRoot) of
708        true ->
709            set_server(#sconf{port=Port, servername=Servername,
710                              listen={127,0,0,1},docroot=AbsDocRoot});
711        false ->
712            throw({error, ?F("Invalid docroot: directory ~s does not exist",
713                             [AbsDocRoot])})
714    end.
715
716
717yaws_dir() ->
718    yaws:get_app_dir().
719
720string_to_host_and_port(String) ->
721    HostPortRE = "^(?:\\[([^\\]]+)\\]|([^:]+)):([0-9]+)$",
722    REOptions = [{capture, all_but_first, list}],
723    case re:run(String, HostPortRE, REOptions) of
724        {match, [IPv6, HostOrIPv4, Port]} ->
725            case string:to_integer(Port) of
726                {Integer, []} when Integer >= 0, Integer =< 65535 ->
727                    case IPv6 of
728                        "" -> {ok, HostOrIPv4, Integer};
729                        _  -> {ok, IPv6, Integer}
730                    end;
731                _Else ->
732                    {error, ?F("~p is not a valid port number", [Port])}
733            end;
734        nomatch ->
735            {error, ?F("bad host and port specifier, expected HOST:PORT; "
736                "use [IP]:PORT for IPv6 address", [])}
737    end.
738
739string_to_node_mod_fun(String) ->
740    case string:tokens(String, ":") of
741        [Node, Mod, Fun] ->
742            {ok, list_to_atom(Node), list_to_atom(Mod), list_to_atom(Fun)};
743        [Mod, Fun] ->
744            {ok, list_to_atom(Mod), list_to_atom(Fun)};
745        _ ->
746            {error, ?F("bad external module specifier, "
747                       "expected NODE:MODULE:FUNCTION or MODULE:FUNCTION", [])}
748    end.
749
750
751
752%% two states, global, server
753fload(FD, GC) ->
754    case catch fload(FD, GC, [], 1, ?NEXTLINE) of
755        {ok, GC1, Cs} -> {ok, GC1, lists:reverse(Cs)};
756        Err           -> Err
757    end.
758
759
760fload(FD, GC, Cs, _Lno, eof) ->
761    file:close(FD),
762    {ok, GC, Cs};
763
764fload(FD, GC, Cs, Lno, Chars) ->
765    case toks(Lno, Chars) of
766        [] ->
767            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
768
769        ["subconfig", '=', Name] ->
770            case subconfigfiles(FD, Name, Lno) of
771                {ok, Files} ->
772                    case fload_subconfigfiles(Files, global, GC, Cs) of
773                        {ok, GC1, Cs1} ->
774                            fload(FD, GC1, Cs1, Lno+1, ?NEXTLINE);
775                        Err ->
776                            Err
777                    end;
778                Err ->
779                    Err
780            end;
781
782        ["subconfigdir", '=', Name] ->
783            case subconfigdir(FD, Name, Lno) of
784                {ok, Files} ->
785                    case fload_subconfigfiles(Files, global, GC, Cs) of
786                        {ok, GC1, Cs1} ->
787                            fload(FD, GC1, Cs1, Lno+1, ?NEXTLINE);
788                        Err ->
789                            Err
790                    end;
791                Err ->
792                    Err
793            end;
794
795        ["trace", '=', Bstr] when GC#gconf.trace == false ->
796            case Bstr of
797                "traffic" ->
798                    fload(FD, GC#gconf{trace = {true, traffic}}, Cs,
799                          Lno+1, ?NEXTLINE);
800                "http" ->
801                    fload(FD, GC#gconf{trace = {true, http}}, Cs,
802                          Lno+1, ?NEXTLINE);
803                "false" ->
804                    fload(FD, GC#gconf{trace = false}, Cs, Lno+1, ?NEXTLINE);
805                _ ->
806                    {error, ?F("Expect false|http|traffic at line ~w",[Lno])}
807            end;
808        ["trace", '=', _Bstr] ->
809            %% don't overwrite setting from commandline
810            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
811
812
813        ["logdir", '=', Logdir] ->
814            Dir = case Logdir of
815                      "+" ++ D ->
816                          D1 = filename:absname(D),
817                          %% try to make the log directory if it doesn't exist
818                          yaws:mkdir(D1),
819                          D1;
820                      _ ->
821                          filename:absname(Logdir)
822                  end,
823            case is_dir(Dir) of
824                true ->
825                    put(logdir, Dir),
826                    fload(FD, GC#gconf{logdir = Dir}, Cs, Lno+1, ?NEXTLINE);
827                false ->
828                    {error, ?F("Expect directory at line ~w (logdir ~s)",
829                               [Lno, Dir])}
830            end;
831
832        ["ebin_dir", '=', Ebindir] ->
833            Dir = filename:absname(Ebindir),
834            case warn_dir("ebin_dir", Dir) of
835                true ->
836                    fload(FD, GC#gconf{ebin_dir = [Dir|GC#gconf.ebin_dir]}, Cs,
837                          Lno+1, ?NEXTLINE);
838                false ->
839                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE)
840            end;
841
842        ["src_dir", '=', Srcdir] ->
843            Dir = filename:absname(Srcdir),
844            case warn_dir("src_dir", Dir) of
845                true ->
846                    fload(FD, GC#gconf{src_dir = [Dir|GC#gconf.src_dir]}, Cs,
847                          Lno+1, ?NEXTLINE);
848                false ->
849                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE)
850            end;
851
852        ["runmod", '=', Mod0] ->
853            Mod = list_to_atom(Mod0),
854            fload(FD, GC#gconf{runmods = [Mod|GC#gconf.runmods]}, Cs,
855                  Lno+1, ?NEXTLINE);
856
857        ["enable_soap", '=', Bool] ->
858            if (Bool == "true") ->
859                    fload(FD, GC#gconf{enable_soap = true}, Cs,
860                          Lno+1, ?NEXTLINE);
861               true ->
862                    fload(FD, GC#gconf{enable_soap = false}, Cs,
863                          Lno+1, ?NEXTLINE)
864            end;
865
866        ["soap_srv_mods", '=' | SoapSrvMods] ->
867            case parse_soap_srv_mods(SoapSrvMods, []) of
868                {ok, L} ->
869                    fload(FD, GC#gconf{soap_srv_mods = L}, Cs,
870                          Lno+1, ?NEXTLINE);
871                {error, Str} ->
872                    {error, ?F("~s at line ~w", [Str, Lno])}
873            end;
874
875        ["max_connections", '=', Int] ->
876            case (catch list_to_integer(Int)) of
877                I when is_integer(I) ->
878                    fload(FD, GC#gconf{max_connections = I}, Cs,
879                          Lno+1, ?NEXTLINE);
880                _ when Int == "nolimit" ->
881                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
882                _ ->
883                    {error, ?F("Expect integer at line ~w", [Lno])}
884            end;
885
886        ["process_options", '=', POpts] ->
887            case parse_process_options(POpts) of
888                {ok, ProcList} ->
889                    fload(FD, GC#gconf{process_options=ProcList}, Cs,
890                          Lno+1, ?NEXTLINE);
891                {error, Str} ->
892                    {error, ?F("~s at line ~w", [Str, Lno])}
893            end;
894
895        ["large_file_chunk_size", '=', Int] ->
896            case (catch list_to_integer(Int)) of
897                I when is_integer(I) ->
898                    fload(FD, GC#gconf{large_file_chunk_size = I}, Cs,
899                          Lno+1, ?NEXTLINE);
900                _ ->
901                    {error, ?F("Expect integer at line ~w", [Lno])}
902            end;
903
904        ["large_file_sendfile", '=', Method] ->
905            case set_sendfile_flags(GC, Method) of
906                {ok, GC1} ->
907                    fload(FD, GC1, Cs, Lno+1, ?NEXTLINE);
908                {error, Str} ->
909                    {error, ?F("~s at line ~w", [Str, Lno])}
910            end;
911
912        ["acceptor_pool_size", '=', Int] ->
913            case catch list_to_integer(Int) of
914                I when is_integer(I), I >= 0 ->
915                    fload(FD, GC#gconf{acceptor_pool_size = I}, Cs,
916                          Lno+1, ?NEXTLINE);
917                _ ->
918                    {error, ?F("Expect integer >= 0 at line ~w", [Lno])}
919            end;
920
921        ["log_wrap_size", '=', Int] ->
922            case (catch list_to_integer(Int)) of
923                I when is_integer(I) ->
924                    fload(FD, GC#gconf{log_wrap_size = I}, Cs,
925                          Lno+1, ?NEXTLINE);
926                _ ->
927                    {error, ?F("Expect integer at line ~w", [Lno])}
928            end;
929
930        ["log_resolve_hostname", '=',  Bool] ->
931            case is_bool(Bool) of
932                {true, Val} ->
933                    fload(FD, ?gc_log_set_resolve_hostname(GC, Val), Cs,
934                          Lno+1, ?NEXTLINE);
935                false ->
936                    {error, ?F("Expect true|false at line ~w", [Lno])}
937            end;
938
939        ["fail_on_bind_err", '=',  Bool] ->
940            case is_bool(Bool) of
941                {true, Val} ->
942                    fload(FD, ?gc_set_fail_on_bind_err(GC, Val), Cs,
943                          Lno+1, ?NEXTLINE);
944                false ->
945                    {error, ?F("Expect true|false at line ~w", [Lno])}
946            end;
947
948
949        ["include_dir", '=', Incdir] ->
950            Dir = filename:absname(Incdir),
951            case warn_dir("include_dir", Dir) of
952                true ->
953                    fload(FD, GC#gconf{include_dir= [Dir|GC#gconf.include_dir]},
954                          Cs, Lno+1, ?NEXTLINE);
955                false ->
956                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE)
957
958            end;
959
960        ["mnesia_dir", '=', Mnesiadir] ->
961            Dir = filename:absname(Mnesiadir),
962            case is_dir(Dir) of
963                true ->
964                    put(mnesiadir, Dir),
965                    fload(FD, GC#gconf{mnesia_dir = Dir}, Cs, Lno+1, ?NEXTLINE);
966                false ->
967                    {error, ?F("Expect mnesia directory at line ~w", [Lno])}
968            end;
969
970        ["tmpdir", '=', _TmpDir] ->
971            %% ignore
972            error_logger:format(
973              "tmpdir in yaws.conf is no longer supported - ignoring\n",[]
974             ),
975            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
976
977        ["keepalive_timeout", '=', Val] ->
978            %% keep this bugger for backward compat for a while
979            case (catch list_to_integer(Val)) of
980                I when is_integer(I) ->
981                    fload(FD, GC#gconf{keepalive_timeout = I}, Cs,
982                          Lno+1, ?NEXTLINE);
983                _ when Val == "infinity" ->
984                    fload(FD, GC#gconf{keepalive_timeout = infinity}, Cs,
985                          Lno+1, ?NEXTLINE);
986                _ ->
987                    {error, ?F("Expect integer at line ~w", [Lno])}
988            end;
989
990        ["keepalive_maxuses", '=', Int] ->
991            case (catch list_to_integer(Int)) of
992                I when is_integer(I) ->
993                    fload(FD, GC#gconf{keepalive_maxuses = I}, Cs,
994                          Lno+1, ?NEXTLINE);
995                _ when Int == "nolimit" ->
996                    %% nolimit is the default
997                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
998                _ ->
999                    {error, ?F("Expect integer at line ~w", [Lno])}
1000            end;
1001
1002        ["php_exe_path", '=' , PhpPath] ->
1003            error_logger:format(
1004              "'php_exe_path' is deprecated, use 'php_handler' instead\n",
1005              []),
1006            case is_file(PhpPath) of
1007                true ->
1008                    fload(FD, GC#gconf{phpexe = PhpPath}, Cs, Lno+1, ?NEXTLINE);
1009                false ->
1010                    {error, ?F("Expect executable file at line ~w", [Lno])}
1011            end;
1012
1013        ["read_timeout", '=', _Val] ->
1014            %% deprected, don't use
1015            error_logger:format(
1016              "read_timeout in yaws.conf is no longer supported - ignoring\n",[]
1017             ),
1018            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1019
1020        ["max_num_cached_files", '=', Val] ->
1021            case (catch list_to_integer(Val)) of
1022                I when is_integer(I) ->
1023                    fload(FD, GC#gconf{max_num_cached_files = I}, Cs,
1024                          Lno+1, ?NEXTLINE);
1025                _ ->
1026                    {error, ?F("Expect integer at line ~w", [Lno])}
1027            end;
1028
1029
1030        ["max_num_cached_bytes", '=', Val] ->
1031            case (catch list_to_integer(Val)) of
1032                I when is_integer(I) ->
1033                    fload(FD, GC#gconf{max_num_cached_bytes = I}, Cs,
1034                          Lno+1, ?NEXTLINE);
1035                _ ->
1036                    {error, ?F("Expect integer at line ~w", [Lno])}
1037            end;
1038
1039
1040        ["max_size_cached_file", '=', Val] ->
1041            case (catch list_to_integer(Val)) of
1042                I when is_integer(I) ->
1043                    fload(FD, GC#gconf{max_size_cached_file = I}, Cs,
1044                          Lno+1, ?NEXTLINE);
1045                _ ->
1046                    {error, ?F("Expect integer at line ~w", [Lno])}
1047            end;
1048
1049        ["cache_refresh_secs", '=', Val] ->
1050            case (catch list_to_integer(Val)) of
1051                I when is_integer(I), I >= 0 ->
1052                    fload(FD, GC#gconf{cache_refresh_secs = I}, Cs,
1053                          Lno+1, ?NEXTLINE);
1054                _ ->
1055                    {error, ?F("Expect 0 or positive integer at line ~w",[Lno])}
1056            end;
1057
1058
1059        ["copy_error_log", '=', Bool] ->
1060            case is_bool(Bool) of
1061                {true, Val} ->
1062                    fload(FD, ?gc_set_copy_errlog(GC, Val), Cs,
1063                          Lno+1, ?NEXTLINE);
1064                false ->
1065                    {error, ?F("Expect true|false at line ~w", [Lno])}
1066            end;
1067
1068
1069        ["auth_log", '=', Bool] ->
1070            error_logger:format(
1071              "'auth_log' global variable is deprecated and ignored."
1072              " it is now a per-server variable", []),
1073            case is_bool(Bool) of
1074                {true, _Val} ->
1075                    fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1076                false ->
1077                    {error, ?F("Expect true|false at line ~w", [Lno])}
1078            end;
1079
1080        ["id", '=', String] when GC#gconf.id == undefined;
1081                                 GC#gconf.id == "default" ->
1082            fload(FD, GC#gconf{id=String}, Cs, Lno+1, ?NEXTLINE);
1083        ["id", '=', String]  ->
1084            error_logger:format("Ignoring 'id = ~p' setting at line ~p~n",
1085                                [String,Lno]),
1086            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1087
1088        ["pick_first_virthost_on_nomatch", '=',  Bool] ->
1089            case is_bool(Bool) of
1090                {true, Val} ->
1091                    fload(FD, ?gc_set_pick_first_virthost_on_nomatch(GC,Val),
1092                          Cs, Lno+1, ?NEXTLINE);
1093                false ->
1094                    {error, ?F("Expect true|false at line ~w", [Lno])}
1095            end;
1096
1097        ["use_fdsrv", '=',  _Bool] ->
1098            %% feature removed
1099            error_logger:format(
1100              "use_fdsrv in yaws.conf is no longer supported - ignoring\n",[]
1101             ),
1102            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1103
1104        ["use_old_ssl", '=',  _Bool] ->
1105            %% feature removed
1106            error_logger:format(
1107              "use_old_ssl in yaws.conf is no longer supported - ignoring\n",[]
1108             ),
1109            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1110
1111        ["use_large_ssl_pool", '=',  _Bool] ->
1112            %% just ignore - not relevant any longer
1113            error_logger:format(
1114              "use_large_ssl_pool in yaws.conf is no longer supported"
1115              " - ignoring\n", []
1116             ),
1117            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1118
1119        ["x_forwarded_for_log_proxy_whitelist", '=' | _] ->
1120            error_logger:format(
1121              "x_forwarded_for_log_proxy_whitelist in yaws.conf is no longer"
1122              " supported - ignoring\n", []
1123             ),
1124            fload(FD, GC, Cs, Lno+1, ?NEXTLINE);
1125
1126        ["ysession_mod", '=', Mod_str] ->
1127            Ysession_mod = list_to_atom(Mod_str),
1128            fload(FD, GC#gconf{ysession_mod = Ysession_mod}, Cs,
1129                  Lno+1, ?NEXTLINE);
1130
1131        ["ysession_cookiegen", '=', Mod_str] ->
1132            Ysession_cookiegen = list_to_atom(Mod_str),
1133            fload(FD, GC#gconf{ysession_cookiegen = Ysession_cookiegen}, Cs,
1134                  Lno+1, ?NEXTLINE);
1135
1136        ["ysession_idle_timeout", '=', YsessionIdle] ->
1137            case (catch list_to_integer(YsessionIdle)) of
1138                I when is_integer(I), I > 0 ->
1139                    fload(FD, GC#gconf{ysession_idle_timeout = I}, Cs,
1140                          Lno+1, ?NEXTLINE);
1141                _ ->
1142                    {error, ?F("Expect positive integer at line ~w",[Lno])}
1143            end;
1144
1145        ["ysession_long_timeout", '=', YsessionLong] ->
1146            case (catch list_to_integer(YsessionLong)) of
1147                I when is_integer(I), I > 0 ->
1148                    fload(FD, GC#gconf{ysession_long_timeout = I}, Cs,
1149                          Lno+1, ?NEXTLINE);
1150                _ ->
1151                    {error, ?F("Expect positive integer at line ~w",[Lno])}
1152            end;
1153
1154        ["server_signature", '=', Signature] ->
1155            fload(FD, GC#gconf{yaws=Signature}, Cs, Lno+1, ?NEXTLINE);
1156
1157        ["default_type", '=', MimeType] ->
1158            case parse_mime_types_info(default_type, MimeType,
1159                                       GC#gconf.mime_types_info,
1160                                       #mime_types_info{}) of
1161                {ok, Info} ->
1162                    fload(FD, GC#gconf{mime_types_info=Info}, Cs,
1163                          Lno+1, ?NEXTLINE);
1164                {error, Str} ->
1165                    {error, ?F("~s at line ~w", [Str, Lno])}
1166            end;
1167
1168        ["default_charset", '=', Charset] ->
1169            case parse_mime_types_info(default_charset, Charset,
1170                                       GC#gconf.mime_types_info,
1171                                       #mime_types_info{}) of
1172                {ok, Info} ->
1173                    fload(FD, GC#gconf{mime_types_info=Info}, Cs,
1174                          Lno+1, ?NEXTLINE);
1175                {error, Str} ->
1176                    {error, ?F("~s at line ~w", [Str, Lno])}
1177            end;
1178
1179        ["mime_types_file", '=', File] ->
1180            case parse_mime_types_info(mime_types_file, File,
1181                                       GC#gconf.mime_types_info,
1182                                       #mime_types_info{}) of
1183                {ok, Info} ->
1184                    fload(FD, GC#gconf{mime_types_info=Info}, Cs,
1185                          Lno+1, ?NEXTLINE);
1186                {error, Str} ->
1187                    {error, ?F("~s at line ~w", [Str, Lno])}
1188            end;
1189
1190        ["add_types", '=' | NewTypes] ->
1191            case parse_mime_types_info(add_types, NewTypes,
1192                                       GC#gconf.mime_types_info,
1193                                       #mime_types_info{}) of
1194                {ok, Info} ->
1195                    fload(FD, GC#gconf{mime_types_info=Info}, Cs,
1196                          Lno+1, ?NEXTLINE);
1197                {error, Str} ->
1198                    {error, ?F("~s at line ~w", [Str, Lno])}
1199            end;
1200
1201        ["add_charsets", '=' | NewCharsets] ->
1202            case parse_mime_types_info(add_charsets, NewCharsets,
1203                                       GC#gconf.mime_types_info,
1204                                       #mime_types_info{}) of
1205                {ok, Info} ->
1206                    fload(FD, GC#gconf{mime_types_info=Info}, Cs,
1207                          Lno+1, ?NEXTLINE);
1208                {error, Str} ->
1209                    {error, ?F("~s at line ~w", [Str, Lno])}
1210            end;
1211
1212        ["nslookup_pref", '=' | Pref] ->
1213            case parse_nslookup_pref(Pref) of
1214                {ok, Families} ->
1215                    fload(FD, GC#gconf{nslookup_pref = Families}, Cs,
1216                          Lno+1, ?NEXTLINE);
1217                {error, Str} ->
1218                    {error, ?F("~s at line ~w", [Str, Lno])}
1219            end;
1220
1221        ["sni", '=', Sni] ->
1222            if
1223                Sni == "disable" ->
1224                    fload(FD, GC#gconf{sni=disable}, Cs, Lno+1, ?NEXTLINE);
1225
1226                Sni == "enable" orelse Sni == "strict" ->
1227                    case yaws_dynopts:have_ssl_sni() of
1228                        true ->
1229                            fload(FD, GC#gconf{sni=list_to_atom(Sni)}, Cs, Lno+1,
1230                                  ?NEXTLINE);
1231                        _ ->
1232                            error_logger:info_msg("Warning, sni option is not"
1233                                                  " supported at line ~w~n", [Lno]),
1234                            fload(FD, GC, Cs, Lno+1, ?NEXTLINE)
1235                    end;
1236                true ->
1237                    {error, ?F("Expect disable|enable|strict at line ~w",[Lno])}
1238            end;
1239
1240        ['<', "server", Server, '>'] ->
1241            C = #sconf{servername = Server, listen = [],
1242                       php_handler = {cgi, GC#gconf.phpexe}},
1243            fload(FD, server, GC, C, Cs, Lno+1, ?NEXTLINE);
1244
1245        [H|_] ->
1246            {error, ?F("Unexpected tokens ~p at line ~w", [H, Lno])};
1247        Err ->
1248            Err
1249    end.
1250
1251
1252fload(FD, server, _GC, _C, _Cs, Lno, eof) ->
1253    file:close(FD),
1254    {error, ?F("Unexpected end-of-file at line ~w", [Lno])};
1255
1256fload(FD, server, GC, C, Cs, Lno, Chars) ->
1257    case fload(FD, server, GC, C, Lno, Chars) of
1258        {ok, _, _, Lno1, eof} ->
1259            {error, ?F("Unexpected end-of-file at line ~w", [Lno1])};
1260        {ok, GC1, C1, Lno1, ['<', "/server", '>']} ->
1261            HasDocroot =
1262                case C1#sconf.docroot of
1263                    undefined ->
1264                        Tests =
1265                            [fun() ->
1266                                     lists:keymember("/", #proxy_cfg.prefix,
1267                                                     C1#sconf.revproxy)
1268                             end,
1269                             fun() ->
1270                                     lists:keymember("/", 1,
1271                                                     C1#sconf.redirect_map)
1272                             end,
1273                             fun() ->
1274                                     lists:foldl(fun(_, true) -> true;
1275                                                    ({"/", _}, _Acc) -> true;
1276                                                    (_, Acc) -> Acc
1277                                                 end, false, C1#sconf.appmods)
1278                             end,
1279                             fun() ->
1280                                     ?sc_forward_proxy(C1)
1281                             end],
1282                        lists:any(fun(T) -> T() end, Tests);
1283                    _ ->
1284                        true
1285                end,
1286            case HasDocroot of
1287                true ->
1288                    case C1#sconf.listen of
1289                        [] ->
1290                            C2 = C1#sconf{listen = {127,0,0,1}},
1291                            fload(FD, GC1, [C2|Cs], Lno1+1, ?NEXTLINE);
1292                        Ls ->
1293                            Cs1 = [C1#sconf{listen=L} || L <- Ls] ++ Cs,
1294                            fload(FD, GC1, Cs1, Lno1+1, ?NEXTLINE)
1295                    end;
1296                false ->
1297                    {error,
1298                     ?F("No valid docroot configured for virthost "
1299                        "'~s' (port: ~w)",
1300                        [C1#sconf.servername, C1#sconf.port])}
1301            end;
1302        Err ->
1303            Err
1304    end.
1305
1306
1307fload(FD, server, GC, C, Lno, eof) ->
1308    file:close(FD),
1309    {ok, GC, C, Lno, eof};
1310fload(FD, _,  _GC, _C, Lno, eof) ->
1311    file:close(FD),
1312    {error, ?F("Unexpected end-of-file at line ~w", [Lno])};
1313
1314fload(FD, server, GC, C, Lno, Chars) ->
1315    case toks(Lno, Chars) of
1316        [] ->
1317            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
1318
1319        ["subconfig", '=', Name] ->
1320            case subconfigfiles(FD, Name, Lno) of
1321                {ok, Files} ->
1322                    case fload_subconfigfiles(Files, server, GC, C) of
1323                        {ok, GC1, C1} ->
1324                            fload(FD, server, GC1, C1, Lno+1, ?NEXTLINE);
1325                        Err ->
1326                            Err
1327                    end;
1328                Err ->
1329                    Err
1330            end;
1331
1332        ["subconfigdir", '=', Name] ->
1333            case subconfigdir(FD, Name, Lno) of
1334                {ok, Files} ->
1335                    case fload_subconfigfiles(Files, server, GC, C) of
1336                        {ok, GC1, C1} ->
1337                            fload(FD, server, GC1, C1, Lno+1, ?NEXTLINE);
1338                        Err ->
1339                            Err
1340                    end;
1341                Err ->
1342                    Err
1343            end;
1344
1345        ["server_signature", '=', Sig] ->
1346            fload(FD, server, GC, C#sconf{yaws=Sig}, Lno+1, ?NEXTLINE);
1347
1348        ["access_log", '=', Bool] ->
1349            case is_bool(Bool) of
1350                {true, Val} ->
1351                    C1 = ?sc_set_access_log(C, Val),
1352                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1353                false ->
1354                    {error, ?F("Expect true|false at line ~w", [Lno])}
1355            end;
1356
1357        ["auth_log", '=', Bool] ->
1358            case is_bool(Bool) of
1359                {true, Val} ->
1360                    C1 = ?sc_set_auth_log(C, Val),
1361                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1362                false ->
1363                    {error, ?F("Expect true|false at line ~w", [Lno])}
1364            end;
1365
1366        ["logger_mod", '=', Module] ->
1367            C1 = C#sconf{logger_mod = list_to_atom(Module)},
1368            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1369
1370        ["dir_listings", '=', StrVal] ->
1371            case StrVal of
1372                "true" ->
1373                    C1 = ?sc_set_dir_listings(C, true),
1374                    C2 = ?sc_set_dir_all_zip(C1, true),
1375                    C3 = C2#sconf{appmods = [ {"all.zip", yaws_ls},
1376                                              {"all.tgz", yaws_ls},
1377                                              {"all.tbz2", yaws_ls}|
1378                                              C2#sconf.appmods]},
1379                    fload(FD, server, GC, C3, Lno+1, ?NEXTLINE);
1380                "true_nozip" ->
1381                    C1 = ?sc_set_dir_listings(C, true),
1382                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1383                "false" ->
1384                    C1 = ?sc_set_dir_listings(C, false),
1385                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1386                _ ->
1387                    {error, ?F("Expect true|true_nozip|false at line ~w",[Lno])}
1388            end;
1389
1390        ["deflate", '=', Bool] ->
1391            case is_bool(Bool) of
1392                {true, Val} ->
1393                    C1 = C#sconf{deflate_options=#deflate{}},
1394                    C2 = ?sc_set_deflate(C1, Val),
1395                    fload(FD, server, GC, C2, Lno+1, ?NEXTLINE);
1396                false ->
1397                    {error, ?F("Expect true|false at line ~w", [Lno])}
1398            end;
1399
1400        ["auth_skip_docroot",'=',Bool] ->
1401            case is_bool(Bool) of
1402                {true,Val} ->
1403                    C1 = ?sc_set_auth_skip_docroot(C, Val),
1404                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1405                false ->
1406                    {error, ?F("Expect true|false at line ~w", [Lno])}
1407            end;
1408
1409        ["dav", '=', Bool] ->
1410            case is_bool(Bool) of
1411                {true, true} ->
1412                    %% Ever since WebDAV support was moved into an appmod,
1413                    %% we must no longer set the dav flag in the
1414                    %% sconf. Always turn it off instead.
1415                    C1 = ?sc_set_dav(C, false),
1416                    Runmods = GC#gconf.runmods,
1417                    GC1 = case lists:member(yaws_runmod_lock, Runmods) of
1418                              false ->
1419                                  GC#gconf{runmods=[yaws_runmod_lock|Runmods]};
1420                              true ->
1421                                  GC
1422                          end,
1423                    DavAppmods = lists:keystore(yaws_appmod_dav, 2,
1424                                                C1#sconf.appmods,
1425                                                {"/",yaws_appmod_dav}),
1426                    C2 = C1#sconf{appmods=DavAppmods},
1427                    fload(FD, server, GC1, C2, Lno+1, ?NEXTLINE);
1428                {true,false} ->
1429                    C1 = ?sc_set_dav(C, false),
1430                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1431                false ->
1432                    {error, ?F("Expect true|false at line ~w", [Lno])}
1433            end;
1434
1435        ["port", '=', Val] ->
1436            case (catch list_to_integer(Val)) of
1437                I when is_integer(I) ->
1438                    C1 = C#sconf{port = I},
1439                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1440                _ ->
1441                    {error, ?F("Expect integer at line ~w", [Lno])}
1442            end;
1443
1444        ["rmethod", '=', Val] ->
1445            case Val of
1446                "http" ->
1447                    C1 = C#sconf{rmethod = Val},
1448                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1449                "https" ->
1450                    C1 = C#sconf{rmethod = Val},
1451                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1452                _ ->
1453                    {error, ?F("Expect http or https at line ~w", [Lno])}
1454            end;
1455
1456        ["rhost", '=', Val] ->
1457            C1 = C#sconf{rhost = Val},
1458            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1459
1460        ["listen", '=', IP] ->
1461            case inet_parse:address(IP) of
1462                {error, _} ->
1463                    {error, ?F("Expect IP address at line ~w:", [Lno])};
1464                {ok,Addr} ->
1465                    Lstn = C#sconf.listen,
1466                    C1 = if
1467                             is_list(Lstn) ->
1468                                 case lists:member(Addr, Lstn) of
1469                                     false ->
1470                                         C#sconf{listen = [Addr|Lstn]};
1471                                     true ->
1472                                         C
1473                                 end;
1474                             true ->
1475                                 C#sconf{listen = [Addr, Lstn]}
1476                         end,
1477                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE)
1478            end;
1479
1480        ["listen_backlog", '=', Val] ->
1481            case (catch list_to_integer(Val)) of
1482                B when is_integer(B) ->
1483                    C1 = update_soptions(C, listen_opts, backlog, B),
1484                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1485                _ ->
1486                    {error, ?F("Expect integer at line ~w", [Lno])}
1487            end;
1488
1489        ["servername", '=', Name] ->
1490            C1 = ?sc_set_add_port((C#sconf{servername = Name}),false),
1491            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1492
1493        ["serveralias", '=' | Names] ->
1494            C1 = C#sconf{serveralias = Names ++ C#sconf.serveralias},
1495            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1496
1497        [ '<', "listen_opts", '>'] ->
1498            fload(FD, listen_opts, GC, C, Lno+1, ?NEXTLINE);
1499
1500        ["docroot", '=', Rootdir | XtraDirs] ->
1501            RootDirs = lists:map(fun(R) -> filename:absname(R) end,
1502                                 [Rootdir | XtraDirs]),
1503            case lists:filter(fun(R) -> not is_dir(R) end, RootDirs) of
1504                [] when C#sconf.docroot =:= undefined ->
1505                    C1 = C#sconf{docroot = hd(RootDirs),
1506                                 xtra_docroots = tl(RootDirs)},
1507                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1508                [] ->
1509                    XtraDocroots = RootDirs ++ C#sconf.xtra_docroots,
1510                    C1 = C#sconf{xtra_docroots = XtraDocroots},
1511                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1512                NoDirs ->
1513                    error_logger:info_msg("Warning, Skip invalid docroots"
1514                                          " at line ~w : ~s~n",
1515                                          [Lno, string:join(NoDirs, ", ")]),
1516                    case lists:subtract(RootDirs, NoDirs) of
1517                        [] ->
1518                            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
1519                        [H|T] when C#sconf.docroot =:= undefined ->
1520                            C1 = C#sconf{docroot = H, xtra_docroots = T},
1521                            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1522                        Ds ->
1523                            XtraDocroots = Ds ++ C#sconf.xtra_docroots,
1524                            C1 = C#sconf{xtra_docroots = XtraDocroots},
1525                            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE)
1526                    end
1527            end;
1528
1529        ["partial_post_size",'=',Size] ->
1530            case Size of
1531                "nolimit" ->
1532                    C1 = C#sconf{partial_post_size = nolimit},
1533                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1534                Val ->
1535                    case (catch list_to_integer(Val)) of
1536                        I when is_integer(I) ->
1537                            C1 = C#sconf{partial_post_size = I},
1538                            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1539                        _ ->
1540                            {error,
1541                             ?F("Expect integer or 'nolimit' at line ~w",
1542                                [Lno])}
1543                    end
1544            end;
1545
1546        ['<', "auth", '>'] ->
1547            C1 = C#sconf{authdirs=[#auth{}|C#sconf.authdirs]},
1548            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
1549
1550        ['<', "redirect", '>'] ->
1551            fload(FD, server_redirect, GC, C, Lno+1, ?NEXTLINE);
1552
1553        ['<', "deflate", '>'] ->
1554            C1 = C#sconf{deflate_options=#deflate{mime_types=[]}},
1555            fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
1556
1557        ["default_server_on_this_ip", '=', _Bool] ->
1558            error_logger:format(
1559              "default_server_on_this_ip in yaws.conf is no longer"
1560              " supported - ignoring\n", []
1561             ),
1562            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
1563
1564        [ '<', "ssl", '>'] ->
1565            ssl_start(),
1566            fload(FD, ssl, GC, C#sconf{ssl = #ssl{}}, Lno+1, ?NEXTLINE);
1567
1568        ["appmods", '=' | AppMods] ->
1569            case parse_appmods(AppMods, []) of
1570                {ok, L} ->
1571                    C1 = C#sconf{appmods = L ++ C#sconf.appmods},
1572                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1573                {error, Str} ->
1574                    {error, ?F("~s at line ~w", [Str, Lno])}
1575            end;
1576
1577        ["dispatchmod", '=', DispatchMod] ->
1578            C1 = C#sconf{dispatch_mod = list_to_atom(DispatchMod)},
1579            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1580
1581        ["expires", '=' | Expires] ->
1582            case parse_expires(Expires, []) of
1583                {ok, L} ->
1584                    C1 = C#sconf{expires = L ++ C#sconf.expires},
1585                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1586                {error, Str} ->
1587                    {error, ?F("~s at line ~w", [Str, Lno])}
1588            end;
1589
1590        ["errormod_404", '=' , Module] ->
1591            C1 = C#sconf{errormod_404 = list_to_atom(Module)},
1592            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1593
1594        ["errormod_crash", '=', Module] ->
1595            C1 = C#sconf{errormod_crash = list_to_atom(Module)},
1596            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1597
1598        ["errormod_401", '=' , Module] ->
1599            C1 = C#sconf{errormod_401 = list_to_atom(Module)},
1600            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1601
1602        ["arg_rewrite_mod", '=', Module] ->
1603            C1 = C#sconf{arg_rewrite_mod = list_to_atom(Module)},
1604            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1605
1606        ["tilde_expand", '=', Bool] ->
1607            case is_bool(Bool) of
1608                {true, Val} ->
1609                    C1 = ?sc_set_tilde_expand(C,Val),
1610                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1611                false ->
1612                    {error, ?F("Expect true|false at line ~w", [Lno])}
1613            end;
1614
1615        ['<', "opaque", '>'] ->
1616            fload(FD, opaque, GC, C, Lno+1, ?NEXTLINE);
1617
1618        ["start_mod", '=' , Module] ->
1619            C1 = C#sconf{start_mod = list_to_atom(Module)},
1620            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1621
1622        ['<', "rss", '>'] ->
1623            erase(rss_id),
1624            put(rss, []),
1625            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
1626
1627        ["tilde_allowed_scripts", '=' | Suffixes] ->
1628            C1 = C#sconf{tilde_allowed_scripts=Suffixes},
1629            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1630
1631        ["allowed_scripts", '=' | Suffixes] ->
1632            C1 = C#sconf{allowed_scripts=Suffixes},
1633            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1634
1635        ["index_files", '=' | Files] ->
1636            case parse_index_files(Files) of
1637                ok ->
1638                    C1 = C#sconf{index_files = Files},
1639                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1640                {error, Str} ->
1641                    {error, ?F("~s at line ~w", [Str, Lno])}
1642            end;
1643
1644        ["revproxy", '=' | Tail] ->
1645            case parse_revproxy(Tail) of
1646                {ok, RevProxy} ->
1647                    C1 = C#sconf{revproxy = [RevProxy | C#sconf.revproxy]},
1648                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1649                {error, url} ->
1650                    {error, ?F("Bad url at line ~p",[Lno])};
1651                {error, syntax} ->
1652                    {error, ?F("Bad revproxy syntax at line ~p",[Lno])};
1653                Error ->
1654                    Error
1655            end;
1656
1657        ["fwdproxy", '=', Bool] ->
1658            case is_bool(Bool) of
1659                {true, Val} ->
1660                    C1 = ?sc_set_forward_proxy(C, Val),
1661                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1662                false ->
1663                    {error, ?F("Expect true|false at line ~w", [Lno])}
1664            end;
1665
1666        ['<', "extra_cgi_vars", "dir", '=', Dir, '>'] ->
1667            C1 = C#sconf{extra_cgi_vars=[{Dir, []}|C#sconf.extra_cgi_vars]},
1668            fload(FD, extra_cgi_vars, GC, C1, Lno+1, ?NEXTLINE);
1669
1670        ["statistics", '=', Bool] ->
1671            case is_bool(Bool) of
1672                {true, Val} ->
1673                    C1 = ?sc_set_statistics(C, Val),
1674                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1675                false ->
1676                    {error, ?F("Expect true|false at line ~w", [Lno])}
1677            end;
1678
1679        ["fcgi_app_server", '=' | Val] ->
1680            HostPortSpec = case Val of
1681                [HPS]                    -> HPS;
1682                ['[', HSpec, ']', PSpec] -> "[" ++ HSpec ++ "]" ++ PSpec
1683            end,
1684            case string_to_host_and_port(HostPortSpec) of
1685                {ok, Host, Port} ->
1686                    C1 = C#sconf{fcgi_app_server = {Host, Port}},
1687                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1688                {error, Reason} ->
1689                    {error, ?F("Invalid fcgi_app_server ~p at line ~w: ~s",
1690                               [HostPortSpec, Lno, Reason])}
1691            end;
1692
1693        ["fcgi_trace_protocol", '=', Bool] ->
1694            case is_bool(Bool) of
1695                {true, Val} ->
1696                    C1 = ?sc_set_fcgi_trace_protocol(C, Val),
1697                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1698                false ->
1699                    {error, ?F("Expect true|false at line ~w", [Lno])}
1700            end;
1701
1702        ["fcgi_log_app_error", '=', Bool] ->
1703            case is_bool(Bool) of
1704                {true, Val} ->
1705                    C1 = ?sc_set_fcgi_log_app_error(C, Val),
1706                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1707                false ->
1708                    {error, ?F("Expect true|false at line ~w", [Lno])}
1709            end;
1710
1711        ["phpfcgi", '=', HostPortSpec] ->
1712            error_logger:format(
1713              "'phpfcgi' is deprecated, use 'php_handler' instead\n", []),
1714            case string_to_host_and_port(HostPortSpec) of
1715                {ok, Host, Port} ->
1716                    C1 = C#sconf{php_handler = {fcgi, {Host, Port}}},
1717                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1718                {error, Reason} ->
1719                    {error,
1720                     ?F("Invalid php fcgi server ~p at line ~w: ~s",
1721                        [HostPortSpec, Lno, Reason])}
1722            end;
1723
1724        ["php_handler", '=' | PhpMod] ->
1725            case parse_phpmod(PhpMod, GC#gconf.phpexe) of
1726                {ok, I} ->
1727                    C1 = C#sconf{php_handler = I},
1728                    fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1729                {error, Reason} ->
1730                    {error,
1731                     ?F("Invalid php_handler configuration at line ~w: ~s",
1732                        [Lno, Reason])}
1733            end;
1734
1735        ["shaper", '=', Module] ->
1736            C1 = C#sconf{shaper = list_to_atom(Module)},
1737            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
1738
1739
1740        ["default_type", '=', MimeType] ->
1741            case parse_mime_types_info(default_type, MimeType,
1742                                       C#sconf.mime_types_info,
1743                                       GC#gconf.mime_types_info) of
1744                {ok, Info} ->
1745                    fload(FD, server, GC, C#sconf{mime_types_info=Info},
1746                          Lno+1, ?NEXTLINE);
1747                {error, Str} ->
1748                    {error, ?F("~s at line ~w", [Str, Lno])}
1749            end;
1750
1751        ["default_charset", '=', Charset] ->
1752            case parse_mime_types_info(default_charset, Charset,
1753                                       C#sconf.mime_types_info,
1754                                       GC#gconf.mime_types_info) of
1755                {ok, Info} ->
1756                    fload(FD, server, GC, C#sconf{mime_types_info=Info},
1757                          Lno+1, ?NEXTLINE);
1758                {error, Str} ->
1759                    {error, ?F("~s at line ~w", [Str, Lno])}
1760            end;
1761
1762        ["mime_types_file", '=', File] ->
1763            case parse_mime_types_info(mime_types_file, File,
1764                                       C#sconf.mime_types_info,
1765                                       GC#gconf.mime_types_info) of
1766                {ok, Info} ->
1767                    fload(FD, server, GC, C#sconf{mime_types_info=Info},
1768                          Lno+1, ?NEXTLINE);
1769                {error, Str} ->
1770                    {error, ?F("~s at line ~w", [Str, Lno])}
1771            end;
1772
1773        ["add_types", '=' | NewTypes] ->
1774            case parse_mime_types_info(add_types, NewTypes,
1775                                       C#sconf.mime_types_info,
1776                                       GC#gconf.mime_types_info) of
1777                {ok, Info} ->
1778                    fload(FD, server, GC, C#sconf{mime_types_info=Info},
1779                          Lno+1, ?NEXTLINE);
1780                {error, Str} ->
1781                    {error, ?F("~s at line ~w", [Str, Lno])}
1782            end;
1783
1784        ["add_charsets", '=' | NewCharsets] ->
1785            case parse_mime_types_info(add_charsets, NewCharsets,
1786                                       C#sconf.mime_types_info,
1787                                       GC#gconf.mime_types_info) of
1788                {ok, Info} ->
1789                    fload(FD, server, GC, C#sconf{mime_types_info=Info},
1790                          Lno+1, ?NEXTLINE);
1791                {error, Str} ->
1792                    {error, ?F("~s at line ~w", [Str, Lno])}
1793            end;
1794
1795        ['<', "/server", '>'] ->
1796            {ok, GC, C, Lno, ['<', "/server", '>']};
1797
1798        [H|T] ->
1799            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
1800        Err ->
1801            Err
1802    end;
1803
1804
1805fload(FD, listen_opts, GC, C, Lno, Chars) ->
1806    case toks(Lno, Chars) of
1807        [] ->
1808            fload(FD, listen_opts, GC, C, Lno+1, ?NEXTLINE);
1809
1810        ["buffer", '=', Int] ->
1811            case (catch list_to_integer(Int)) of
1812                B when is_integer(B) ->
1813                    C1 = update_soptions(C, listen_opts, buffer, B),
1814                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1815                _ ->
1816                    {error, ?F("Expect integer at line ~w", [Lno])}
1817            end;
1818
1819        ["delay_send", '=', Bool] ->
1820            case is_bool(Bool) of
1821                {true, Val} ->
1822                    C1 = update_soptions(C, listen_opts, delay_send, Val),
1823                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1824                false ->
1825                    {error, ?F("Expect true|false at line ~w", [Lno])}
1826            end;
1827
1828        ["linger", '=', Val] ->
1829            case (catch list_to_integer(Val)) of
1830                I when is_integer(I) ->
1831                    C1 = update_soptions(C, listen_opts, linger, {true, I}),
1832                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1833                _ when Val == "false" ->
1834                    C1 = update_soptions(C, listen_opts, linger, {false, 0}),
1835                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1836                _ ->
1837                    {error, ?F("Expect integer|false at line ~w", [Lno])}
1838            end;
1839
1840        ["nodelay", '=', Bool] ->
1841            case is_bool(Bool) of
1842                {true, Val} ->
1843                    C1 = update_soptions(C, listen_opts, nodelay, Val),
1844                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1845                false ->
1846                    {error, ?F("Expect true|false at line ~w", [Lno])}
1847            end;
1848
1849        ["priority", '=', Int] ->
1850            case (catch list_to_integer(Int)) of
1851                P when is_integer(P) ->
1852                    C1 = update_soptions(C, listen_opts, priority, P),
1853                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1854                _ ->
1855                    {error, ?F("Expect integer at line ~w", [Lno])}
1856            end;
1857
1858        ["sndbuf", '=', Int] ->
1859            case (catch list_to_integer(Int)) of
1860                I when is_integer(I) ->
1861                    C1 = update_soptions(C, listen_opts, sndbuf, I),
1862                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1863                _ ->
1864                    {error, ?F("Expect integer at line ~w", [Lno])}
1865            end;
1866
1867        ["recbuf", '=', Int] ->
1868            case (catch list_to_integer(Int)) of
1869                I when is_integer(I) ->
1870                    C1 = update_soptions(C, listen_opts, recbuf, I),
1871                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1872                _ ->
1873                    {error, ?F("Expect integer at line ~w", [Lno])}
1874            end;
1875
1876        ["send_timeout", '=', Val] ->
1877            case (catch list_to_integer(Val)) of
1878                I when is_integer(I) ->
1879                    C1 = update_soptions(C, listen_opts, send_timeout, I),
1880                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1881                _ when Val == "infinity" ->
1882                    C1 = update_soptions(C, listen_opts, send_timeout,
1883                                         infinity),
1884                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1885                _ ->
1886                    {error, ?F("Expect integer|infinity at line ~w", [Lno])}
1887            end;
1888
1889        ["send_timeout_close", '=', Bool] ->
1890            case is_bool(Bool) of
1891                {true, Val} ->
1892                    C1 = update_soptions(C, listen_opts, send_timeout_close,
1893                                         Val),
1894                    fload(FD, listen_opts, GC, C1, Lno+1, ?NEXTLINE);
1895                false ->
1896                    {error, ?F("Expect true|false at line ~w", [Lno])}
1897            end;
1898
1899        ['<', "/listen_opts", '>'] ->
1900            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
1901
1902        [H|T] ->
1903            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
1904        Err ->
1905            Err
1906    end;
1907
1908fload(FD, ssl, GC, C, Lno, Chars) ->
1909    case toks(Lno, Chars) of
1910        [] ->
1911            fload(FD, ssl, GC, C, Lno+1, ?NEXTLINE);
1912
1913        %% A bunch of ssl options
1914
1915        ["keyfile", '=', Val] ->
1916            case is_file(Val) of
1917                true ->
1918                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{keyfile = Val}},
1919                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1920                _ ->
1921                    {error, ?F("Expect existing file at line ~w", [Lno])}
1922            end;
1923
1924        ["certfile", '=', Val] ->
1925            case is_file(Val) of
1926                true ->
1927                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{certfile = Val}},
1928                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1929                _ ->
1930                    {error, ?F("Expect existing file at line ~w", [Lno])}
1931            end;
1932
1933        ["cacertfile", '=', Val] ->
1934            case is_file(Val) of
1935                true ->
1936                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{cacertfile = Val}},
1937                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1938                _ ->
1939                    {error, ?F("Expect existing file at line ~w", [Lno])}
1940            end;
1941
1942        ["dhfile", '=', Val] ->
1943            case is_file(Val) of
1944                true ->
1945                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{dhfile = Val}},
1946                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1947                _ ->
1948                    {error, ?F("Expect existing file at line ~w", [Lno])}
1949            end;
1950
1951        ["verify", '=', Val0] ->
1952            Fail0 = (C#sconf.ssl)#ssl.fail_if_no_peer_cert,
1953            {Val, Fail} = try
1954                              case list_to_integer(Val0) of
1955                                  0 -> {verify_none, Fail0};
1956                                  1 -> {verify_peer, false};
1957                                  2 -> {verify_peer, true};
1958                                  _ -> {error, Fail0}
1959                              end
1960                          catch error:badarg ->
1961                                  case list_to_atom(Val0) of
1962                                      verify_none -> {verify_none, Fail0};
1963                                      verify_peer -> {verify_peer, Fail0};
1964                                      _           -> {error, Fail0}
1965                                  end
1966                          end,
1967            case Val of
1968                error ->
1969                    {error, ?F("Expect integer or verify_none, "
1970                               "verify_peer at line ~w", [Lno])};
1971                _ ->
1972                    SSL = (C#sconf.ssl)#ssl{verify=Val,
1973                                            fail_if_no_peer_cert=Fail},
1974                    C1 = C#sconf{ssl=SSL},
1975                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE)
1976            end;
1977
1978        ["fail_if_no_peer_cert", '=', Bool] ->
1979            case is_bool(Bool) of
1980                {true, Val} ->
1981                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{
1982                                         fail_if_no_peer_cert = Val}},
1983                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1984                false ->
1985                    {error, ?F("Expect true|false at line ~w", [Lno])}
1986            end;
1987
1988        ["depth", '=', Val0] ->
1989            Val = (catch list_to_integer(Val0)),
1990            case lists:member(Val, [0, 1,2,3,4,5,6,7]) of
1991                true ->
1992                    C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{depth = Val}},
1993                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
1994                _ ->
1995                    {error, ?F("Expect integer 0..7 at line ~w", [Lno])}
1996            end;
1997
1998        ["password", '=', Val] ->
1999            C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{password = Val}},
2000            fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
2001
2002        ["ciphers", '=', Val] ->
2003            try
2004                L = str2term(Val),
2005                Ciphers = ssl:cipher_suites(),
2006                case check_ciphers(L, Ciphers) of
2007                    ok ->
2008                        C1 = C#sconf{ssl = (C#sconf.ssl)#ssl{ciphers = L}},
2009                        fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
2010                    Err ->
2011                        Err
2012                end
2013            catch _:_ ->
2014                    {error, ?F("Bad cipherspec at line ~w", [Lno])}
2015            end;
2016
2017        ["secure_renegotiate", '=', Bool] ->
2018            case is_bool(Bool) of
2019                {true, Val} ->
2020                    C1 = C#sconf{ssl=(C#sconf.ssl)#ssl{secure_renegotiate=Val}},
2021                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
2022                false ->
2023                    {error, ?F("Expect true|false at line ~w", [Lno])}
2024            end;
2025
2026        ["client_renegotiation", '=', Bool] ->
2027            case yaws_dynopts:have_ssl_client_renegotiation() of
2028                true ->
2029                    case is_bool(Bool) of
2030                        {true, Val} ->
2031                            C1 = C#sconf{ssl=(C#sconf.ssl)#ssl{client_renegotiation=Val}},
2032                            fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
2033                        false ->
2034                            {error, ?F("Expect true|false at line ~w", [Lno])}
2035                    end;
2036                _ ->
2037                    error_logger:info_msg("Warning, client_renegotiation SSL "
2038                                          "option is not supported "
2039                                          "at line ~w~n", [Lno]),
2040                    fload(FD, ssl, GC, C, Lno+1, ?NEXTLINE)
2041            end;
2042
2043        ["honor_cipher_order", '=', Bool] ->
2044            case yaws_dynopts:have_ssl_honor_cipher_order() of
2045                true ->
2046                    case is_bool(Bool) of
2047                        {true, Val} ->
2048                            C2 = C#sconf{
2049                                   ssl=(C#sconf.ssl)#ssl{honor_cipher_order=Val}
2050                                  },
2051                            fload(FD, ssl, GC, C2, Lno+1, ?NEXTLINE);
2052                        false ->
2053                            {error, ?F("Expect true|false at line ~w", [Lno])}
2054                    end;
2055                _ ->
2056                    error_logger:info_msg("Warning, honor_cipher_order SSL "
2057                                          "option is not supported "
2058                                          "at line ~w~n", [Lno]),
2059                    fload(FD, ssl, GC, C, Lno+1, ?NEXTLINE)
2060            end;
2061
2062        ["protocol_version", '=' | Vsns0] ->
2063            try
2064                Vsns = [list_to_existing_atom(V) || V <- Vsns0, not is_atom(V)],
2065                C1 = C#sconf{
2066                       ssl=(C#sconf.ssl)#ssl{protocol_version=Vsns}
2067                      },
2068                fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE)
2069            catch _:_ ->
2070                    {error, ?F("Bad ssl protocol_version at line ~w", [Lno])}
2071            end;
2072
2073        ["require_sni", '=', Bool] ->
2074            case is_bool(Bool) of
2075                {true, Val} ->
2076                    C1 = C#sconf{
2077                           ssl=(C#sconf.ssl)#ssl{require_sni=Val}
2078                          },
2079                    fload(FD, ssl, GC, C1, Lno+1, ?NEXTLINE);
2080                false ->
2081                    {error, ?F("Expect true|false at line ~w", [Lno])}
2082            end;
2083
2084        ['<', "/ssl", '>'] ->
2085            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
2086
2087        [H|T] ->
2088            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2089        Err ->
2090            Err
2091    end;
2092
2093fload(FD, server_auth, GC, C, Lno, Chars) ->
2094    [Auth|AuthDirs] = C#sconf.authdirs,
2095    case toks(Lno, Chars) of
2096        [] ->
2097            fload(FD, server_auth, GC, C, Lno+1, ?NEXTLINE);
2098
2099        ["docroot", '=', Docroot] ->
2100            Auth1 = Auth#auth{docroot = filename:absname(Docroot)},
2101            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2102            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2103
2104        ["dir", '=', Dir] ->
2105            case file:list_dir(Dir) of
2106                {ok,_} when Dir /= "/" ->
2107                    error_logger:info_msg("Warning, authdir must be set "
2108                                          "relative docroot ~n",[]);
2109                _ ->
2110                    ok
2111            end,
2112            Dir1 = yaws_api:path_norm(Dir),
2113            Auth1 = Auth#auth{dir = [Dir1 | Auth#auth.dir]},
2114            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2115            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2116
2117        ["realm", '=', Realm] ->
2118            Auth1 = Auth#auth{realm = Realm},
2119            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2120            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2121
2122        ["authmod", '=', Mod] ->
2123            Mod1 = list_to_atom(Mod),
2124            code:ensure_loaded(Mod1),
2125            %% Add the auth header for the mod
2126            H = try
2127                    Mod1:get_header() ++ Auth#auth.headers
2128                catch _:_ ->
2129                        error_logger:format("Failed to ~p:get_header() \n",
2130                                            [Mod1]),
2131                        Auth#auth.headers
2132                end,
2133            Auth1 = Auth#auth{mod = Mod1, headers = H},
2134            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2135            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2136
2137        ["user", '=', User] ->
2138            case parse_auth_user(User, Lno) of
2139                {Name, Algo, Salt, Hash} ->
2140                    Auth1 = Auth#auth{
2141                              users = [{Name, Algo, Salt, Hash}|Auth#auth.users]
2142                             },
2143                    C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2144                    fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2145                {error, Str} ->
2146                    {error, Str}
2147            end;
2148
2149        ["allow", '=', "all"] ->
2150            Auth1 = case Auth#auth.acl of
2151                        none    -> Auth#auth{acl={all, [], deny_allow}};
2152                        {_,D,O} -> Auth#auth{acl={all, D, O}}
2153                    end,
2154            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2155            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2156
2157        ["allow", '=' | IPs] ->
2158            Auth1 = case Auth#auth.acl of
2159                        none ->
2160                            AllowIPs = parse_auth_ips(IPs, []),
2161                            Auth#auth{acl={AllowIPs, [], deny_allow}};
2162                        {all, _, _} ->
2163                            Auth;
2164                        {AllowIPs, DenyIPs, Order} ->
2165                            AllowIPs1 = parse_auth_ips(IPs, []) ++ AllowIPs,
2166                            Auth#auth{acl={AllowIPs1, DenyIPs, Order}}
2167                    end,
2168            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2169            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2170
2171        ["deny", '=', "all"] ->
2172            Auth1 = case Auth#auth.acl of
2173                        none    -> Auth#auth{acl={[], all, deny_allow}};
2174                        {A,_,O} -> Auth#auth{acl={A, all, O}}
2175                    end,
2176            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2177            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2178
2179        ["deny", '=' | IPs] ->
2180            Auth1 = case Auth#auth.acl of
2181                        none ->
2182                            DenyIPs = parse_auth_ips(IPs, []),
2183                            Auth#auth{acl={[], DenyIPs, deny_allow}};
2184                        {_, all, _} ->
2185                            Auth;
2186                        {AllowIPs, DenyIPs, Order} ->
2187                            DenyIPs1 = parse_auth_ips(IPs, []) ++ DenyIPs,
2188                            Auth#auth{acl={AllowIPs, DenyIPs1, Order}}
2189                    end,
2190            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2191            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2192
2193        ["order", '=', "allow", ',', "deny"] ->
2194            Auth1 = case Auth#auth.acl of
2195                        none    -> Auth#auth{acl={[], [], allow_deny}};
2196                        {A,D,_} -> Auth#auth{acl={A, D, allow_deny}}
2197                    end,
2198            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2199            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2200
2201        ["order", '=', "deny", ',', "allow"] ->
2202            Auth1 = case Auth#auth.acl of
2203                        none    -> Auth#auth{acl={[], [], deny_allow}};
2204                        {A,D,_} -> Auth#auth{acl={A, D, deny_allow}}
2205                    end,
2206            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2207            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2208
2209        ["pam", "service", '=', Serv] ->
2210            Auth1 = Auth#auth{pam=Serv},
2211            C1 = C#sconf{authdirs=[Auth1|AuthDirs]},
2212            fload(FD, server_auth, GC, C1, Lno+1, ?NEXTLINE);
2213
2214        ['<', "/auth", '>'] ->
2215            Pam = Auth#auth.pam,
2216            Users = Auth#auth.users,
2217            Realm = Auth#auth.realm,
2218            Auth1 =  case {Pam, Users} of
2219                         {false, []} ->
2220                             Auth;
2221                         _ ->
2222                             H = Auth#auth.headers ++
2223                                 yaws:make_www_authenticate_header({realm, Realm}),
2224                             Auth#auth{headers = H}
2225                     end,
2226            AuthDirs1 = case Auth1#auth.dir of
2227                            [] -> [Auth1#auth{dir="/"}|AuthDirs];
2228                            Ds -> [Auth1#auth{dir=D} || D <- Ds] ++ AuthDirs
2229                        end,
2230            C1 = C#sconf{authdirs=AuthDirs1},
2231            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
2232
2233        [H|T] ->
2234            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2235        Err ->
2236            Err
2237    end;
2238
2239fload(FD, server_redirect, GC, C, Lno, Chars) ->
2240    RedirMap = C#sconf.redirect_map,
2241    case toks(Lno, Chars) of
2242        [] ->
2243            fload(FD, server_redirect, GC, C, Lno+1, ?NEXTLINE);
2244
2245        [Path, '=', '=' | Rest] ->
2246            %% "Normalize" Path
2247            Path1 = filename:join([yaws_api:path_norm(Path)]),
2248            case parse_redirect(Path1, Rest, noappend, Lno) of
2249                {error, Str} ->
2250                    {error, Str};
2251                Redir ->
2252                    C1 = C#sconf{redirect_map=RedirMap ++ [Redir]},
2253                    fload(FD, server_redirect, GC, C1, Lno+1, ?NEXTLINE)
2254            end;
2255
2256        [Path, '=' | Rest] ->
2257            %% "Normalize" Path
2258            Path1 = filename:join([yaws_api:path_norm(Path)]),
2259            case parse_redirect(Path1, Rest, append, Lno) of
2260                {error, Str} ->
2261                    {error, Str};
2262                Redir ->
2263                    C1 = C#sconf{redirect_map=RedirMap ++ [Redir]},
2264                    fload(FD, server_redirect, GC, C1, Lno+1, ?NEXTLINE)
2265            end;
2266
2267        ['<', "/redirect", '>'] ->
2268            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
2269
2270        [H|T] ->
2271            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2272        Err ->
2273            Err
2274    end;
2275
2276fload(FD, server_deflate, GC, C, Lno, Chars) ->
2277    Deflate = C#sconf.deflate_options,
2278    case toks(Lno, Chars) of
2279        [] ->
2280            fload(FD, server_deflate, GC, C, Lno+1, ?NEXTLINE);
2281
2282        ["min_compress_size", '=', CSize] ->
2283            case (catch list_to_integer(CSize)) of
2284                I when is_integer(I), I > 0 ->
2285                    Deflate1 = Deflate#deflate{min_compress_size=I},
2286                    C1 = C#sconf{deflate_options=Deflate1},
2287                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2288                _ when CSize == "nolimit" ->
2289                    Deflate1 = Deflate#deflate{min_compress_size=nolimit},
2290                    C1 = C#sconf{deflate_options=Deflate1},
2291                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2292                _ ->
2293                    {error, ?F("Expect integer > 0 at line ~w", [Lno])}
2294            end;
2295
2296        ["mime_types", '=' | MimeTypes] ->
2297            case parse_compressible_mime_types(MimeTypes,
2298                                               Deflate#deflate.mime_types) of
2299                {ok, L} ->
2300                    Deflate1 = Deflate#deflate{mime_types=L},
2301                    C1 = C#sconf{deflate_options=Deflate1},
2302                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2303                {error, Str} ->
2304                    {error, ?F("~s at line ~w", [Str, Lno])}
2305            end;
2306
2307        ["compression_level", '=', CLevel] ->
2308            L = try
2309                    list_to_integer(CLevel)
2310                catch error:badarg ->
2311                        list_to_atom(CLevel)
2312                end,
2313            if
2314                L =:= none; L =:= default;
2315                L =:= best_compression; L =:= best_speed ->
2316                    Deflate1 = Deflate#deflate{compression_level=L},
2317                    C1 = C#sconf{deflate_options=Deflate1},
2318                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2319                is_integer(L), L >= 0, L =< 9 ->
2320                    Deflate1 = Deflate#deflate{compression_level=L},
2321                    C1 = C#sconf{deflate_options=Deflate1},
2322                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2323                true ->
2324                    {error, ?F("Bad compression level at line ~w", [Lno])}
2325            end;
2326
2327        ["window_size", '=', WSize] ->
2328            case (catch list_to_integer(WSize)) of
2329                I when is_integer(I), I > 8, I < 16 ->
2330                    Deflate1 = Deflate#deflate{window_size=I * -1},
2331                    C1 = C#sconf{deflate_options=Deflate1},
2332                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2333                _ ->
2334                    {error,
2335                     ?F("Expect integer between 9..15 at line ~w",
2336                        [Lno])}
2337            end;
2338
2339        ["mem_level", '=', MLevel] ->
2340            case (catch list_to_integer(MLevel)) of
2341                I when is_integer(I), I >= 1, I =< 9 ->
2342                    Deflate1 = Deflate#deflate{mem_level=I},
2343                    C1 = C#sconf{deflate_options=Deflate1},
2344                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2345                _ ->
2346                    {error, ?F("Expect integer between 1..9 at line ~w", [Lno])}
2347            end;
2348
2349        ["strategy", '=', Strategy] ->
2350            if
2351                Strategy =:= "default";
2352                Strategy =:= "filtered";
2353                Strategy =:= "huffman_only" ->
2354                    Deflate1 = Deflate#deflate{strategy=list_to_atom(Strategy)},
2355                    C1 = C#sconf{deflate_options=Deflate1},
2356                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2357                true ->
2358                    {error,
2359                     ?F("Unknown strategy ~p at line ~w", [Strategy, Lno])}
2360            end;
2361
2362        ["use_gzip_static", '=', Bool] ->
2363            case is_bool(Bool) of
2364                {true, Val} ->
2365                    Deflate1 = Deflate#deflate{use_gzip_static=Val},
2366                    C1 = C#sconf{deflate_options=Deflate1},
2367                    fload(FD, server_deflate, GC, C1, Lno+1, ?NEXTLINE);
2368                false ->
2369                    {error, ?F("Expect true|false at line ~w", [Lno])}
2370            end;
2371
2372        ['<', "/deflate", '>'] ->
2373            Deflate1 = case Deflate#deflate.mime_types of
2374                           [] ->
2375                               Deflate#deflate{
2376                                 mime_types = ?DEFAULT_COMPRESSIBLE_MIME_TYPES
2377                                };
2378                           _ ->
2379                               Deflate
2380                       end,
2381            C1 = C#sconf{deflate_options = Deflate1},
2382            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
2383
2384        [H|T] ->
2385            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2386        Err ->
2387            Err
2388    end;
2389
2390fload(FD, extra_cgi_vars, GC, C, Lno, Chars) ->
2391    [{Dir, Vars}|EVars] = C#sconf.extra_cgi_vars,
2392    case toks(Lno, Chars) of
2393        [] ->
2394            fload(FD, extra_cgi_vars, GC, C, Lno+1, ?NEXTLINE);
2395
2396        [Var, '=', Val] ->
2397            C1 = C#sconf{extra_cgi_vars=[{Dir, [{Var, Val} | Vars]}|EVars]},
2398            fload(FD, extra_cgi_vars, GC, C1, Lno+1, ?NEXTLINE);
2399
2400        ['<', "/extra_cgi_vars", '>'] ->
2401            C1 = C#sconf{extra_cgi_vars = [EVars | C#sconf.extra_cgi_vars]},
2402            fload(FD, server, GC, C1, Lno+1, ?NEXTLINE);
2403
2404        [H|T] ->
2405            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2406        Err ->
2407            Err
2408    end;
2409
2410fload(FD, rss, GC, C, Lno, Chars) ->
2411    case toks(Lno, Chars) of
2412        [] ->
2413            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2414
2415        ["rss_id", '=', Value] ->   % mandatory !!
2416            put(rss_id, list_to_atom(Value)),
2417            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2418
2419        ["rss_dir", '=', Value] ->   % mandatory !!
2420            put(rss, [{db_dir, Value} | get(rss)]),
2421            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2422
2423        ["rss_expire", '=', Value] ->
2424            put(rss, [{expire, Value} | get(rss)]),
2425            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2426
2427        ["rss_days", '=', Value] ->
2428            put(rss, [{days, Value} | get(rss)]),
2429            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2430
2431        ["rss_rm_exp", '=', Value] ->
2432            put(rss, [{rm_exp, Value} | get(rss)]),
2433            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2434
2435        ["rss_max", '=', Value] ->
2436            put(rss, [{rm_max, Value} | get(rss)]),
2437            fload(FD, rss, GC, C, Lno+1, ?NEXTLINE);
2438
2439        ['<', "/rss", '>'] ->
2440            case get(rss_id) of
2441                undefined ->
2442                    {error, ?F("No rss_id specified at line ~w", [Lno])};
2443                RSSid ->
2444                    yaws_rss:open(RSSid, get(rss)),
2445                    fload(FD, server, GC, C, Lno+1, ?NEXTLINE)
2446            end;
2447
2448        [H|T] ->
2449            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2450        Err ->
2451            Err
2452    end;
2453
2454fload(FD, opaque, GC, C, Lno, Chars) ->
2455    case toks(Lno, Chars) of
2456        [] ->
2457            fload(FD, opaque, GC, C, Lno+1, ?NEXTLINE);
2458
2459        [Key, '=', Value] ->
2460            C1 = C#sconf{opaque = [{Key,Value} | C#sconf.opaque]},
2461            fload(FD, opaque, GC, C1, Lno+1, ?NEXTLINE);
2462
2463        [Key, '='| Value] ->
2464            String_value = lists:flatten(
2465                             lists:map(
2466                               fun(Item) when is_atom(Item) ->
2467                                       atom_to_list(Item);
2468                                  (Item) ->
2469                                       Item
2470                               end, Value)),
2471            C1 = C#sconf{opaque = [{Key, String_value} | C#sconf.opaque]},
2472            fload(FD, opaque, GC, C1, Lno+1, ?NEXTLINE);
2473
2474        ['<', "/opaque", '>'] ->
2475            fload(FD, server, GC, C, Lno+1, ?NEXTLINE);
2476
2477        [H|T] ->
2478            {error, ?F("Unexpected input ~p at line ~w", [[H|T], Lno])};
2479        Err ->
2480            Err
2481    end.
2482
2483
2484is_bool("true") ->
2485    {true, true};
2486is_bool("false") ->
2487    {true, false};
2488is_bool(_) ->
2489    false.
2490
2491
2492warn_dir(Type, Dir) ->
2493    case is_dir(Dir) of
2494        true ->
2495            true;
2496        false ->
2497            error_logger:format("Config Warning: Directory ~s "
2498                                "for ~s doesn't exist~n",
2499                                [Dir, Type]),
2500            false
2501    end.
2502
2503is_dir(Val) ->
2504    case file:read_file_info(Val) of
2505        {ok, FI} when FI#file_info.type == directory ->
2506            true;
2507        _ ->
2508            false
2509    end.
2510
2511
2512is_file(Val) ->
2513    case file:read_file_info(Val) of
2514        {ok, FI} when FI#file_info.type == regular ->
2515            true;
2516        _ ->
2517            false
2518    end.
2519
2520is_wildcard(Val) ->
2521    (lists:member($*, Val) orelse
2522     lists:member($?, Val) orelse
2523     (lists:member($[, Val) andalso lists:member($], Val)) orelse
2524     (lists:member(${, Val) andalso lists:member($}, Val))).
2525
2526
2527%% tokenizer
2528toks(Lno, Chars) ->
2529    toks(Lno, Chars, free, [], []). % two accumulators
2530
2531toks(Lno, [$#|_T], Mode, Ack, Tack) ->
2532    toks(Lno, [], Mode, Ack, Tack);
2533
2534toks(Lno, [H|T], free, Ack, Tack) ->
2535    %%?Debug("Char=~p", [H]),
2536    case {is_quote(H), is_string_char([H|T]),is_special(H), yaws:is_space(H)} of
2537        {_,_, _, true} ->
2538            toks(Lno, T, free, Ack, Tack);
2539        {_,_, true, _} ->
2540            toks(Lno, T, free, [], [list_to_atom([H]) | Tack]);
2541        {_,true, _,_} ->
2542            toks(Lno, T, string, [H], Tack);
2543        {_,utf8, _,_} ->
2544            toks(Lno, tl(T), string, [H, hd(T)], Tack);
2545        {true,_, _,_} ->
2546            toks(Lno, T, quote, [], Tack);
2547        {false, false, false, false} ->
2548            {error, ?F("Unexpected character  <~p / ~c> at line ~w",
2549                       [H,H, Lno])}
2550    end;
2551toks(Lno, [C|T], string, Ack, Tack) ->
2552    case {is_backquote(C), is_quote(C), is_string_char([C|T]), is_special(C),
2553          yaws:is_space(C)} of
2554        {true, _, _, _,_} ->
2555            toks(Lno, T, [backquote,string], Ack, Tack);
2556        {_, _, true, _,_} ->
2557            toks(Lno, T, string, [C|Ack], Tack);
2558        {_, _, utf8, _,_} ->
2559            toks(Lno, tl(T), string, [C, hd(T)|Ack], Tack);
2560        {_, _, _, true, _} ->
2561            toks(Lno, T, free, [], [list_to_atom([C]),lists:reverse(Ack)|Tack]);
2562        {_, true, _, _, _} ->
2563            toks(Lno, T, quote, [], [lists:reverse(Ack)|Tack]);
2564        {_, _, _, _, true} ->
2565            toks(Lno, T, free, [], [lists:reverse(Ack)|Tack]);
2566        {false, false, false, false, false} ->
2567            {error, ?F("Unexpected character  <~p / ~c> at line ~w",
2568                       [C, C, Lno])}
2569    end;
2570toks(Lno, [C|T], quote, Ack, Tack) ->
2571    case {is_quote(C), is_backquote(C)} of
2572        {true, _} ->
2573            toks(Lno, T, free, [], [lists:reverse(Ack)|Tack]);
2574        {_, true} ->
2575            toks(Lno, T, [backquote,quote], [C|Ack], Tack);
2576        {false, false} ->
2577            toks(Lno, T, quote, [C|Ack], Tack)
2578    end;
2579toks(Lno, [C|T], [backquote,Mode], Ack, Tack) ->
2580    toks(Lno, T, Mode, [C|Ack], Tack);
2581toks(_Lno, [], string, Ack, Tack) ->
2582    lists:reverse([lists:reverse(Ack) | Tack]);
2583toks(_Lno, [], free, _,Tack) ->
2584    lists:reverse(Tack).
2585
2586is_quote(34) -> true ;  %% $" but emacs mode can't handle it
2587is_quote(_)  -> false.
2588
2589is_backquote($\\) -> true ;
2590is_backquote(_)  -> false.
2591
2592is_string_char([C|T]) ->
2593    if
2594        $a =< C, C =< $z ->
2595            true;
2596        $A =< C, C =< $Z ->
2597            true;
2598        $0 =< C, C =< $9 ->
2599            true;
2600        C == 195 , T /= [] ->
2601            %% FIXME check that [C, hd(T)] really is a char ?? how
2602            utf8;
2603        true ->
2604            lists:member(C, [$., $/, $:, $_, $-, $+, $~, $@, $*, $?])
2605    end.
2606
2607is_special(C) ->
2608    lists:member(C, [$=, $[, $], ${, $}, $, ,$<, $>, $,]).
2609
2610%% parse the argument string PLString which can either be the undefined
2611%% atom or a proplist. Currently the only supported keys are
2612%% fullsweep_after, min_heap_size, and min_bin_vheap_size. Any other
2613%% key/values are ignored.
2614parse_process_options(PLString) ->
2615    case erl_scan:string(PLString ++ ".") of
2616        {ok, PLTokens, _} ->
2617            case erl_parse:parse_term(PLTokens) of
2618                {ok, undefined} ->
2619                    {ok, []};
2620                {ok, []} ->
2621                    {ok, []};
2622                {ok, [Hd|_Tl]=PList} when is_atom(Hd); is_tuple(Hd) ->
2623                    %% create new safe proplist of desired options
2624                    {ok, proplists_int_copy([], PList, [fullsweep_after,
2625                                                        min_heap_size,
2626                                                        min_bin_vheap_size])};
2627                _ ->
2628                    {error, "Expect undefined or proplist"}
2629            end;
2630        _ ->
2631            {error, "Expect undefined or proplist"}
2632    end.
2633
2634%% copy proplist integer values for the given keys from the
2635%% Src proplist to the Dest proplist. Ignored keys that are not
2636%% found or have non-integer values. Returns the new Dest proplist.
2637proplists_int_copy(Dest, _Src, []) ->
2638    Dest;
2639proplists_int_copy(Dest, Src, [Key|NextKeys]) ->
2640    case proplists:get_value(Key, Src) of
2641        Val when is_integer(Val) ->
2642            proplists_int_copy([{Key, Val}|Dest], Src, NextKeys);
2643        _ ->
2644            proplists_int_copy(Dest, Src, NextKeys)
2645    end.
2646
2647parse_soap_srv_mods(['<', Module, ',' , Handler, ',', WsdlFile, '>' | Tail],
2648                    Ack) ->
2649    case is_file(WsdlFile) of
2650        true ->
2651            S = { {list_to_atom(Module), list_to_atom(Handler)}, WsdlFile},
2652            parse_soap_srv_mods(Tail, [S |Ack]);
2653        false ->
2654            {error, ?F("Bad wsdl file ~p", [WsdlFile])}
2655    end;
2656
2657parse_soap_srv_mods(['<', Module, ',' , Handler, ',', WsdlFile, ',',
2658                     Prefix, '>' | Tail], Ack) ->
2659    case is_file(WsdlFile) of
2660        true ->
2661            S = { {list_to_atom(Module), list_to_atom(Handler)},
2662                  WsdlFile, Prefix},
2663            parse_soap_srv_mods(Tail, [S |Ack]);
2664        false ->
2665            {error, ?F("Bad wsdl file ~p", [WsdlFile])}
2666    end;
2667
2668parse_soap_srv_mods([ SoapSrvMod | _Tail], _Ack) ->
2669    {error, ?F("Bad soap_srv_mods syntax: ~p", [SoapSrvMod])};
2670
2671parse_soap_srv_mods([], Ack) ->
2672    {ok, Ack}.
2673
2674parse_appmods(['<', PathElem, ',' , AppMod, '>' | Tail], Ack) ->
2675    S = {PathElem , list_to_atom(AppMod)},
2676    parse_appmods(Tail, [S |Ack]);
2677
2678parse_appmods(['<', PathElem, ',' , AppMod, "exclude_paths" |Tail], Ack)->
2679    Paths = lists:takewhile(fun(X) -> X /= '>' end,
2680                            Tail),
2681    Tail2 = lists:dropwhile(fun(X) -> X /= '>' end,
2682                            Tail),
2683    Tail3 = tl(Tail2),
2684
2685    S = {PathElem , list_to_atom(AppMod), lists:map(
2686                                            fun(Str) ->
2687                                                    string:tokens(Str, "/")
2688                                            end, Paths)},
2689    parse_appmods(Tail3, [S |Ack]);
2690
2691
2692parse_appmods([AppMod | Tail], Ack) ->
2693    %% just some simpleminded test to catch syntax errors in the config
2694    case AppMod of
2695        [Char] ->
2696            case is_special(Char) of
2697                true ->
2698                    {error, "Bad appmod syntax"};
2699                false ->
2700                    S = {AppMod, list_to_atom(AppMod)},
2701                    parse_appmods(Tail, [S | Ack])
2702            end;
2703        _ ->
2704            S = {AppMod, list_to_atom(AppMod)},
2705            parse_appmods(Tail, [S | Ack])
2706    end;
2707
2708parse_appmods([], Ack) ->
2709    {ok, Ack}.
2710
2711
2712parse_revproxy([Prefix, Url]) ->
2713    parse_revproxy_url(Prefix, Url);
2714parse_revproxy([Prefix, Url, "intercept_mod", InterceptMod]) ->
2715    case parse_revproxy_url(Prefix, Url) of
2716        {ok, RP} ->
2717            {ok, RP#proxy_cfg{intercept_mod = list_to_atom(InterceptMod)}};
2718        Error ->
2719            Error
2720    end;
2721parse_revproxy([Prefix, Proto, '[', IPv6, ']', Rest, "intercept_mod", InterceptMod]) ->
2722    Url = Proto ++ "[" ++ IPv6 ++ "]" ++ Rest,
2723    parse_revproxy([Prefix, Url, "intercept_mod", InterceptMod]);
2724parse_revproxy([Prefix, Proto, '[', IPv6, ']', Rest]) ->
2725    Url = Proto ++ "[" ++ IPv6 ++ "]" ++ Rest,
2726    parse_revproxy([Prefix, Url]);
2727parse_revproxy(_Other) ->
2728    {error, syntax}.
2729
2730parse_revproxy_url(Prefix, Url) ->
2731    case (catch yaws_api:parse_url(Url)) of
2732        {'EXIT', _} ->
2733            {error, url};
2734        URL when URL#url.path == "/" ->
2735            P = case lists:reverse(Prefix) of
2736                    [$/|_Tail] ->
2737                        Prefix;
2738                    Other ->
2739                        lists:reverse(Other)
2740                end,
2741            {ok, #proxy_cfg{prefix=P, url=URL}};
2742        _URL ->
2743            {error, "Can't revproxy to a URL with a path "}
2744    end.
2745
2746
2747parse_expires(['<', MimeType, ',' , Expire, '>' | Tail], Acc) ->
2748    {EType, Value} =
2749        case string:tokens(Expire, "+") of
2750            ["always"] ->
2751                {always, 0};
2752            [Secs] ->
2753                {access, (catch list_to_integer(Secs))};
2754            ["access", Secs] ->
2755                {access, (catch list_to_integer(Secs))};
2756            ["modify", Secs] ->
2757                {modify, (catch list_to_integer(Secs))};
2758            _ ->
2759                {error, "Bad expires syntax"}
2760        end,
2761    if
2762        EType =:= error ->
2763            {EType, Value};
2764        not is_integer(Value) ->
2765            {error, "Bad expires syntax"};
2766        true ->
2767            case parse_mime_type(MimeType) of
2768                {ok, "*", "*"} ->
2769                    E = {all, EType, Value},
2770                    parse_expires(Tail, [E |Acc]);
2771                {ok, Type, "*"} ->
2772                    E = {{Type, all}, EType, Value},
2773                    parse_expires(Tail, [E |Acc]);
2774                {ok, _Type, _SubType} ->
2775                    E = {MimeType, EType, Value},
2776                    parse_expires(Tail, [E |Acc]);
2777                Error ->
2778                    Error
2779            end
2780    end;
2781parse_expires([], Acc)->
2782    {ok, Acc}.
2783
2784
2785parse_phpmod(['<', "cgi", ',', DefaultPhpPath, '>'], DefaultPhpPath) ->
2786    {ok, {cgi, DefaultPhpPath}};
2787parse_phpmod(['<', "cgi", ',', PhpPath, '>'], _) ->
2788    case is_file(PhpPath) of
2789        true ->
2790            {ok, {cgi, PhpPath}};
2791        false ->
2792            {error, ?F("~s is not a regular file", [PhpPath])}
2793    end;
2794parse_phpmod(['<', "fcgi", ',', HostPortSpec, '>'], _) ->
2795    case string_to_host_and_port(HostPortSpec) of
2796        {ok, Host, Port} ->
2797            {ok, {fcgi, {Host, Port}}};
2798        {error, Reason} ->
2799            {error, Reason}
2800    end;
2801parse_phpmod(['<', "fcgi", ',', '[', HostSpec, ']', PortSpec, '>'], _) ->
2802    case string_to_host_and_port("[" ++ HostSpec ++ "]" ++ PortSpec) of
2803        {ok, Host, Port} ->
2804            {ok, {fcgi, {Host, Port}}};
2805        {error, Reason} ->
2806            {error, Reason}
2807    end;
2808parse_phpmod(['<', "extern", ',', NodeModFunSpec, '>'], _) ->
2809    case string_to_node_mod_fun(NodeModFunSpec) of
2810        {ok, Node, Mod, Fun} ->
2811            {ok, {extern, {Node,Mod,Fun}}};
2812        {ok, Mod, Fun} ->
2813            {ok, {extern, {Mod,Fun}}};
2814        {error, Reason} ->
2815            {error, Reason}
2816    end.
2817
2818
2819parse_compressible_mime_types(_, all) ->
2820    {ok, all};
2821parse_compressible_mime_types(["all"|_], _Acc) ->
2822    {ok, all};
2823parse_compressible_mime_types(["defaults"|Rest], Acc) ->
2824    parse_compressible_mime_types(Rest, ?DEFAULT_COMPRESSIBLE_MIME_TYPES++Acc);
2825parse_compressible_mime_types([',' | Rest], Acc) ->
2826    parse_compressible_mime_types(Rest, Acc);
2827parse_compressible_mime_types([MimeType | Rest], Acc) ->
2828    case parse_mime_type(MimeType) of
2829        {ok, "*", "*"} ->
2830            {ok, all};
2831        {ok, Type, "*"} ->
2832            parse_compressible_mime_types(Rest, [{Type, all}|Acc]);
2833        {ok, Type, SubType} ->
2834            parse_compressible_mime_types(Rest, [{Type, SubType}|Acc]);
2835        Error ->
2836            Error
2837    end;
2838parse_compressible_mime_types([], Acc) ->
2839    {ok, Acc}.
2840
2841
2842parse_mime_type(MimeType) ->
2843    Res = re:run(MimeType, "^([-\\w\+]+|\\*)/([-\\w\+\.]+|\\*)$",
2844                 [{capture, all_but_first, list}]),
2845    case Res of
2846        {match, [Type,SubType]} ->
2847            {ok, Type, SubType};
2848        nomatch ->
2849            {error, "Invalid MimeType"}
2850    end.
2851
2852
2853parse_index_files([]) ->
2854    ok;
2855parse_index_files([Idx|Rest]) ->
2856    case Idx of
2857        [$/|_] when Rest /= [] ->
2858            {error, "Only the last index should be absolute"};
2859        _ ->
2860            parse_index_files(Rest)
2861    end.
2862
2863is_valid_mime_type(MimeType) ->
2864    case re:run(MimeType, "^[-\\w\+]+/[-\\w\+\.]+$", [{capture, none}]) of
2865        match   -> true;
2866        nomatch -> false
2867    end.
2868
2869parse_mime_types(['<', MimeType, ',' | Tail], Acc0) ->
2870    Exts      = lists:takewhile(fun(X) -> X /= '>' end, Tail),
2871    [_|Tail2] = lists:dropwhile(fun(X) -> X /= '>' end, Tail),
2872    Acc1 = lists:foldl(fun(E, Acc) ->
2873                               lists:keystore(E, 1, Acc, {E, MimeType})
2874                       end, Acc0, Exts),
2875    case is_valid_mime_type(MimeType) of
2876        true  -> parse_mime_types(Tail2, Acc1);
2877        false -> {error, ?F("Invalid mime-type '~p'", [MimeType])}
2878    end;
2879parse_mime_types([], Acc)->
2880    {ok, lists:reverse(Acc)};
2881parse_mime_types(_, _) ->
2882    {error, "Unexpected tokens"}.
2883
2884parse_charsets(['<', Charset, ',' | Tail], Acc0) ->
2885    Exts      = lists:takewhile(fun(X) -> X /= '>' end, Tail),
2886    [_|Tail2] = lists:dropwhile(fun(X) -> X /= '>' end, Tail),
2887    Acc1 = lists:foldl(fun(E, Acc) ->
2888                               lists:keystore(E, 1, Acc, {E, Charset})
2889                       end, Acc0, Exts),
2890    parse_charsets(Tail2, Acc1);
2891parse_charsets([], Acc)->
2892    {ok, lists:reverse(Acc)};
2893parse_charsets(_, _) ->
2894    {error, "Unexpected tokens"}.
2895
2896
2897parse_mime_types_info(Directive, Type, undefined, undefined) ->
2898    parse_mime_types_info(Directive, Type, #mime_types_info{});
2899parse_mime_types_info(Directive, Type, undefined, DefaultInfo) ->
2900    parse_mime_types_info(Directive, Type, DefaultInfo);
2901parse_mime_types_info(Directive, Type, Info, _) ->
2902    parse_mime_types_info(Directive, Type, Info).
2903
2904parse_mime_types_info(default_type, Type, Info) ->
2905    case is_valid_mime_type(Type) of
2906        true  -> {ok, Info#mime_types_info{default_type=Type}};
2907        false -> {error, ?F("Invalid mime-type '~p'", [Type])}
2908    end;
2909parse_mime_types_info(default_charset, Charset, Info) ->
2910    {ok, Info#mime_types_info{default_charset=Charset}};
2911parse_mime_types_info(mime_types_file, File, Info) ->
2912    {ok, Info#mime_types_info{mime_types_file=File}};
2913parse_mime_types_info(add_types, NewTypes, Info) ->
2914    case parse_mime_types(NewTypes, Info#mime_types_info.types) of
2915        {ok, Types} -> {ok, Info#mime_types_info{types=Types}};
2916        Error       -> Error
2917    end;
2918parse_mime_types_info(add_charsets, NewCharsets, Info) ->
2919    case parse_charsets(NewCharsets, Info#mime_types_info.charsets) of
2920        {ok, Charsets} -> {ok, Info#mime_types_info{charsets=Charsets}};
2921        Error          -> Error
2922    end.
2923
2924
2925parse_nslookup_pref(Pref) ->
2926    parse_nslookup_pref(Pref, []).
2927
2928parse_nslookup_pref(Empty, []) when Empty == [] orelse Empty == ['[', ']'] ->
2929    %% Get default value, if nslookup_pref = [].
2930    {ok, yaws:gconf_nslookup_pref(#gconf{})};
2931parse_nslookup_pref([C, Family | Rest], Result)
2932  when C == '[' orelse C == ',' ->
2933    case Family of
2934        "inet" ->
2935            case lists:member(inet, Result) of
2936                false -> parse_nslookup_pref(Rest, [inet | Result]);
2937                true  -> parse_nslookup_pref(Rest, Result)
2938            end;
2939        "inet6" ->
2940            case lists:member(inet6, Result) of
2941                false -> parse_nslookup_pref(Rest, [inet6 | Result]);
2942                true  -> parse_nslookup_pref(Rest, Result)
2943            end;
2944        _ ->
2945            case Result of
2946                [PreviousFamily | _] ->
2947                    {error, ?F("Invalid nslookup_pref: invalid family or "
2948                        "token '~s', after family '~s'",
2949                        [Family, PreviousFamily])};
2950                [] ->
2951                    {error, ?F("Invalid nslookup_pref: invalid family or "
2952                        "token '~s'", [Family])}
2953            end
2954    end;
2955parse_nslookup_pref([']'], Result) ->
2956    {ok, lists:reverse(Result)};
2957parse_nslookup_pref([Invalid | _], []) ->
2958    {error, ?F("Invalid nslookup_pref: unexpected token '~s'", [Invalid])};
2959parse_nslookup_pref([Invalid | _], [Family | _]) ->
2960    {error, ?F("Invalid nslookup_pref: unexpected token '~s', "
2961        "after family '~s'", [Invalid, Family])}.
2962
2963
2964parse_redirect(Path, [Code, URL], Mode, Lno) ->
2965    case catch list_to_integer(Code) of
2966        I when is_integer(I), I >= 300, I =< 399 ->
2967            try yaws_api:parse_url(URL, sloppy) of
2968                U when is_record(U, url) ->
2969                    {Path, I, U, Mode}
2970            catch _:_ ->
2971                    {error, ?F("Bad redirect URL ~p at line ~w", [URL, Lno])}
2972            end;
2973        I when is_integer(I), I >= 100, I =< 599 ->
2974            %% Only relative path are authorized here
2975            try yaws_api:parse_url(URL, sloppy) of
2976                #url{scheme=undefined, host=[], port=undefined, path=P} ->
2977                    {Path, I, P, Mode};
2978                #url{} ->
2979                    {error, ?F("Bad redirect rule at line ~w: "
2980                               " Absolute URL is forbidden here", [Lno])}
2981            catch _:_ ->
2982                    {error, ?F("Bad redirect URL ~p at line ~w", [URL, Lno])}
2983            end;
2984        _ ->
2985            {error, ?F("Bad status code ~p at line ~w", [Code, Lno])}
2986    end;
2987parse_redirect(Path, [CodeOrUrl], Mode, Lno) ->
2988    case catch list_to_integer(CodeOrUrl) of
2989        I when is_integer(I), I >= 300, I =< 399 ->
2990            {error, ?F("Bad redirect rule at line ~w: "
2991                       "URL to redirect to is missing ", [Lno])};
2992        I when is_integer(I), I >= 100, I =< 599 ->
2993            {Path, I, undefined, Mode};
2994        I when is_integer(I) ->
2995            {error, ?F("Bad status code ~p at line ~w", [CodeOrUrl, Lno])};
2996        _ ->
2997            try yaws_api:parse_url(CodeOrUrl, sloppy) of
2998                #url{}=U ->
2999                    {Path, 302, U, Mode}
3000            catch _:_ ->
3001                    {error, ?F("Bad redirect URL ~p at line ~w",
3002                               [CodeOrUrl, Lno])}
3003            end
3004    end;
3005parse_redirect(_Path, _, _Mode, Lno) ->
3006    {error, ?F("Bad redirect rule at line ~w", [Lno])}.
3007
3008
3009ssl_start() ->
3010    case catch ssl:start() of
3011        ok ->
3012            ok;
3013        {error,{already_started,ssl}} ->
3014            ok;
3015        Err ->
3016            error_logger:format("Failed to start ssl: ~p~n", [Err])
3017    end.
3018
3019
3020
3021%% search for an SC within Pairs that have the same, listen,port,ssl,severname
3022%% Return {Pid, SC, Scs} or false
3023%% Pairs is the pairs in yaws_server #state{}
3024search_sconf(GC, NewSC, Pairs) ->
3025    case lists:zf(
3026           fun({Pid, Scs = [SC|_]}) ->
3027                   case same_virt_srv(GC, NewSC, SC) of
3028                       true ->
3029                           case lists:keysearch(NewSC#sconf.servername,
3030                                                #sconf.servername, Scs) of
3031                               {value, Found} ->
3032                                   {true, {Pid, Found, Scs}};
3033                               false ->
3034                                   false
3035                           end;
3036                       false ->
3037                           false
3038                   end
3039           end, Pairs) of
3040        [] ->
3041            false;
3042        [{Pid, Found, Scs}] ->
3043            {Pid, Found, Scs};
3044        _Other ->
3045            error_logger:format("Fatal error, no two sconfs should "
3046                                " ever be considered equal ..",[]),
3047            erlang:error(fatal_conf)
3048    end.
3049
3050%% find the group a new SC would belong to
3051search_group(GC, SC, Pairs) ->
3052    Fun =  fun({Pid, [S|Ss]}) ->
3053                   case same_virt_srv(GC, S, SC) of
3054                       true ->
3055                           {true, {Pid, [S|Ss]}};
3056                       false ->
3057                           false
3058                   end
3059           end,
3060
3061    lists:zf(Fun, Pairs).
3062
3063
3064%% Return a new Pairs list with one SC updated
3065update_sconf(Gc, NewSc, Pos, Pairs) ->
3066    lists:map(
3067      fun({Pid, Scs}) ->
3068              case same_virt_srv(Gc, hd(Scs), NewSc) of
3069                  true ->
3070                      L2 = lists:keydelete(NewSc#sconf.servername,
3071                                           #sconf.servername, Scs),
3072                      {Pid, yaws:insert_at(NewSc, Pos, L2)};
3073                  false ->
3074                      {Pid, Scs}
3075              end
3076      end, Pairs).
3077
3078
3079%% return a new pairs list with SC removed
3080delete_sconf(Gc, OldSc, Pairs) ->
3081    lists:zf(
3082      fun({Pid, Scs}) ->
3083              case same_virt_srv(Gc, hd(Scs), OldSc) of
3084                  true ->
3085                      L2 = lists:keydelete(OldSc#sconf.servername,
3086                                           #sconf.servername, Scs),
3087                      {true, {Pid, L2}};
3088                  false ->
3089                      {true, {Pid, Scs}}
3090              end
3091
3092      end, Pairs).
3093
3094
3095
3096same_virt_srv(Gc, S, NewSc) when S#sconf.listen == NewSc#sconf.listen,
3097                                 S#sconf.port == NewSc#sconf.port ->
3098    if
3099        Gc#gconf.sni == disable orelse
3100        S#sconf.ssl == undefined orelse
3101        NewSc#sconf.ssl == undefined ->
3102            (S#sconf.ssl == NewSc#sconf.ssl);
3103        true ->
3104            true
3105    end;
3106same_virt_srv(_,_,_) ->
3107    false.
3108
3109
3110eq_sconfs(S1,S2) ->
3111    (S1#sconf.port == S2#sconf.port andalso
3112     S1#sconf.flags == S2#sconf.flags andalso
3113     S1#sconf.redirect_map == S2#sconf.redirect_map andalso
3114     S1#sconf.rhost == S2#sconf.rhost andalso
3115     S1#sconf.rmethod == S2#sconf.rmethod andalso
3116     S1#sconf.docroot == S2#sconf.docroot andalso
3117     S1#sconf.xtra_docroots == S2#sconf.xtra_docroots andalso
3118     S1#sconf.listen == S2#sconf.listen andalso
3119     S1#sconf.servername == S2#sconf.servername andalso
3120     S1#sconf.yaws == S2#sconf.yaws andalso
3121     S1#sconf.ssl == S2#sconf.ssl andalso
3122     S1#sconf.authdirs == S2#sconf.authdirs andalso
3123     S1#sconf.partial_post_size == S2#sconf.partial_post_size andalso
3124     S1#sconf.appmods == S2#sconf.appmods andalso
3125     S1#sconf.expires == S2#sconf.expires andalso
3126     S1#sconf.errormod_401 == S2#sconf.errormod_401 andalso
3127     S1#sconf.errormod_404 == S2#sconf.errormod_404 andalso
3128     S1#sconf.errormod_crash == S2#sconf.errormod_crash andalso
3129     S1#sconf.arg_rewrite_mod == S2#sconf.arg_rewrite_mod andalso
3130     S1#sconf.logger_mod == S2#sconf.logger_mod andalso
3131     S1#sconf.opaque == S2#sconf.opaque andalso
3132     S1#sconf.start_mod == S2#sconf.start_mod andalso
3133     S1#sconf.allowed_scripts == S2#sconf.allowed_scripts andalso
3134     S1#sconf.tilde_allowed_scripts == S2#sconf.tilde_allowed_scripts andalso
3135     S1#sconf.index_files == S2#sconf.index_files andalso
3136     S1#sconf.revproxy == S2#sconf.revproxy andalso
3137     S1#sconf.soptions == S2#sconf.soptions andalso
3138     S1#sconf.extra_cgi_vars == S2#sconf.extra_cgi_vars andalso
3139     S1#sconf.stats == S2#sconf.stats andalso
3140     S1#sconf.fcgi_app_server == S2#sconf.fcgi_app_server andalso
3141     S1#sconf.php_handler == S2#sconf.php_handler andalso
3142     S1#sconf.shaper == S2#sconf.shaper andalso
3143     S1#sconf.deflate_options == S2#sconf.deflate_options andalso
3144     S1#sconf.mime_types_info == S2#sconf.mime_types_info).
3145
3146
3147
3148
3149%% This the version of setconf that perform a
3150%% soft reconfig, it requires the args to be checked.
3151soft_setconf(GC, Groups, OLDGC, OldGroups) ->
3152    if
3153        GC /= OLDGC ->
3154            yaws_trace:setup(GC),
3155            update_gconf(GC);
3156        true ->
3157            ok
3158    end,
3159    compile_and_load_src_dir(GC),
3160    Grps = load_mime_types_module(GC, Groups),
3161    Rems = remove_old_scs(GC, lists:flatten(OldGroups), Grps),
3162    Adds = soft_setconf_scs(GC, lists:flatten(Grps), 1, OldGroups),
3163    lists:foreach(
3164      fun({delete_sconf, SC}) ->
3165              delete_sconf(SC);
3166         ({add_sconf, N, SC}) ->
3167              add_sconf(N, SC);
3168         ({update_sconf, N, SC}) ->
3169              update_sconf(N, SC)
3170      end, Rems ++ Adds).
3171
3172
3173
3174hard_setconf(GC, Groups) ->
3175    gen_server:call(yaws_server,{setconf, GC, Groups}, infinity).
3176
3177
3178remove_old_scs(Gc, [Sc|Scs], NewGroups) ->
3179    case find_group(Gc, Sc, NewGroups) of
3180        false ->
3181            [{delete_sconf, Sc} |remove_old_scs(Gc, Scs, NewGroups)];
3182        {true, G} ->
3183            case find_sc(Sc, G) of
3184                false ->
3185                    [{delete_sconf, Sc} | remove_old_scs(Gc, Scs, NewGroups)];
3186                _ ->
3187                    remove_old_scs(Gc, Scs, NewGroups)
3188            end
3189    end;
3190remove_old_scs(_, [],_) ->
3191    [].
3192
3193soft_setconf_scs(Gc, [Sc|Scs], N, OldGroups) ->
3194    case find_group(Gc, Sc, OldGroups) of
3195        false ->
3196            [{add_sconf,N,Sc} | soft_setconf_scs(Gc, Scs, N+1, OldGroups)];
3197        {true, G} ->
3198            case find_sc(Sc, G) of
3199                false ->
3200                    [{add_sconf,N,Sc} | soft_setconf_scs(Gc, Scs,N+1,OldGroups)];
3201                {true, _OldSc} ->
3202                    [{update_sconf,N,Sc} | soft_setconf_scs(Gc, Scs,N+1,OldGroups)]
3203            end
3204    end;
3205soft_setconf_scs(_,[], _, _) ->
3206    [].
3207
3208
3209%% checking code
3210
3211can_hard_gc(New, Old) ->
3212    if
3213        Old == undefined ->
3214            true;
3215        New#gconf.yaws_dir == Old#gconf.yaws_dir,
3216        New#gconf.runmods == Old#gconf.runmods,
3217        New#gconf.logdir == Old#gconf.logdir ->
3218            true;
3219        true ->
3220            false
3221    end.
3222
3223
3224
3225can_soft_setconf(NEWGC, NewGroups, OLDGC, OldGroups) ->
3226    can_soft_gc(NEWGC, OLDGC) andalso
3227        can_soft_sconf(NEWGC, lists:flatten(NewGroups), OldGroups).
3228
3229can_soft_gc(G1, G2) ->
3230    if
3231        G1#gconf.flags == G2#gconf.flags,
3232        G1#gconf.logdir == G2#gconf.logdir,
3233        G1#gconf.log_wrap_size == G2#gconf.log_wrap_size,
3234        G1#gconf.sni == G2#gconf.sni,
3235        G1#gconf.id == G2#gconf.id ->
3236            true;
3237        true ->
3238            false
3239    end.
3240
3241
3242can_soft_sconf(Gc, [Sc|Scs], OldGroups) ->
3243    case find_group(Gc, Sc, OldGroups) of
3244        false ->
3245            can_soft_sconf(Gc, Scs, OldGroups);
3246        {true, G} ->
3247            case find_sc(Sc, G) of
3248                false ->
3249                    can_soft_sconf(Gc, Scs, OldGroups);
3250                {true, Old} when Old#sconf.start_mod /= Sc#sconf.start_mod ->
3251                    false;
3252                {true, Old} ->
3253                    case
3254                        {proplists:get_value(listen_opts, Old#sconf.soptions),
3255                         proplists:get_value(listen_opts, Sc#sconf.soptions)} of
3256                        {Opts, Opts} ->
3257                            can_soft_sconf(Gc, Scs, OldGroups);
3258                        _ ->
3259                            false
3260                    end
3261            end
3262    end;
3263can_soft_sconf(_, [], _) ->
3264    true.
3265
3266
3267find_group(GC, SC, [G|Gs]) ->
3268    case same_virt_srv(GC, SC, hd(G)) of
3269        true ->
3270            {true, G};
3271        false ->
3272            find_group(GC, SC, Gs)
3273    end;
3274find_group(_,_,[]) ->
3275    false.
3276
3277find_sc(SC, [S|Ss]) ->
3278    if SC#sconf.servername  == S#sconf.servername  ->
3279            {true, S};
3280       true ->
3281            find_sc(SC, Ss)
3282    end;
3283find_sc(_SC,[]) ->
3284    false.
3285
3286
3287verify_upgrade_args(GC, Groups0) when is_record(GC, gconf) ->
3288    SCs0 = lists:flatten(Groups0),
3289    case lists:all(fun(SC) -> is_record(SC, sconf) end, SCs0) of
3290        true ->
3291            %% Embedded code may give appmods as a list of strings, or
3292            %% appmods can be {StringPathElem,ModAtom} or
3293            %% {StringPathElem,ModAtom,ExcludePathsList} tuples. Handle
3294            %% all possible variants here.
3295            SCs1 = lists:map(
3296                     fun(SC) ->
3297                             SC#sconf{appmods =
3298                                          lists:map(
3299                                            fun({PE, Mod}) ->
3300                                                    {PE, Mod};
3301                                               ({PE,Mod,Ex}) ->
3302                                                    {PE,Mod,Ex};
3303                                               (AM) when is_list(AM) ->
3304                                                    {AM,list_to_atom(AM)};
3305                                               (AM) when is_atom(AM) ->
3306                                                    {atom_to_list(AM), AM}
3307                                            end,
3308                                            SC#sconf.appmods)}
3309                     end, SCs0),
3310            case catch validate_cs(GC, SCs1) of
3311                {ok, GC, Groups1} -> {GC, Groups1};
3312                {error, Reason}   -> erlang:error(Reason);
3313                _                 -> erlang:error(badgroups)
3314            end;
3315        false ->
3316            erlang:error(badgroups)
3317    end.
3318
3319
3320
3321add_sconf(SC) ->
3322    add_sconf(-1, SC).
3323
3324add_sconf(Pos, SC0) ->
3325    {ok, SC1} = gen_server:call(yaws_server, {add_sconf, Pos, SC0}, infinity),
3326    ok = yaws_log:add_sconf(SC1),
3327    {ok, SC1}.
3328
3329update_sconf(Pos, SC) ->
3330    gen_server:call(yaws_server, {update_sconf, Pos, SC}, infinity).
3331
3332delete_sconf(SC) ->
3333    ok = gen_server:call(yaws_server, {delete_sconf, SC}, infinity),
3334    ok = yaws_log:del_sconf(SC).
3335
3336update_gconf(GC) ->
3337    ok = gen_server:call(yaws_server, {update_gconf, GC}, infinity).
3338
3339
3340parse_auth_ips([], Result) ->
3341    Result;
3342parse_auth_ips([Str|Rest], Result) ->
3343    try
3344        parse_auth_ips(Rest, [yaws:parse_ipmask(Str)|Result])
3345    catch
3346        _:_ -> parse_auth_ips(Rest, Result)
3347    end.
3348
3349parse_auth_user(User, Lno) ->
3350    try
3351        [Name, Passwd] = string:tokens(User, ":"),
3352        case re:run(Passwd, "{([^}]+)}(?:\\$([^$]+)\\$)?(.+)", [{capture,all_but_first,list}]) of
3353            {match, [Algo, B64Salt, B64Hash]} ->
3354                case parse_auth_user(Name, Algo, B64Salt, B64Hash) of
3355                    {ok, Res} ->
3356                        Res;
3357                    {error, bad_algo} ->
3358                        {error, ?F("Unsupported hash algorithm '~p' at line ~w",
3359                                   [Algo, Lno])};
3360                    {error, bad_user} ->
3361                        {error, ?F("Invalid user at line ~w", [Lno])}
3362                end;
3363            _ ->
3364                Salt = crypto:strong_rand_bytes(32),
3365                {Name, sha256, Salt, crypto:hash(sha256, [Salt, Passwd])}
3366        end
3367    catch
3368        _:_ ->
3369            {error, ?F("Invalid user at line ~w", [Lno])}
3370    end.
3371
3372parse_auth_user(User, Algo, B64Salt, B64Hash) ->
3373    try
3374        if
3375            Algo == "md5"    orelse Algo == "sha"    orelse
3376            Algo == "sha224" orelse Algo == "sha256" orelse
3377            Algo == "sha384" orelse Algo == "sha512" orelse
3378            Algo == "ripemd160" ->
3379                Salt = base64:decode(B64Salt),
3380                Hash = base64:decode(B64Hash),
3381                {ok, {User, list_to_atom(Algo), Salt, Hash}};
3382            true ->
3383                {error, bad_algo}
3384        end
3385    catch
3386        _:_ -> {error, bad_user}
3387    end.
3388
3389
3390subconfigfiles(FD, Name, Lno) ->
3391    {ok, Config} = file:pid2name(FD),
3392    ConfPath = filename:dirname(filename:absname(Config)),
3393    File = filename:absname(Name, ConfPath),
3394    case {is_file(File), is_wildcard(Name)} of
3395        {true,_} ->
3396            {ok, [File]};
3397        {false,true} ->
3398            Names = filelib:wildcard(Name, ConfPath),
3399            Files = [filename:absname(N, ConfPath) || N <- lists:sort(Names)],
3400            {ok, lists:filter(fun filter_subconfigfile/1, Files)};
3401        {false,false} ->
3402            {error, ?F("Expect filename or wildcard at line ~w"
3403                       " (subconfig: ~s)", [Lno, Name])}
3404    end.
3405
3406subconfigdir(FD, Name, Lno) ->
3407    {ok, Config} = file:pid2name(FD),
3408    ConfPath = filename:dirname(filename:absname(Config)),
3409    Dir = filename:absname(Name, ConfPath),
3410    case is_dir(Dir) of
3411        true ->
3412            case file:list_dir(Dir) of
3413                {ok, Names} ->
3414                    Files = [filename:absname(N, Dir) || N <- lists:sort(Names)],
3415                    {ok, lists:filter(fun filter_subconfigfile/1, Files)};
3416                {error, Error} ->
3417                    {error, ?F("Directory ~s is not readable: ~s",
3418                               [Name, Error])}
3419            end;
3420        false ->
3421            {error, ?F("Expect directory at line ~w (subconfdir: ~s)",
3422                       [Lno, Dir])}
3423    end.
3424
3425filter_subconfigfile(File) ->
3426    case filename:basename(File) of
3427        [$.|_] ->
3428            error_logger:info_msg("Yaws: Ignore subconfig file ~s~n", [File]),
3429            false;
3430        _ ->
3431            true
3432    end.
3433
3434fload_subconfigfiles([], global, GC, Cs) ->
3435    {ok, GC, Cs};
3436fload_subconfigfiles([File|Files], global, GC, Cs) ->
3437    error_logger:info_msg("Yaws: Using global subconfig file ~s~n", [File]),
3438    case file:open(File, [read]) of
3439        {ok, FD} ->
3440            R = (catch fload(FD, GC, Cs, 1, ?NEXTLINE)),
3441            ?Debug("FLOAD(~s): ~p", [File, R]),
3442            case R of
3443                {ok, GC1, Cs1} -> fload_subconfigfiles(Files, global, GC1, Cs1);
3444                Err            -> Err
3445            end;
3446        Err ->
3447            {error, ?F("Can't open subconfig file ~s: ~p", [File,Err])}
3448    end;
3449fload_subconfigfiles([], server, GC, C) ->
3450    {ok, GC, C};
3451fload_subconfigfiles([File|Files], server, GC, C) ->
3452    error_logger:info_msg("Yaws: Using server subconfig file ~s~n", [File]),
3453    case file:open(File, [read]) of
3454        {ok, FD} ->
3455            R = (catch fload(FD, server, GC, C, 1, ?NEXTLINE)),
3456            ?Debug("FLOAD(~s): ~p", [File, R]),
3457            case R of
3458                {ok, GC1, C1, _, eof} ->
3459                    fload_subconfigfiles(Files, server, GC1, C1);
3460                {ok, _, _, Lno, ['<', "/server", '>']} ->
3461                    {error, ?F("Unexpected closing tag in subconfgile ~s"
3462                               " at line ~w ", [File, Lno])};
3463                Err ->
3464                    Err
3465            end;
3466        Err ->
3467            {error, ?F("Can't open subconfig file ~s: ~p", [File,Err])}
3468    end.
3469
3470
3471str2term(Str0) ->
3472    Str=Str0++".",
3473    {ok,Tokens,_EndLine} = erl_scan:string(Str),
3474    {ok,AbsForm} = erl_parse:parse_exprs(Tokens),
3475    {value,Value,_Bs} = erl_eval:exprs(AbsForm, erl_eval:new_bindings()),
3476    Value.
3477
3478check_ciphers([], _) ->
3479    ok;
3480check_ciphers([Spec|Specs], L) ->
3481    case lists:member(Spec, L) of
3482        true ->
3483            check_ciphers(Specs, L);
3484        false ->
3485            {error, ?F("Bad cipherspec ~p",[Spec])}
3486    end;
3487check_ciphers(X,_) ->
3488    {error, ?F("Bad cipherspec ~p",[X])}.
3489
3490
3491io_get_line(FD, Prompt, Acc) ->
3492    Next = io:get_line(FD, Prompt),
3493    if
3494        is_list(Next) ->
3495            case lists:reverse(Next) of
3496                [$\n, $\\ |More] ->
3497                    io_get_line(FD, Prompt, Acc ++ lists:reverse(More));
3498                _ ->
3499                    Acc ++ Next
3500            end;
3501        true ->
3502            Next
3503    end.
3504
3505update_soptions(SC, Name, Key, Value) ->
3506    Opts0 = proplists:get_value(Name, SC#sconf.soptions),
3507    Opts1 = lists:keystore(Key, 1, Opts0, {Key, Value}),
3508    SOpts = lists:keystore(Name, 1, SC#sconf.soptions, {Name, Opts1}),
3509    SC#sconf{soptions = SOpts}.
3510
3511
3512set_sendfile_flags(GC, "erlang") ->
3513    GC1 = ?gc_set_use_erlang_sendfile(GC, true),
3514    {ok, ?gc_set_use_yaws_sendfile(GC1, false)};
3515set_sendfile_flags(GC, "yaws") ->
3516    GC1 = ?gc_set_use_erlang_sendfile(GC, false),
3517    {ok, ?gc_set_use_yaws_sendfile(GC1, true)};
3518set_sendfile_flags(GC, "disable") ->
3519    GC1 = ?gc_set_use_erlang_sendfile(GC, false),
3520    {ok, ?gc_set_use_yaws_sendfile(GC1, false)};
3521set_sendfile_flags(_, _) ->
3522    {error, "Expect erlang|yaws|disable"}.
3523