1%% @author Bob Ippolito <bob@mochimedia.com>
2%% @copyright 2007 Mochi Media, Inc.
3
4%% @doc Utilities for parsing and quoting.
5
6-module(mochiweb_util).
7-author('bob@mochimedia.com').
8-export([join/2, quote_plus/1, urlencode/1, parse_qs/1, unquote/1]).
9-export([path_split/1]).
10-export([urlsplit/1, urlsplit_path/1, urlunsplit/1, urlunsplit_path/1]).
11-export([guess_mime/1, parse_header/1]).
12-export([shell_quote/1, cmd/1, cmd_string/1, cmd_port/2, cmd_status/1, cmd_status/2]).
13-export([record_to_proplist/2, record_to_proplist/3]).
14-export([safe_relative_path/1, partition/2]).
15-export([parse_qvalues/1, pick_accepted_encodings/3]).
16-export([make_io/1]).
17
18-define(PERCENT, 37).  % $\%
19-define(FULLSTOP, 46). % $\.
20-define(IS_HEX(C), ((C >= $0 andalso C =< $9) orelse
21                    (C >= $a andalso C =< $f) orelse
22                    (C >= $A andalso C =< $F))).
23-define(QS_SAFE(C), ((C >= $a andalso C =< $z) orelse
24                     (C >= $A andalso C =< $Z) orelse
25                     (C >= $0 andalso C =< $9) orelse
26                     (C =:= ?FULLSTOP orelse C =:= $- orelse C =:= $~ orelse
27                      C =:= $_))).
28
29hexdigit(C) when C < 10 -> $0 + C;
30hexdigit(C) when C < 16 -> $A + (C - 10).
31
32unhexdigit(C) when C >= $0, C =< $9 -> C - $0;
33unhexdigit(C) when C >= $a, C =< $f -> C - $a + 10;
34unhexdigit(C) when C >= $A, C =< $F -> C - $A + 10.
35
36%% @spec partition(String, Sep) -> {String, [], []} | {Prefix, Sep, Postfix}
37%% @doc Inspired by Python 2.5's str.partition:
38%%      partition("foo/bar", "/") = {"foo", "/", "bar"},
39%%      partition("foo", "/") = {"foo", "", ""}.
40partition(String, Sep) ->
41    case partition(String, Sep, []) of
42        undefined ->
43            {String, "", ""};
44        Result ->
45            Result
46    end.
47
48partition("", _Sep, _Acc) ->
49    undefined;
50partition(S, Sep, Acc) ->
51    case partition2(S, Sep) of
52        undefined ->
53            [C | Rest] = S,
54            partition(Rest, Sep, [C | Acc]);
55        Rest ->
56            {lists:reverse(Acc), Sep, Rest}
57    end.
58
59partition2(Rest, "") ->
60    Rest;
61partition2([C | R1], [C | R2]) ->
62    partition2(R1, R2);
63partition2(_S, _Sep) ->
64    undefined.
65
66
67
68%% @spec safe_relative_path(string()) -> string() | undefined
69%% @doc Return the reduced version of a relative path or undefined if it
70%%      is not safe. safe relative paths can be joined with an absolute path
71%%      and will result in a subdirectory of the absolute path. Safe paths
72%%      never contain a backslash character.
73safe_relative_path("/" ++ _) ->
74    undefined;
75safe_relative_path(P) ->
76    case string:chr(P, $\\) of
77        0 ->
78           safe_relative_path(P, []);
79        _ ->
80           undefined
81    end.
82
83safe_relative_path("", Acc) ->
84    case Acc of
85        [] ->
86            "";
87        _ ->
88            string:join(lists:reverse(Acc), "/")
89    end;
90safe_relative_path(P, Acc) ->
91    case partition(P, "/") of
92        {"", "/", _} ->
93            %% /foo or foo//bar
94            undefined;
95        {"..", _, _} when Acc =:= [] ->
96            undefined;
97        {"..", _, Rest} ->
98            safe_relative_path(Rest, tl(Acc));
99        {Part, "/", ""} ->
100            safe_relative_path("", ["", Part | Acc]);
101        {Part, _, Rest} ->
102            safe_relative_path(Rest, [Part | Acc])
103    end.
104
105%% @spec shell_quote(string()) -> string()
106%% @doc Quote a string according to UNIX shell quoting rules, returns a string
107%%      surrounded by double quotes.
108shell_quote(L) ->
109    shell_quote(L, [$\"]).
110
111%% @spec cmd_port([string()], Options) -> port()
112%% @doc open_port({spawn, mochiweb_util:cmd_string(Argv)}, Options).
113cmd_port(Argv, Options) ->
114    open_port({spawn, cmd_string(Argv)}, Options).
115
116%% @spec cmd([string()]) -> string()
117%% @doc os:cmd(cmd_string(Argv)).
118cmd(Argv) ->
119    os:cmd(cmd_string(Argv)).
120
121%% @spec cmd_string([string()]) -> string()
122%% @doc Create a shell quoted command string from a list of arguments.
123cmd_string(Argv) ->
124    string:join([shell_quote(X) || X <- Argv], " ").
125
126%% @spec cmd_status([string()]) -> {ExitStatus::integer(), Stdout::binary()}
127%% @doc Accumulate the output and exit status from the given application,
128%%      will be spawned with cmd_port/2.
129cmd_status(Argv) ->
130    cmd_status(Argv, []).
131
132%% @spec cmd_status([string()], [atom()]) -> {ExitStatus::integer(), Stdout::binary()}
133%% @doc Accumulate the output and exit status from the given application,
134%%      will be spawned with cmd_port/2.
135cmd_status(Argv, Options) ->
136    Port = cmd_port(Argv, [exit_status, stderr_to_stdout,
137                           use_stdio, binary | Options]),
138    try cmd_loop(Port, [])
139    after catch port_close(Port)
140    end.
141
142%% @spec cmd_loop(port(), list()) -> {ExitStatus::integer(), Stdout::binary()}
143%% @doc Accumulate the output and exit status from a port.
144cmd_loop(Port, Acc) ->
145    receive
146        {Port, {exit_status, Status}} ->
147            {Status, iolist_to_binary(lists:reverse(Acc))};
148        {Port, {data, Data}} ->
149            cmd_loop(Port, [Data | Acc])
150    end.
151
152%% @spec join([iolist()], iolist()) -> iolist()
153%% @doc Join a list of strings or binaries together with the given separator
154%%      string or char or binary. The output is flattened, but may be an
155%%      iolist() instead of a string() if any of the inputs are binary().
156join([], _Separator) ->
157    [];
158join([S], _Separator) ->
159    lists:flatten(S);
160join(Strings, Separator) ->
161    lists:flatten(revjoin(lists:reverse(Strings), Separator, [])).
162
163revjoin([], _Separator, Acc) ->
164    Acc;
165revjoin([S | Rest], Separator, []) ->
166    revjoin(Rest, Separator, [S]);
167revjoin([S | Rest], Separator, Acc) ->
168    revjoin(Rest, Separator, [S, Separator | Acc]).
169
170%% @spec quote_plus(atom() | integer() | float() | string() | binary()) -> string()
171%% @doc URL safe encoding of the given term.
172quote_plus(Atom) when is_atom(Atom) ->
173    quote_plus(atom_to_list(Atom));
174quote_plus(Int) when is_integer(Int) ->
175    quote_plus(integer_to_list(Int));
176quote_plus(Binary) when is_binary(Binary) ->
177    quote_plus(binary_to_list(Binary));
178quote_plus(Float) when is_float(Float) ->
179    quote_plus(mochinum:digits(Float));
180quote_plus(String) ->
181    quote_plus(String, []).
182
183quote_plus([], Acc) ->
184    lists:reverse(Acc);
185quote_plus([C | Rest], Acc) when ?QS_SAFE(C) ->
186    quote_plus(Rest, [C | Acc]);
187quote_plus([$\s | Rest], Acc) ->
188    quote_plus(Rest, [$+ | Acc]);
189quote_plus([C | Rest], Acc) ->
190    <<Hi:4, Lo:4>> = <<C>>,
191    quote_plus(Rest, [hexdigit(Lo), hexdigit(Hi), ?PERCENT | Acc]).
192
193%% @spec urlencode([{Key, Value}]) -> string()
194%% @doc URL encode the property list.
195urlencode(Props) ->
196    Pairs = lists:foldr(
197              fun ({K, V}, Acc) ->
198                      [quote_plus(K) ++ "=" ++ quote_plus(V) | Acc]
199              end, [], Props),
200    string:join(Pairs, "&").
201
202%% @spec parse_qs(string() | binary()) -> [{Key, Value}]
203%% @doc Parse a query string or application/x-www-form-urlencoded.
204parse_qs(Binary) when is_binary(Binary) ->
205    parse_qs(binary_to_list(Binary));
206parse_qs(String) ->
207    parse_qs(String, []).
208
209parse_qs([], Acc) ->
210    lists:reverse(Acc);
211parse_qs(String, Acc) ->
212    {Key, Rest} = parse_qs_key(String),
213    {Value, Rest1} = parse_qs_value(Rest),
214    parse_qs(Rest1, [{Key, Value} | Acc]).
215
216parse_qs_key(String) ->
217    parse_qs_key(String, []).
218
219parse_qs_key([], Acc) ->
220    {qs_revdecode(Acc), ""};
221parse_qs_key([$= | Rest], Acc) ->
222    {qs_revdecode(Acc), Rest};
223parse_qs_key(Rest=[$; | _], Acc) ->
224    {qs_revdecode(Acc), Rest};
225parse_qs_key(Rest=[$& | _], Acc) ->
226    {qs_revdecode(Acc), Rest};
227parse_qs_key([C | Rest], Acc) ->
228    parse_qs_key(Rest, [C | Acc]).
229
230parse_qs_value(String) ->
231    parse_qs_value(String, []).
232
233parse_qs_value([], Acc) ->
234    {qs_revdecode(Acc), ""};
235parse_qs_value([$; | Rest], Acc) ->
236    {qs_revdecode(Acc), Rest};
237parse_qs_value([$& | Rest], Acc) ->
238    {qs_revdecode(Acc), Rest};
239parse_qs_value([C | Rest], Acc) ->
240    parse_qs_value(Rest, [C | Acc]).
241
242%% @spec unquote(string() | binary()) -> string()
243%% @doc Unquote a URL encoded string.
244unquote(Binary) when is_binary(Binary) ->
245    unquote(binary_to_list(Binary));
246unquote(String) ->
247    qs_revdecode(lists:reverse(String)).
248
249qs_revdecode(S) ->
250    qs_revdecode(S, []).
251
252qs_revdecode([], Acc) ->
253    Acc;
254qs_revdecode([$+ | Rest], Acc) ->
255    qs_revdecode(Rest, [$\s | Acc]);
256qs_revdecode([Lo, Hi, ?PERCENT | Rest], Acc) when ?IS_HEX(Lo), ?IS_HEX(Hi) ->
257    qs_revdecode(Rest, [(unhexdigit(Lo) bor (unhexdigit(Hi) bsl 4)) | Acc]);
258qs_revdecode([C | Rest], Acc) ->
259    qs_revdecode(Rest, [C | Acc]).
260
261%% @spec urlsplit(Url) -> {Scheme, Netloc, Path, Query, Fragment}
262%% @doc Return a 5-tuple, does not expand % escapes. Only supports HTTP style
263%%      URLs.
264urlsplit(Url) ->
265    {Scheme, Url1} = urlsplit_scheme(Url),
266    {Netloc, Url2} = urlsplit_netloc(Url1),
267    {Path, Query, Fragment} = urlsplit_path(Url2),
268    {Scheme, Netloc, Path, Query, Fragment}.
269
270urlsplit_scheme(Url) ->
271    case urlsplit_scheme(Url, []) of
272        no_scheme ->
273            {"", Url};
274        Res ->
275            Res
276    end.
277
278urlsplit_scheme([C | Rest], Acc) when ((C >= $a andalso C =< $z) orelse
279                                       (C >= $A andalso C =< $Z) orelse
280                                       (C >= $0 andalso C =< $9) orelse
281                                       C =:= $+ orelse C =:= $- orelse
282                                       C =:= $.) ->
283    urlsplit_scheme(Rest, [C | Acc]);
284urlsplit_scheme([$: | Rest], Acc=[_ | _]) ->
285    {string:to_lower(lists:reverse(Acc)), Rest};
286urlsplit_scheme(_Rest, _Acc) ->
287    no_scheme.
288
289urlsplit_netloc("//" ++ Rest) ->
290    urlsplit_netloc(Rest, []);
291urlsplit_netloc(Path) ->
292    {"", Path}.
293
294urlsplit_netloc("", Acc) ->
295    {lists:reverse(Acc), ""};
296urlsplit_netloc(Rest=[C | _], Acc) when C =:= $/; C =:= $?; C =:= $# ->
297    {lists:reverse(Acc), Rest};
298urlsplit_netloc([C | Rest], Acc) ->
299    urlsplit_netloc(Rest, [C | Acc]).
300
301
302%% @spec path_split(string()) -> {Part, Rest}
303%% @doc Split a path starting from the left, as in URL traversal.
304%%      path_split("foo/bar") = {"foo", "bar"},
305%%      path_split("/foo/bar") = {"", "foo/bar"}.
306path_split(S) ->
307    path_split(S, []).
308
309path_split("", Acc) ->
310    {lists:reverse(Acc), ""};
311path_split("/" ++ Rest, Acc) ->
312    {lists:reverse(Acc), Rest};
313path_split([C | Rest], Acc) ->
314    path_split(Rest, [C | Acc]).
315
316
317%% @spec urlunsplit({Scheme, Netloc, Path, Query, Fragment}) -> string()
318%% @doc Assemble a URL from the 5-tuple. Path must be absolute.
319urlunsplit({Scheme, Netloc, Path, Query, Fragment}) ->
320    lists:flatten([case Scheme of "" -> "";  _ -> [Scheme, "://"] end,
321                   Netloc,
322                   urlunsplit_path({Path, Query, Fragment})]).
323
324%% @spec urlunsplit_path({Path, Query, Fragment}) -> string()
325%% @doc Assemble a URL path from the 3-tuple.
326urlunsplit_path({Path, Query, Fragment}) ->
327    lists:flatten([Path,
328                   case Query of "" -> ""; _ -> [$? | Query] end,
329                   case Fragment of "" -> ""; _ -> [$# | Fragment] end]).
330
331%% @spec urlsplit_path(Url) -> {Path, Query, Fragment}
332%% @doc Return a 3-tuple, does not expand % escapes. Only supports HTTP style
333%%      paths.
334urlsplit_path(Path) ->
335    urlsplit_path(Path, []).
336
337urlsplit_path("", Acc) ->
338    {lists:reverse(Acc), "", ""};
339urlsplit_path("?" ++ Rest, Acc) ->
340    {Query, Fragment} = urlsplit_query(Rest),
341    {lists:reverse(Acc), Query, Fragment};
342urlsplit_path("#" ++ Rest, Acc) ->
343    {lists:reverse(Acc), "", Rest};
344urlsplit_path([C | Rest], Acc) ->
345    urlsplit_path(Rest, [C | Acc]).
346
347urlsplit_query(Query) ->
348    urlsplit_query(Query, []).
349
350urlsplit_query("", Acc) ->
351    {lists:reverse(Acc), ""};
352urlsplit_query("#" ++ Rest, Acc) ->
353    {lists:reverse(Acc), Rest};
354urlsplit_query([C | Rest], Acc) ->
355    urlsplit_query(Rest, [C | Acc]).
356
357%% @spec guess_mime(string()) -> string()
358%% @doc  Guess the mime type of a file by the extension of its filename.
359guess_mime(File) ->
360    case filename:basename(File) of
361        "crossdomain.xml" ->
362            "text/x-cross-domain-policy";
363        Name ->
364            case mochiweb_mime:from_extension(filename:extension(Name)) of
365                undefined ->
366                    "text/plain";
367                Mime ->
368                    Mime
369            end
370    end.
371
372%% @spec parse_header(string()) -> {Type, [{K, V}]}
373%% @doc  Parse a Content-Type like header, return the main Content-Type
374%%       and a property list of options.
375parse_header(String) ->
376    %% TODO: This is exactly as broken as Python's cgi module.
377    %%       Should parse properly like mochiweb_cookies.
378    [Type | Parts] = [string:strip(S) || S <- string:tokens(String, ";")],
379    F = fun (S, Acc) ->
380                case lists:splitwith(fun (C) -> C =/= $= end, S) of
381                    {"", _} ->
382                        %% Skip anything with no name
383                        Acc;
384                    {_, ""} ->
385                        %% Skip anything with no value
386                        Acc;
387                    {Name, [$\= | Value]} ->
388                        [{string:to_lower(string:strip(Name)),
389                          unquote_header(string:strip(Value))} | Acc]
390                end
391        end,
392    {string:to_lower(Type),
393     lists:foldr(F, [], Parts)}.
394
395unquote_header("\"" ++ Rest) ->
396    unquote_header(Rest, []);
397unquote_header(S) ->
398    S.
399
400unquote_header("", Acc) ->
401    lists:reverse(Acc);
402unquote_header("\"", Acc) ->
403    lists:reverse(Acc);
404unquote_header([$\\, C | Rest], Acc) ->
405    unquote_header(Rest, [C | Acc]);
406unquote_header([C | Rest], Acc) ->
407    unquote_header(Rest, [C | Acc]).
408
409%% @spec record_to_proplist(Record, Fields) -> proplist()
410%% @doc calls record_to_proplist/3 with a default TypeKey of '__record'
411record_to_proplist(Record, Fields) ->
412    record_to_proplist(Record, Fields, '__record').
413
414%% @spec record_to_proplist(Record, Fields, TypeKey) -> proplist()
415%% @doc Return a proplist of the given Record with each field in the
416%%      Fields list set as a key with the corresponding value in the Record.
417%%      TypeKey is the key that is used to store the record type
418%%      Fields should be obtained by calling record_info(fields, record_type)
419%%      where record_type is the record type of Record
420record_to_proplist(Record, Fields, TypeKey)
421  when tuple_size(Record) - 1 =:= length(Fields) ->
422    lists:zip([TypeKey | Fields], tuple_to_list(Record)).
423
424
425shell_quote([], Acc) ->
426    lists:reverse([$\" | Acc]);
427shell_quote([C | Rest], Acc) when C =:= $\" orelse C =:= $\` orelse
428                                  C =:= $\\ orelse C =:= $\$ ->
429    shell_quote(Rest, [C, $\\ | Acc]);
430shell_quote([C | Rest], Acc) ->
431    shell_quote(Rest, [C | Acc]).
432
433%% @spec parse_qvalues(string()) -> [qvalue()] | invalid_qvalue_string
434%% @type qvalue() = {media_type() | encoding() , float()}.
435%% @type media_type() = string().
436%% @type encoding() = string().
437%%
438%% @doc Parses a list (given as a string) of elements with Q values associated
439%%      to them. Elements are separated by commas and each element is separated
440%%      from its Q value by a semicolon. Q values are optional but when missing
441%%      the value of an element is considered as 1.0. A Q value is always in the
442%%      range [0.0, 1.0]. A Q value list is used for example as the value of the
443%%      HTTP "Accept" and "Accept-Encoding" headers.
444%%
445%%      Q values are described in section 2.9 of the RFC 2616 (HTTP 1.1).
446%%
447%%      Example:
448%%
449%%      parse_qvalues("gzip; q=0.5, deflate, identity;q=0.0") ->
450%%          [{"gzip", 0.5}, {"deflate", 1.0}, {"identity", 0.0}]
451%%
452parse_qvalues(QValuesStr) ->
453    try
454        lists:map(
455            fun(Pair) ->
456                [Type | Params] = string:tokens(Pair, ";"),
457                NormParams = normalize_media_params(Params),
458                {Q, NonQParams} = extract_q(NormParams),
459                {string:join([string:strip(Type) | NonQParams], ";"), Q}
460            end,
461            string:tokens(string:to_lower(QValuesStr), ",")
462        )
463    catch
464        _Type:_Error ->
465            invalid_qvalue_string
466    end.
467
468normalize_media_params(Params) ->
469    {ok, Re} = re:compile("\\s"),
470    normalize_media_params(Re, Params, []).
471
472normalize_media_params(_Re, [], Acc) ->
473    lists:reverse(Acc);
474normalize_media_params(Re, [Param | Rest], Acc) ->
475    NormParam = re:replace(Param, Re, "", [global, {return, list}]),
476    normalize_media_params(Re, Rest, [NormParam | Acc]).
477
478extract_q(NormParams) ->
479    {ok, KVRe} = re:compile("^([^=]+)=([^=]+)$"),
480    {ok, QRe} = re:compile("^((?:0|1)(?:\\.\\d{1,3})?)$"),
481    extract_q(KVRe, QRe, NormParams, []).
482
483extract_q(_KVRe, _QRe, [], Acc) ->
484    {1.0, lists:reverse(Acc)};
485extract_q(KVRe, QRe, [Param | Rest], Acc) ->
486    case re:run(Param, KVRe, [{capture, [1, 2], list}]) of
487        {match, [Name, Value]} ->
488            case Name of
489            "q" ->
490                {match, [Q]} = re:run(Value, QRe, [{capture, [1], list}]),
491                QVal = case Q of
492                    "0" ->
493                        0.0;
494                    "1" ->
495                        1.0;
496                    Else ->
497                        list_to_float(Else)
498                end,
499                case QVal < 0.0 orelse QVal > 1.0 of
500                false ->
501                    {QVal, lists:reverse(Acc) ++ Rest}
502                end;
503            _ ->
504                extract_q(KVRe, QRe, Rest, [Param | Acc])
505            end
506    end.
507
508%% @spec pick_accepted_encodings([qvalue()], [encoding()], encoding()) ->
509%%    [encoding()]
510%%
511%% @doc Determines which encodings specified in the given Q values list are
512%%      valid according to a list of supported encodings and a default encoding.
513%%
514%%      The returned list of encodings is sorted, descendingly, according to the
515%%      Q values of the given list. The last element of this list is the given
516%%      default encoding unless this encoding is explicitily or implicitily
517%%      marked with a Q value of 0.0 in the given Q values list.
518%%      Note: encodings with the same Q value are kept in the same order as
519%%            found in the input Q values list.
520%%
521%%      This encoding picking process is described in section 14.3 of the
522%%      RFC 2616 (HTTP 1.1).
523%%
524%%      Example:
525%%
526%%      pick_accepted_encodings(
527%%          [{"gzip", 0.5}, {"deflate", 1.0}],
528%%          ["gzip", "identity"],
529%%          "identity"
530%%      ) ->
531%%          ["gzip", "identity"]
532%%
533pick_accepted_encodings(AcceptedEncs, SupportedEncs, DefaultEnc) ->
534    SortedQList = lists:reverse(
535        lists:sort(fun({_, Q1}, {_, Q2}) -> Q1 < Q2 end, AcceptedEncs)
536    ),
537    {Accepted, Refused} = lists:foldr(
538        fun({E, Q}, {A, R}) ->
539            case Q > 0.0 of
540                true ->
541                    {[E | A], R};
542                false ->
543                    {A, [E | R]}
544            end
545        end,
546        {[], []},
547        SortedQList
548    ),
549    Refused1 = lists:foldr(
550        fun(Enc, Acc) ->
551            case Enc of
552                "*" ->
553                    lists:subtract(SupportedEncs, Accepted) ++ Acc;
554                _ ->
555                    [Enc | Acc]
556            end
557        end,
558        [],
559        Refused
560    ),
561    Accepted1 = lists:foldr(
562        fun(Enc, Acc) ->
563            case Enc of
564                "*" ->
565                    lists:subtract(SupportedEncs, Accepted ++ Refused1) ++ Acc;
566                _ ->
567                    [Enc | Acc]
568            end
569        end,
570        [],
571        Accepted
572    ),
573    Accepted2 = case lists:member(DefaultEnc, Accepted1) of
574        true ->
575            Accepted1;
576        false ->
577            Accepted1 ++ [DefaultEnc]
578    end,
579    [E || E <- Accepted2, lists:member(E, SupportedEncs),
580        not lists:member(E, Refused1)].
581
582make_io(Atom) when is_atom(Atom) ->
583    atom_to_list(Atom);
584make_io(Integer) when is_integer(Integer) ->
585    integer_to_list(Integer);
586make_io(Io) when is_list(Io); is_binary(Io) ->
587    Io.
588
589%%
590%% Tests
591%%
592-ifdef(TEST).
593-include_lib("eunit/include/eunit.hrl").
594
595make_io_test() ->
596    ?assertEqual(
597       <<"atom">>,
598       iolist_to_binary(make_io(atom))),
599    ?assertEqual(
600       <<"20">>,
601       iolist_to_binary(make_io(20))),
602    ?assertEqual(
603       <<"list">>,
604       iolist_to_binary(make_io("list"))),
605    ?assertEqual(
606       <<"binary">>,
607       iolist_to_binary(make_io(<<"binary">>))),
608    ok.
609
610-record(test_record, {field1=f1, field2=f2}).
611record_to_proplist_test() ->
612    ?assertEqual(
613       [{'__record', test_record},
614        {field1, f1},
615        {field2, f2}],
616       record_to_proplist(#test_record{}, record_info(fields, test_record))),
617    ?assertEqual(
618       [{'typekey', test_record},
619        {field1, f1},
620        {field2, f2}],
621       record_to_proplist(#test_record{},
622                          record_info(fields, test_record),
623                          typekey)),
624    ok.
625
626shell_quote_test() ->
627    ?assertEqual(
628       "\"foo \\$bar\\\"\\`' baz\"",
629       shell_quote("foo $bar\"`' baz")),
630    ok.
631
632cmd_port_test_spool(Port, Acc) ->
633    receive
634        {Port, eof} ->
635            Acc;
636        {Port, {data, {eol, Data}}} ->
637            cmd_port_test_spool(Port, ["\n", Data | Acc]);
638        {Port, Unknown} ->
639            throw({unknown, Unknown})
640    after 1000 ->
641            throw(timeout)
642    end.
643
644cmd_port_test() ->
645    Port = cmd_port(["echo", "$bling$ `word`!"],
646                    [eof, stream, {line, 4096}]),
647    Res = try lists:append(lists:reverse(cmd_port_test_spool(Port, [])))
648          after catch port_close(Port)
649          end,
650    self() ! {Port, wtf},
651    try cmd_port_test_spool(Port, [])
652    catch throw:{unknown, wtf} -> ok
653    end,
654    try cmd_port_test_spool(Port, [])
655    catch throw:timeout -> ok
656    end,
657    ?assertEqual(
658       "$bling$ `word`!\n",
659       Res).
660
661cmd_test() ->
662    ?assertEqual(
663       "$bling$ `word`!\n",
664       cmd(["echo", "$bling$ `word`!"])),
665    ok.
666
667cmd_string_test() ->
668    ?assertEqual(
669       "\"echo\" \"\\$bling\\$ \\`word\\`!\"",
670       cmd_string(["echo", "$bling$ `word`!"])),
671    ok.
672
673cmd_status_test() ->
674    ?assertEqual(
675       {0, <<"$bling$ `word`!\n">>},
676       cmd_status(["echo", "$bling$ `word`!"])),
677    ok.
678
679
680parse_header_test() ->
681    ?assertEqual(
682       {"multipart/form-data", [{"boundary", "AaB03x"}]},
683       parse_header("multipart/form-data; boundary=AaB03x")),
684    %% This tests (currently) intentionally broken behavior
685    ?assertEqual(
686       {"multipart/form-data",
687        [{"b", ""},
688         {"cgi", "is"},
689         {"broken", "true\"e"}]},
690       parse_header("multipart/form-data;b=;cgi=\"i\\s;broken=true\"e;=z;z")),
691    ok.
692
693guess_mime_test() ->
694    ?assertEqual("text/plain", guess_mime("")),
695    ?assertEqual("text/plain", guess_mime(".text")),
696    ?assertEqual("application/zip", guess_mime(".zip")),
697    ?assertEqual("application/zip", guess_mime("x.zip")),
698    ?assertEqual("text/html", guess_mime("x.html")),
699    ?assertEqual("application/xhtml+xml", guess_mime("x.xhtml")),
700    ?assertEqual("text/x-cross-domain-policy", guess_mime("crossdomain.xml")),
701    ?assertEqual("text/x-cross-domain-policy", guess_mime("www/crossdomain.xml")),
702    ok.
703
704path_split_test() ->
705    {"", "foo/bar"} = path_split("/foo/bar"),
706    {"foo", "bar"} = path_split("foo/bar"),
707    {"bar", ""} = path_split("bar"),
708    ok.
709
710urlsplit_test() ->
711    {"", "", "/foo", "", "bar?baz"} = urlsplit("/foo#bar?baz"),
712    {"http", "host:port", "/foo", "", "bar?baz"} =
713        urlsplit("http://host:port/foo#bar?baz"),
714    {"http", "host", "", "", ""} = urlsplit("http://host"),
715    {"", "", "/wiki/Category:Fruit", "", ""} =
716        urlsplit("/wiki/Category:Fruit"),
717    ok.
718
719urlsplit_path_test() ->
720    {"/foo/bar", "", ""} = urlsplit_path("/foo/bar"),
721    {"/foo", "baz", ""} = urlsplit_path("/foo?baz"),
722    {"/foo", "", "bar?baz"} = urlsplit_path("/foo#bar?baz"),
723    {"/foo", "", "bar?baz#wibble"} = urlsplit_path("/foo#bar?baz#wibble"),
724    {"/foo", "bar", "baz"} = urlsplit_path("/foo?bar#baz"),
725    {"/foo", "bar?baz", "baz"} = urlsplit_path("/foo?bar?baz#baz"),
726    ok.
727
728urlunsplit_test() ->
729    "/foo#bar?baz" = urlunsplit({"", "", "/foo", "", "bar?baz"}),
730    "http://host:port/foo#bar?baz" =
731        urlunsplit({"http", "host:port", "/foo", "", "bar?baz"}),
732    ok.
733
734urlunsplit_path_test() ->
735    "/foo/bar" = urlunsplit_path({"/foo/bar", "", ""}),
736    "/foo?baz" = urlunsplit_path({"/foo", "baz", ""}),
737    "/foo#bar?baz" = urlunsplit_path({"/foo", "", "bar?baz"}),
738    "/foo#bar?baz#wibble" = urlunsplit_path({"/foo", "", "bar?baz#wibble"}),
739    "/foo?bar#baz" = urlunsplit_path({"/foo", "bar", "baz"}),
740    "/foo?bar?baz#baz" = urlunsplit_path({"/foo", "bar?baz", "baz"}),
741    ok.
742
743join_test() ->
744    ?assertEqual("foo,bar,baz",
745                  join(["foo", "bar", "baz"], $,)),
746    ?assertEqual("foo,bar,baz",
747                  join(["foo", "bar", "baz"], ",")),
748    ?assertEqual("foo bar",
749                  join([["foo", " bar"]], ",")),
750    ?assertEqual("foo bar,baz",
751                  join([["foo", " bar"], "baz"], ",")),
752    ?assertEqual("foo",
753                  join(["foo"], ",")),
754    ?assertEqual("foobarbaz",
755                  join(["foo", "bar", "baz"], "")),
756    ?assertEqual("foo" ++ [<<>>] ++ "bar" ++ [<<>>] ++ "baz",
757                 join(["foo", "bar", "baz"], <<>>)),
758    ?assertEqual("foobar" ++ [<<"baz">>],
759                 join(["foo", "bar", <<"baz">>], "")),
760    ?assertEqual("",
761                 join([], "any")),
762    ok.
763
764quote_plus_test() ->
765    "foo" = quote_plus(foo),
766    "1" = quote_plus(1),
767    "1.1" = quote_plus(1.1),
768    "foo" = quote_plus("foo"),
769    "foo+bar" = quote_plus("foo bar"),
770    "foo%0A" = quote_plus("foo\n"),
771    "foo%0A" = quote_plus("foo\n"),
772    "foo%3B%26%3D" = quote_plus("foo;&="),
773    "foo%3B%26%3D" = quote_plus(<<"foo;&=">>),
774    ok.
775
776unquote_test() ->
777    ?assertEqual("foo bar",
778                 unquote("foo+bar")),
779    ?assertEqual("foo bar",
780                 unquote("foo%20bar")),
781    ?assertEqual("foo\r\n",
782                 unquote("foo%0D%0A")),
783    ?assertEqual("foo\r\n",
784                 unquote(<<"foo%0D%0A">>)),
785    ok.
786
787urlencode_test() ->
788    "foo=bar&baz=wibble+%0D%0A&z=1" = urlencode([{foo, "bar"},
789                                                 {"baz", "wibble \r\n"},
790                                                 {z, 1}]),
791    ok.
792
793parse_qs_test() ->
794    ?assertEqual(
795       [{"foo", "bar"}, {"baz", "wibble \r\n"}, {"z", "1"}],
796       parse_qs("foo=bar&baz=wibble+%0D%0a&z=1")),
797    ?assertEqual(
798       [{"", "bar"}, {"baz", "wibble \r\n"}, {"z", ""}],
799       parse_qs("=bar&baz=wibble+%0D%0a&z=")),
800    ?assertEqual(
801       [{"foo", "bar"}, {"baz", "wibble \r\n"}, {"z", "1"}],
802       parse_qs(<<"foo=bar&baz=wibble+%0D%0a&z=1">>)),
803    ?assertEqual(
804       [],
805       parse_qs("")),
806    ?assertEqual(
807       [{"foo", ""}, {"bar", ""}, {"baz", ""}],
808       parse_qs("foo;bar&baz")),
809    ok.
810
811partition_test() ->
812    {"foo", "", ""} = partition("foo", "/"),
813    {"foo", "/", "bar"} = partition("foo/bar", "/"),
814    {"foo", "/", ""} = partition("foo/", "/"),
815    {"", "/", "bar"} = partition("/bar", "/"),
816    {"f", "oo/ba", "r"} = partition("foo/bar", "oo/ba"),
817    ok.
818
819safe_relative_path_test() ->
820    "foo" = safe_relative_path("foo"),
821    "foo/" = safe_relative_path("foo/"),
822    "foo" = safe_relative_path("foo/bar/.."),
823    "bar" = safe_relative_path("foo/../bar"),
824    "bar/" = safe_relative_path("foo/../bar/"),
825    "" = safe_relative_path("foo/.."),
826    "" = safe_relative_path("foo/../"),
827    undefined = safe_relative_path("/foo"),
828    undefined = safe_relative_path("../foo"),
829    undefined = safe_relative_path("foo/../.."),
830    undefined = safe_relative_path("foo//"),
831    undefined = safe_relative_path("foo\\bar"),
832    ok.
833
834parse_qvalues_test() ->
835    [] = parse_qvalues(""),
836    [{"identity", 0.0}] = parse_qvalues("identity;q=0"),
837    [{"identity", 0.0}] = parse_qvalues("identity ;q=0"),
838    [{"identity", 0.0}] = parse_qvalues(" identity; q =0 "),
839    [{"identity", 0.0}] = parse_qvalues("identity ; q = 0"),
840    [{"identity", 0.0}] = parse_qvalues("identity ; q= 0.0"),
841    [{"gzip", 1.0}, {"deflate", 1.0}, {"identity", 0.0}] = parse_qvalues(
842        "gzip,deflate,identity;q=0.0"
843    ),
844    [{"deflate", 1.0}, {"gzip", 1.0}, {"identity", 0.0}] = parse_qvalues(
845        "deflate,gzip,identity;q=0.0"
846    ),
847    [{"gzip", 1.0}, {"deflate", 1.0}, {"gzip", 1.0}, {"identity", 0.0}] =
848        parse_qvalues("gzip,deflate,gzip,identity;q=0"),
849    [{"gzip", 1.0}, {"deflate", 1.0}, {"identity", 0.0}] = parse_qvalues(
850        "gzip, deflate , identity; q=0.0"
851    ),
852    [{"gzip", 1.0}, {"deflate", 1.0}, {"identity", 0.0}] = parse_qvalues(
853        "gzip; q=1, deflate;q=1.0, identity;q=0.0"
854    ),
855    [{"gzip", 0.5}, {"deflate", 1.0}, {"identity", 0.0}] = parse_qvalues(
856        "gzip; q=0.5, deflate;q=1.0, identity;q=0"
857    ),
858    [{"gzip", 0.5}, {"deflate", 1.0}, {"identity", 0.0}] = parse_qvalues(
859        "gzip; q=0.5, deflate , identity;q=0.0"
860    ),
861    [{"gzip", 0.5}, {"deflate", 0.8}, {"identity", 0.0}] = parse_qvalues(
862        "gzip; q=0.5, deflate;q=0.8, identity;q=0.0"
863    ),
864    [{"gzip", 0.5}, {"deflate", 1.0}, {"identity", 1.0}] = parse_qvalues(
865        "gzip; q=0.5,deflate,identity"
866    ),
867    [{"gzip", 0.5}, {"deflate", 1.0}, {"identity", 1.0}, {"identity", 1.0}] =
868        parse_qvalues("gzip; q=0.5,deflate,identity, identity "),
869    [{"text/html;level=1", 1.0}, {"text/plain", 0.5}] =
870        parse_qvalues("text/html;level=1, text/plain;q=0.5"),
871    [{"text/html;level=1", 0.3}, {"text/plain", 1.0}] =
872        parse_qvalues("text/html;level=1;q=0.3, text/plain"),
873    [{"text/html;level=1", 0.3}, {"text/plain", 1.0}] =
874        parse_qvalues("text/html; level = 1; q = 0.3, text/plain"),
875    [{"text/html;level=1", 0.3}, {"text/plain", 1.0}] =
876        parse_qvalues("text/html;q=0.3;level=1, text/plain"),
877    invalid_qvalue_string = parse_qvalues("gzip; q=1.1, deflate"),
878    invalid_qvalue_string = parse_qvalues("gzip; q=0.5, deflate;q=2"),
879    invalid_qvalue_string = parse_qvalues("gzip, deflate;q=AB"),
880    invalid_qvalue_string = parse_qvalues("gzip; q=2.1, deflate"),
881    invalid_qvalue_string = parse_qvalues("gzip; q=0.1234, deflate"),
882    invalid_qvalue_string = parse_qvalues("text/html;level=1;q=0.3, text/html;level"),
883    ok.
884
885pick_accepted_encodings_test() ->
886    ["identity"] = pick_accepted_encodings(
887        [],
888        ["gzip", "identity"],
889        "identity"
890    ),
891    ["gzip", "identity"] = pick_accepted_encodings(
892        [{"gzip", 1.0}],
893        ["gzip", "identity"],
894        "identity"
895    ),
896    ["identity"] = pick_accepted_encodings(
897        [{"gzip", 0.0}],
898        ["gzip", "identity"],
899        "identity"
900    ),
901    ["gzip", "identity"] = pick_accepted_encodings(
902        [{"gzip", 1.0}, {"deflate", 1.0}],
903        ["gzip", "identity"],
904        "identity"
905    ),
906    ["gzip", "identity"] = pick_accepted_encodings(
907        [{"gzip", 0.5}, {"deflate", 1.0}],
908        ["gzip", "identity"],
909        "identity"
910    ),
911    ["identity"] = pick_accepted_encodings(
912        [{"gzip", 0.0}, {"deflate", 0.0}],
913        ["gzip", "identity"],
914        "identity"
915    ),
916    ["gzip"] = pick_accepted_encodings(
917        [{"gzip", 1.0}, {"deflate", 1.0}, {"identity", 0.0}],
918        ["gzip", "identity"],
919        "identity"
920    ),
921    ["gzip", "deflate", "identity"] = pick_accepted_encodings(
922        [{"gzip", 1.0}, {"deflate", 1.0}],
923        ["gzip", "deflate", "identity"],
924        "identity"
925    ),
926    ["gzip", "deflate"] = pick_accepted_encodings(
927        [{"gzip", 1.0}, {"deflate", 1.0}, {"identity", 0.0}],
928        ["gzip", "deflate", "identity"],
929        "identity"
930    ),
931    ["deflate", "gzip", "identity"] = pick_accepted_encodings(
932        [{"gzip", 0.2}, {"deflate", 1.0}],
933        ["gzip", "deflate", "identity"],
934        "identity"
935    ),
936    ["deflate", "deflate", "gzip", "identity"] = pick_accepted_encodings(
937        [{"gzip", 0.2}, {"deflate", 1.0}, {"deflate", 1.0}],
938        ["gzip", "deflate", "identity"],
939        "identity"
940    ),
941    ["deflate", "gzip", "gzip", "identity"] = pick_accepted_encodings(
942        [{"gzip", 0.2}, {"deflate", 1.0}, {"gzip", 1.0}],
943        ["gzip", "deflate", "identity"],
944        "identity"
945    ),
946    ["gzip", "deflate", "gzip", "identity"] = pick_accepted_encodings(
947        [{"gzip", 0.2}, {"deflate", 0.9}, {"gzip", 1.0}],
948        ["gzip", "deflate", "identity"],
949        "identity"
950    ),
951    [] = pick_accepted_encodings(
952        [{"*", 0.0}],
953        ["gzip", "deflate", "identity"],
954        "identity"
955    ),
956    ["gzip", "deflate", "identity"] = pick_accepted_encodings(
957        [{"*", 1.0}],
958        ["gzip", "deflate", "identity"],
959        "identity"
960    ),
961    ["gzip", "deflate", "identity"] = pick_accepted_encodings(
962        [{"*", 0.6}],
963        ["gzip", "deflate", "identity"],
964        "identity"
965    ),
966    ["gzip"] = pick_accepted_encodings(
967        [{"gzip", 1.0}, {"*", 0.0}],
968        ["gzip", "deflate", "identity"],
969        "identity"
970    ),
971    ["gzip", "deflate"] = pick_accepted_encodings(
972        [{"gzip", 1.0}, {"deflate", 0.6}, {"*", 0.0}],
973        ["gzip", "deflate", "identity"],
974        "identity"
975    ),
976    ["deflate", "gzip"] = pick_accepted_encodings(
977        [{"gzip", 0.5}, {"deflate", 1.0}, {"*", 0.0}],
978        ["gzip", "deflate", "identity"],
979        "identity"
980    ),
981    ["gzip", "identity"] = pick_accepted_encodings(
982        [{"deflate", 0.0}, {"*", 1.0}],
983        ["gzip", "deflate", "identity"],
984        "identity"
985    ),
986    ["gzip", "identity"] = pick_accepted_encodings(
987        [{"*", 1.0}, {"deflate", 0.0}],
988        ["gzip", "deflate", "identity"],
989        "identity"
990    ),
991    ok.
992
993-endif.
994