summaryrefslogtreecommitdiff
path: root/src/mochiweb/mochiweb_util.erl
diff options
context:
space:
mode:
Diffstat (limited to 'src/mochiweb/mochiweb_util.erl')
-rw-r--r--src/mochiweb/mochiweb_util.erl361
1 files changed, 221 insertions, 140 deletions
diff --git a/src/mochiweb/mochiweb_util.erl b/src/mochiweb/mochiweb_util.erl
index d8fc89d5..d1cc59de 100644
--- a/src/mochiweb/mochiweb_util.erl
+++ b/src/mochiweb/mochiweb_util.erl
@@ -9,11 +9,11 @@
-export([path_split/1]).
-export([urlsplit/1, urlsplit_path/1, urlunsplit/1, urlunsplit_path/1]).
-export([guess_mime/1, parse_header/1]).
--export([shell_quote/1, cmd/1, cmd_string/1, cmd_port/2]).
+-export([shell_quote/1, cmd/1, cmd_string/1, cmd_port/2, cmd_status/1]).
-export([record_to_proplist/2, record_to_proplist/3]).
-export([safe_relative_path/1, partition/2]).
-export([parse_qvalues/1, pick_accepted_encodings/3]).
--export([test/0]).
+-export([make_io/1]).
-define(PERCENT, 37). % $\%
-define(FULLSTOP, 46). % $\.
@@ -115,11 +115,32 @@ cmd(Argv) ->
%% @spec cmd_string([string()]) -> string()
%% @doc Create a shell quoted command string from a list of arguments.
cmd_string(Argv) ->
- join([shell_quote(X) || X <- Argv], " ").
+ string:join([shell_quote(X) || X <- Argv], " ").
+
+%% @spec cmd_status([string()]) -> {ExitStatus::integer(), Stdout::binary()}
+%% @doc Accumulate the output and exit status from the given application, will be
+%% spawned with cmd_port/2.
+cmd_status(Argv) ->
+ Port = cmd_port(Argv, [exit_status, stderr_to_stdout,
+ use_stdio, binary]),
+ try cmd_loop(Port, [])
+ after catch port_close(Port)
+ end.
+
+%% @spec cmd_loop(port(), list()) -> {ExitStatus::integer(), Stdout::binary()}
+%% @doc Accumulate the output and exit status from a port.
+cmd_loop(Port, Acc) ->
+ receive
+ {Port, {exit_status, Status}} ->
+ {Status, iolist_to_binary(lists:reverse(Acc))};
+ {Port, {data, Data}} ->
+ cmd_loop(Port, [Data | Acc])
+ end.
-%% @spec join([string()], Separator) -> string()
-%% @doc Join a list of strings together with the given separator
-%% string or char.
+%% @spec join([iolist()], iolist()) -> iolist()
+%% @doc Join a list of strings or binaries together with the given separator
+%% string or char or binary. The output is flattened, but may be an
+%% iolist() instead of a string() if any of the inputs are binary().
join([], _Separator) ->
[];
join([S], _Separator) ->
@@ -160,10 +181,11 @@ quote_plus([C | Rest], Acc) ->
%% @spec urlencode([{Key, Value}]) -> string()
%% @doc URL encode the property list.
urlencode(Props) ->
- RevPairs = lists:foldl(fun ({K, V}, Acc) ->
- [[quote_plus(K), $=, quote_plus(V)] | Acc]
- end, [], Props),
- lists:flatten(revjoin(RevPairs, $&, [])).
+ Pairs = lists:foldr(
+ fun ({K, V}, Acc) ->
+ [quote_plus(K) ++ "=" ++ quote_plus(V) | Acc]
+ end, [], Props),
+ string:join(Pairs, "&").
%% @spec parse_qs(string() | binary()) -> [{Key, Value}]
%% @doc Parse a query string or application/x-www-form-urlencoded.
@@ -234,20 +256,31 @@ urlsplit(Url) ->
{Scheme, Netloc, Path, Query, Fragment}.
urlsplit_scheme(Url) ->
- urlsplit_scheme(Url, []).
+ case urlsplit_scheme(Url, []) of
+ no_scheme ->
+ {"", Url};
+ Res ->
+ Res
+ end.
-urlsplit_scheme([], Acc) ->
- {"", lists:reverse(Acc)};
-urlsplit_scheme(":" ++ Rest, Acc) ->
+urlsplit_scheme([C | Rest], Acc) when ((C >= $a andalso C =< $z) orelse
+ (C >= $A andalso C =< $Z) orelse
+ (C >= $0 andalso C =< $9) orelse
+ C =:= $+ orelse C =:= $- orelse
+ C =:= $.) ->
+ urlsplit_scheme(Rest, [C | Acc]);
+urlsplit_scheme([$: | Rest], Acc=[_ | _]) ->
{string:to_lower(lists:reverse(Acc)), Rest};
-urlsplit_scheme([C | Rest], Acc) ->
- urlsplit_scheme(Rest, [C | Acc]).
+urlsplit_scheme(_Rest, _Acc) ->
+ no_scheme.
urlsplit_netloc("//" ++ Rest) ->
urlsplit_netloc(Rest, []);
urlsplit_netloc(Path) ->
{"", Path}.
+urlsplit_netloc("", Acc) ->
+ {lists:reverse(Acc), ""};
urlsplit_netloc(Rest=[C | _], Acc) when C =:= $/; C =:= $?; C =:= $# ->
{lists:reverse(Acc), Rest};
urlsplit_netloc([C | Rest], Acc) ->
@@ -312,67 +345,11 @@ urlsplit_query([C | Rest], Acc) ->
%% @spec guess_mime(string()) -> string()
%% @doc Guess the mime type of a file by the extension of its filename.
guess_mime(File) ->
- case filename:extension(File) of
- ".html" ->
- "text/html";
- ".xhtml" ->
- "application/xhtml+xml";
- ".xml" ->
- "application/xml";
- ".css" ->
- "text/css";
- ".js" ->
- "application/x-javascript";
- ".jpg" ->
- "image/jpeg";
- ".gif" ->
- "image/gif";
- ".png" ->
- "image/png";
- ".swf" ->
- "application/x-shockwave-flash";
- ".zip" ->
- "application/zip";
- ".bz2" ->
- "application/x-bzip2";
- ".gz" ->
- "application/x-gzip";
- ".tar" ->
- "application/x-tar";
- ".tgz" ->
- "application/x-gzip";
- ".txt" ->
+ case mochiweb_mime:from_extension(filename:extension(File)) of
+ undefined ->
"text/plain";
- ".doc" ->
- "application/msword";
- ".pdf" ->
- "application/pdf";
- ".xls" ->
- "application/vnd.ms-excel";
- ".rtf" ->
- "application/rtf";
- ".mov" ->
- "video/quicktime";
- ".mp3" ->
- "audio/mpeg";
- ".z" ->
- "application/x-compress";
- ".wav" ->
- "audio/x-wav";
- ".ico" ->
- "image/x-icon";
- ".bmp" ->
- "image/bmp";
- ".m4a" ->
- "audio/mpeg";
- ".m3u" ->
- "audio/x-mpegurl";
- ".exe" ->
- "application/octet-stream";
- ".csv" ->
- "text/csv";
- _ ->
- "text/plain"
+ Mime ->
+ Mime
end.
%% @spec parse_header(string()) -> {Type, [{K, V}]}
@@ -436,11 +413,9 @@ shell_quote([C | Rest], Acc) when C =:= $\" orelse C =:= $\` orelse
shell_quote([C | Rest], Acc) ->
shell_quote(Rest, [C | Acc]).
-%% @spec parse_qvalues(string()) -> [qvalue()] | error()
-%% @type qvalue() -> {element(), q()}
-%% @type element() -> string()
-%% @type q() -> 0.0 .. 1.0
-%% @type error() -> invalid_qvalue_string
+%% @spec parse_qvalues(string()) -> [qvalue()] | invalid_qvalue_string
+%% @type qvalue() = {encoding(), float()}.
+%% @type encoding() = string().
%%
%% @doc Parses a list (given as a string) of elements with Q values associated
%% to them. Elements are separated by commas and each element is separated
@@ -489,11 +464,8 @@ parse_qvalues(QValuesStr) ->
invalid_qvalue_string
end.
-%% @spec pick_accepted_encodings(qvalues(), [encoding()], encoding()) ->
+%% @spec pick_accepted_encodings([qvalue()], [encoding()], encoding()) ->
%% [encoding()]
-%% @type qvalues() -> [ {encoding(), q()} ]
-%% @type encoding() -> string()
-%% @type q() -> 0.0 .. 1.0
%%
%% @doc Determines which encodings specified in the given Q values list are
%% valid according to a list of supported encodings and a default encoding.
@@ -566,46 +538,118 @@ pick_accepted_encodings(AcceptedEncs, SupportedEncs, DefaultEnc) ->
[E || E <- Accepted2, lists:member(E, SupportedEncs),
not lists:member(E, Refused1)].
-test() ->
- test_join(),
- test_quote_plus(),
- test_unquote(),
- test_urlencode(),
- test_parse_qs(),
- test_urlsplit_path(),
- test_urlunsplit_path(),
- test_urlsplit(),
- test_urlunsplit(),
- test_path_split(),
- test_guess_mime(),
- test_parse_header(),
- test_shell_quote(),
- test_cmd(),
- test_cmd_string(),
- test_partition(),
- test_safe_relative_path(),
- test_parse_qvalues(),
- test_pick_accepted_encodings(),
+make_io(Atom) when is_atom(Atom) ->
+ atom_to_list(Atom);
+make_io(Integer) when is_integer(Integer) ->
+ integer_to_list(Integer);
+make_io(Io) when is_list(Io); is_binary(Io) ->
+ Io.
+
+%%
+%% Tests
+%%
+-include_lib("eunit/include/eunit.hrl").
+-ifdef(TEST).
+
+make_io_test() ->
+ ?assertEqual(
+ <<"atom">>,
+ iolist_to_binary(make_io(atom))),
+ ?assertEqual(
+ <<"20">>,
+ iolist_to_binary(make_io(20))),
+ ?assertEqual(
+ <<"list">>,
+ iolist_to_binary(make_io("list"))),
+ ?assertEqual(
+ <<"binary">>,
+ iolist_to_binary(make_io(<<"binary">>))),
+ ok.
+
+-record(test_record, {field1=f1, field2=f2}).
+record_to_proplist_test() ->
+ ?assertEqual(
+ [{'__record', test_record},
+ {field1, f1},
+ {field2, f2}],
+ record_to_proplist(#test_record{}, record_info(fields, test_record))),
+ ?assertEqual(
+ [{'typekey', test_record},
+ {field1, f1},
+ {field2, f2}],
+ record_to_proplist(#test_record{},
+ record_info(fields, test_record),
+ typekey)),
ok.
-test_shell_quote() ->
- "\"foo \\$bar\\\"\\`' baz\"" = shell_quote("foo $bar\"`' baz"),
+shell_quote_test() ->
+ ?assertEqual(
+ "\"foo \\$bar\\\"\\`' baz\"",
+ shell_quote("foo $bar\"`' baz")),
+ ok.
+
+cmd_port_test_spool(Port, Acc) ->
+ receive
+ {Port, eof} ->
+ Acc;
+ {Port, {data, {eol, Data}}} ->
+ cmd_port_test_spool(Port, ["\n", Data | Acc]);
+ {Port, Unknown} ->
+ throw({unknown, Unknown})
+ after 100 ->
+ throw(timeout)
+ end.
+
+cmd_port_test() ->
+ Port = cmd_port(["echo", "$bling$ `word`!"],
+ [eof, stream, {line, 4096}]),
+ Res = try lists:append(lists:reverse(cmd_port_test_spool(Port, [])))
+ after catch port_close(Port)
+ end,
+ self() ! {Port, wtf},
+ try cmd_port_test_spool(Port, [])
+ catch throw:{unknown, wtf} -> ok
+ end,
+ try cmd_port_test_spool(Port, [])
+ catch throw:timeout -> ok
+ end,
+ ?assertEqual(
+ "$bling$ `word`!\n",
+ Res).
+
+cmd_test() ->
+ ?assertEqual(
+ "$bling$ `word`!\n",
+ cmd(["echo", "$bling$ `word`!"])),
ok.
-test_cmd() ->
- "$bling$ `word`!\n" = cmd(["echo", "$bling$ `word`!"]),
+cmd_string_test() ->
+ ?assertEqual(
+ "\"echo\" \"\\$bling\\$ \\`word\\`!\"",
+ cmd_string(["echo", "$bling$ `word`!"])),
ok.
-test_cmd_string() ->
- "\"echo\" \"\\$bling\\$ \\`word\\`!\"" = cmd_string(["echo", "$bling$ `word`!"]),
+cmd_status_test() ->
+ ?assertEqual(
+ {0, <<"$bling$ `word`!\n">>},
+ cmd_status(["echo", "$bling$ `word`!"])),
ok.
-test_parse_header() ->
- {"multipart/form-data", [{"boundary", "AaB03x"}]} =
- parse_header("multipart/form-data; boundary=AaB03x"),
+
+parse_header_test() ->
+ ?assertEqual(
+ {"multipart/form-data", [{"boundary", "AaB03x"}]},
+ parse_header("multipart/form-data; boundary=AaB03x")),
+ %% This tests (currently) intentionally broken behavior
+ ?assertEqual(
+ {"multipart/form-data",
+ [{"b", ""},
+ {"cgi", "is"},
+ {"broken", "true\"e"}]},
+ parse_header("multipart/form-data;b=;cgi=\"i\\s;broken=true\"e;=z;z")),
ok.
-test_guess_mime() ->
+guess_mime_test() ->
"text/plain" = guess_mime(""),
"text/plain" = guess_mime(".text"),
"application/zip" = guess_mime(".zip"),
@@ -614,19 +658,22 @@ test_guess_mime() ->
"application/xhtml+xml" = guess_mime("x.xhtml"),
ok.
-test_path_split() ->
+path_split_test() ->
{"", "foo/bar"} = path_split("/foo/bar"),
{"foo", "bar"} = path_split("foo/bar"),
{"bar", ""} = path_split("bar"),
ok.
-test_urlsplit() ->
+urlsplit_test() ->
{"", "", "/foo", "", "bar?baz"} = urlsplit("/foo#bar?baz"),
{"http", "host:port", "/foo", "", "bar?baz"} =
urlsplit("http://host:port/foo#bar?baz"),
+ {"http", "host", "", "", ""} = urlsplit("http://host"),
+ {"", "", "/wiki/Category:Fruit", "", ""} =
+ urlsplit("/wiki/Category:Fruit"),
ok.
-test_urlsplit_path() ->
+urlsplit_path_test() ->
{"/foo/bar", "", ""} = urlsplit_path("/foo/bar"),
{"/foo", "baz", ""} = urlsplit_path("/foo?baz"),
{"/foo", "", "bar?baz"} = urlsplit_path("/foo#bar?baz"),
@@ -635,13 +682,13 @@ test_urlsplit_path() ->
{"/foo", "bar?baz", "baz"} = urlsplit_path("/foo?bar?baz#baz"),
ok.
-test_urlunsplit() ->
+urlunsplit_test() ->
"/foo#bar?baz" = urlunsplit({"", "", "/foo", "", "bar?baz"}),
"http://host:port/foo#bar?baz" =
urlunsplit({"http", "host:port", "/foo", "", "bar?baz"}),
ok.
-test_urlunsplit_path() ->
+urlunsplit_path_test() ->
"/foo/bar" = urlunsplit_path({"/foo/bar", "", ""}),
"/foo?baz" = urlunsplit_path({"/foo", "baz", ""}),
"/foo#bar?baz" = urlunsplit_path({"/foo", "", "bar?baz"}),
@@ -650,16 +697,28 @@ test_urlunsplit_path() ->
"/foo?bar?baz#baz" = urlunsplit_path({"/foo", "bar?baz", "baz"}),
ok.
-test_join() ->
- "foo,bar,baz" = join(["foo", "bar", "baz"], $,),
- "foo,bar,baz" = join(["foo", "bar", "baz"], ","),
- "foo bar" = join([["foo", " bar"]], ","),
- "foo bar,baz" = join([["foo", " bar"], "baz"], ","),
- "foo" = join(["foo"], ","),
- "foobarbaz" = join(["foo", "bar", "baz"], ""),
+join_test() ->
+ ?assertEqual("foo,bar,baz",
+ join(["foo", "bar", "baz"], $,)),
+ ?assertEqual("foo,bar,baz",
+ join(["foo", "bar", "baz"], ",")),
+ ?assertEqual("foo bar",
+ join([["foo", " bar"]], ",")),
+ ?assertEqual("foo bar,baz",
+ join([["foo", " bar"], "baz"], ",")),
+ ?assertEqual("foo",
+ join(["foo"], ",")),
+ ?assertEqual("foobarbaz",
+ join(["foo", "bar", "baz"], "")),
+ ?assertEqual("foo" ++ [<<>>] ++ "bar" ++ [<<>>] ++ "baz",
+ join(["foo", "bar", "baz"], <<>>)),
+ ?assertEqual("foobar" ++ [<<"baz">>],
+ join(["foo", "bar", <<"baz">>], "")),
+ ?assertEqual("",
+ join([], "any")),
ok.
-test_quote_plus() ->
+quote_plus_test() ->
"foo" = quote_plus(foo),
"1" = quote_plus(1),
"1.1" = quote_plus(1.1),
@@ -668,26 +727,45 @@ test_quote_plus() ->
"foo%0A" = quote_plus("foo\n"),
"foo%0A" = quote_plus("foo\n"),
"foo%3B%26%3D" = quote_plus("foo;&="),
+ "foo%3B%26%3D" = quote_plus(<<"foo;&=">>),
ok.
-test_unquote() ->
- "foo bar" = unquote("foo+bar"),
- "foo bar" = unquote("foo%20bar"),
- "foo\r\n" = unquote("foo%0D%0A"),
+unquote_test() ->
+ ?assertEqual("foo bar",
+ unquote("foo+bar")),
+ ?assertEqual("foo bar",
+ unquote("foo%20bar")),
+ ?assertEqual("foo\r\n",
+ unquote("foo%0D%0A")),
+ ?assertEqual("foo\r\n",
+ unquote(<<"foo%0D%0A">>)),
ok.
-test_urlencode() ->
+urlencode_test() ->
"foo=bar&baz=wibble+%0D%0A&z=1" = urlencode([{foo, "bar"},
{"baz", "wibble \r\n"},
{z, 1}]),
ok.
-test_parse_qs() ->
- [{"foo", "bar"}, {"baz", "wibble \r\n"}, {"z", "1"}] =
- parse_qs("foo=bar&baz=wibble+%0D%0A&z=1"),
+parse_qs_test() ->
+ ?assertEqual(
+ [{"foo", "bar"}, {"baz", "wibble \r\n"}, {"z", "1"}],
+ parse_qs("foo=bar&baz=wibble+%0D%0a&z=1")),
+ ?assertEqual(
+ [{"", "bar"}, {"baz", "wibble \r\n"}, {"z", ""}],
+ parse_qs("=bar&baz=wibble+%0D%0a&z=")),
+ ?assertEqual(
+ [{"foo", "bar"}, {"baz", "wibble \r\n"}, {"z", "1"}],
+ parse_qs(<<"foo=bar&baz=wibble+%0D%0a&z=1">>)),
+ ?assertEqual(
+ [],
+ parse_qs("")),
+ ?assertEqual(
+ [{"foo", ""}, {"bar", ""}, {"baz", ""}],
+ parse_qs("foo;bar&baz")),
ok.
-test_partition() ->
+partition_test() ->
{"foo", "", ""} = partition("foo", "/"),
{"foo", "/", "bar"} = partition("foo/bar", "/"),
{"foo", "/", ""} = partition("foo/", "/"),
@@ -695,7 +773,7 @@ test_partition() ->
{"f", "oo/ba", "r"} = partition("foo/bar", "oo/ba"),
ok.
-test_safe_relative_path() ->
+safe_relative_path_test() ->
"foo" = safe_relative_path("foo"),
"foo/" = safe_relative_path("foo/"),
"foo" = safe_relative_path("foo/bar/.."),
@@ -709,7 +787,7 @@ test_safe_relative_path() ->
undefined = safe_relative_path("foo//"),
ok.
-test_parse_qvalues() ->
+parse_qvalues_test() ->
[] = parse_qvalues(""),
[{"identity", 0.0}] = parse_qvalues("identity;q=0"),
[{"identity", 0.0}] = parse_qvalues("identity ;q=0"),
@@ -748,9 +826,10 @@ test_parse_qvalues() ->
invalid_qvalue_string = parse_qvalues("gzip; q=0.5, deflate;q=2"),
invalid_qvalue_string = parse_qvalues("gzip, deflate;q=AB"),
invalid_qvalue_string = parse_qvalues("gzip; q=2.1, deflate"),
+ invalid_qvalue_string = parse_qvalues("gzip; q=0.1234, deflate"),
ok.
-test_pick_accepted_encodings() ->
+pick_accepted_encodings_test() ->
["identity"] = pick_accepted_encodings(
[],
["gzip", "identity"],
@@ -857,3 +936,5 @@ test_pick_accepted_encodings() ->
"identity"
),
ok.
+
+-endif.