Skip to content

Commit

Permalink
honor packet_size for http packet parsing to fix OTP-9389
Browse files Browse the repository at this point in the history
Allow applications to use a packet_size setting on a socket to control
acceptable HTTP header line length. This gives them the ability to
accept HTTP headers larger than the default settings allow, but also
lets them avoid DOS attacks by accepting header lines only up to
whatever length they wish to allow.

Without this change, if an HTTP request/response line or header
arrives on a socket in http, http_bin, httph, or httph_bin parsing
mode, and the request/response line or header is too long to fit into
a default inet_drv buffer of 1460 bytes, an unexpected error
occurs. These problems were described and discussed on
erlang-questions in June 2011 in this thread:

http://erlang.org/pipermail/erlang-questions/2011-June/059563.html

In the original code, no buffer reallocation occurs to enlarge the
buffer, even if packet_size or line_length are set in a way that
should allow the HTTP data to be parsed properly. The only available
workaround was to collect headers and parse them using
erlang:decode_packet, but that approach has drawbacks such as having
to collect all HTTP header data before it can be handed to
decode_packet for correct parsing, and also requiring each and every
Erlang web server developer/maintainer to add the workaround to his or
her web server.

Change the packet parser to honor the packet_size setting for HTTP
parsing. If packet_size is set, and an HTTP request/response or header
line exceeds the default 1460 byte TCP buffer limit, return an
indication to tcp_remain that it should realloc the buffer to enlarge
it to packet_size. Also fix the HTTP parsing code to properly honor
line_length by truncating any HTTP request/response or header lines
that exceed that setting.

For backward compatibility, default behavior is unchanged; if an
application wants to be able to accept long HTTP header lines, it must
set packet_size to an appropriate value. Buffer reallocation occurs
only when needed, so the original default buffer size in the code is
still the default.

Make the line mode parsing honor packet_size as well, for consistency.

Add new regression tests to the emulator decode_packet suite and also
to the kernel gen_tcp_misc suite.

The documentation for packet_size in inet:setopts/2 is already
sufficient.

Many thanks to Sverker Eriksson for his guidance on how to best fix
this bug and also for reviewing a number of patch attempts prior to
this one.
  • Loading branch information
vinoski authored and sverker committed Dec 5, 2011
1 parent 290be47 commit 5984409
Show file tree
Hide file tree
Showing 5 changed files with 174 additions and 19 deletions.
43 changes: 36 additions & 7 deletions erts/emulator/beam/packet_parser.c
Original file line number Diff line number Diff line change
Expand Up @@ -301,14 +301,22 @@ int packet_get_length(enum PacketParseType htype,
/* TCP_PB_LINE_LF: [Data ... \n] */
const char* ptr2;
if ((ptr2 = memchr(ptr, '\n', n)) == NULL) {
if (n >= trunc_len && trunc_len!=0) { /* buffer full */
if (n > max_plen && max_plen != 0) { /* packet full */
DEBUGF((" => packet full (no NL)=%d\r\n", n));
goto error;
}
else if (n >= trunc_len && trunc_len!=0) { /* buffer full */
DEBUGF((" => line buffer full (no NL)=%d\r\n", n));
return trunc_len;
}
goto more;
}
else {
int len = (ptr2 - ptr) + 1; /* including newline */
if (len > max_plen && max_plen!=0) {
DEBUGF((" => packet_size %d exceeded\r\n", max_plen));
goto error;
}
if (len > trunc_len && trunc_len!=0) {
DEBUGF((" => truncated line=%d\r\n", trunc_len));
return trunc_len;
Expand Down Expand Up @@ -401,29 +409,50 @@ int packet_get_length(enum PacketParseType htype,
const char* ptr2 = memchr(ptr1, '\n', len);

if (ptr2 == NULL) {
if (n >= trunc_len && trunc_len!=0) { /* buffer full */
if (max_plen != 0) {
if (n > max_plen) /* packet full */
goto error;
}
else if (n >= trunc_len && trunc_len!=0) { /* buffer full */
plen = trunc_len;
goto done;
}
goto more;
}
else {
plen = (ptr2 - ptr) + 1;

if (*statep == 0)

if (*statep == 0) {
if (max_plen != 0 && plen > max_plen)
goto error;
if (plen >= trunc_len && trunc_len != 0)
plen = trunc_len;
goto done;

}

if (plen < n) {
if (SP(ptr2+1) && plen>2) {
/* header field value continue on next line */
ptr1 = ptr2+1;
len = n - plen;
}
else
else {
if (max_plen != 0 && plen > max_plen)
goto error;
if (plen >= trunc_len && trunc_len != 0)
plen = trunc_len;
goto done;
}
}
else
else {
if (max_plen != 0 && plen > max_plen)
goto error;
if (plen >= trunc_len && trunc_len != 0) {
plen = trunc_len;
goto done;
}
goto more;
}
}
}
}
Expand Down
11 changes: 9 additions & 2 deletions erts/emulator/drivers/common/inet_drv.c
Original file line number Diff line number Diff line change
Expand Up @@ -8729,8 +8729,15 @@ static int tcp_remain(tcp_descriptor* desc, int* len)
else if (tlen == 0) { /* need unknown more */
*len = 0;
if (nsz == 0) {
if (nfill == n)
goto error;
if (nfill == n) {
if (desc->inet.psize != 0 && desc->inet.psize > nfill) {
if (tcp_expand_buffer(desc, desc->inet.psize) < 0)
return -1;
return desc->inet.psize;
}
else
goto error;
}
DEBUGF((" => restart more=%d\r\n", nfill - n));
return nfill - n;
}
Expand Down
62 changes: 60 additions & 2 deletions erts/emulator/test/decode_packet_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,14 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
init_per_testcase/2,end_per_testcase/2,
basic/1, packet_size/1, neg/1, http/1, line/1, ssl/1, otp_8536/1]).
basic/1, packet_size/1, neg/1, http/1, line/1, ssl/1, otp_8536/1,
otp_9389/1, otp_9389_line/1]).

suite() -> [{ct_hooks,[ts_install_cth]}].

all() ->
[basic, packet_size, neg, http, line, ssl, otp_8536].
[basic, packet_size, neg, http, line, ssl, otp_8536,
otp_9389, otp_9389_line].

groups() ->
[].
Expand Down Expand Up @@ -251,6 +253,28 @@ packet_size(Config) when is_list(Config) ->
?line {error,_} = decode_pkt(4,<<Size:32,Packet/binary>>)
end,
lists:seq(-10,-1)),

%% Test OTP-9389, long HTTP header lines.
Opts = [{packet_size, 128}],
Pkt = list_to_binary(["GET / HTTP/1.1\r\nHost: localhost\r\nLink: /",
string:chars($Y, 64), "\r\n\r\n"]),
<<Pkt1:50/binary, Pkt2/binary>> = Pkt,
?line {ok, {http_request,'GET',{abs_path,"/"},{1,1}}, Rest1} =
erlang:decode_packet(http, Pkt1, Opts),
?line {ok, {http_header,_,'Host',_,"localhost"}, Rest2} =
erlang:decode_packet(httph, Rest1, Opts),
?line {more, undefined} = erlang:decode_packet(httph, Rest2, Opts),
?line {ok, {http_header,_,"Link",_,_}, _} =
erlang:decode_packet(httph, list_to_binary([Rest2, Pkt2]), Opts),

Pkt3 = list_to_binary(["GET / HTTP/1.1\r\nHost: localhost\r\nLink: /",
string:chars($Y, 129), "\r\n\r\n"]),
?line {ok, {http_request,'GET',{abs_path,"/"},{1,1}}, Rest3} =
erlang:decode_packet(http, Pkt3, Opts),
?line {ok, {http_header,_,'Host',_,"localhost"}, Rest4} =
erlang:decode_packet(httph, Rest3, Opts),
?line {error, invalid} = erlang:decode_packet(httph, Rest4, Opts),

ok.


Expand Down Expand Up @@ -557,3 +581,37 @@ decode_pkt(Type,Bin,Opts) ->
%%io:format(" -> ~p\n",[Res]),
Res.

otp_9389(doc) -> ["Verify line_length works correctly for HTTP headers"];
otp_9389(suite) -> [];
otp_9389(Config) when is_list(Config) ->
Opts = [{packet_size, 16384}, {line_length, 3000}],
Pkt = list_to_binary(["GET / HTTP/1.1\r\nHost: localhost\r\nLink: /",
string:chars($X, 8192),
"\r\nContent-Length: 0\r\n\r\n"]),
<<Pkt1:5000/binary, Pkt2/binary>> = Pkt,
{ok, {http_request,'GET',{abs_path,"/"},{1,1}}, Rest1} =
erlang:decode_packet(http, Pkt1, Opts),
{ok, {http_header,_,'Host',_,"localhost"}, Rest2} =
erlang:decode_packet(httph, Rest1, Opts),
{more, undefined} = erlang:decode_packet(httph, Rest2, Opts),
{ok, {http_header,_,"Link",_,Link}, Rest3} =
erlang:decode_packet(httph, list_to_binary([Rest2, Pkt2]), Opts),
true = (length(Link) =< 3000),
{ok, {http_error, _}, Rest4} = erlang:decode_packet(httph, Rest3, Opts),
{ok, {http_error, _}, Rest5} = erlang:decode_packet(httph, Rest4, Opts),
{ok, {http_header,_,'Content-Length',_,"0"}, <<"\r\n">>} =
erlang:decode_packet(httph, Rest5, Opts),
ok.

otp_9389_line(doc) -> ["Verify packet_size works correctly for line mode"];
otp_9389_line(suite) -> [];
otp_9389_line(Config) when is_list(Config) ->
Opts = [{packet_size, 20}],
Line1 = <<"0123456789012345678\n">>,
Line2 = <<"0123456789\n">>,
Line3 = <<"01234567890123456789\n">>,
Pkt = list_to_binary([Line1, Line2, Line3]),
?line {ok, Line1, Rest1} = erlang:decode_packet(line, Pkt, Opts),
?line {ok, Line2, Rest2} = erlang:decode_packet(line, Rest1, Opts),
?line {error, invalid} = erlang:decode_packet(line, Rest2, Opts),
ok.
11 changes: 6 additions & 5 deletions lib/kernel/test/gen_tcp_echo_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -167,8 +167,12 @@ echo_test_1(SockOpts, EchoFun, Config0) ->
[{type, {cdr, little}}|Config]),
?line case lists:keymember(packet_size, 1, SockOpts) of
false ->
?line echo_packet([{packet, line}|SockOpts],
EchoFun, Config);
% This is cheating, we should test that packet_size
% also works for line and http.
echo_packet([{packet, line}|SockOpts], EchoFun, Config),
echo_packet([{packet, http}|SockOpts], EchoFun, Config),
echo_packet([{packet, http_bin}|SockOpts], EchoFun, Config);

true -> ok
end,
?line echo_packet([{packet, tpkt}|SockOpts], EchoFun, Config),
Expand All @@ -183,9 +187,6 @@ echo_test_1(SockOpts, EchoFun, Config0) ->
[{type, {asn1, short, LongTag}}|Config]),
?line echo_packet([{packet, asn1}|SockOpts], EchoFun,
[{type, {asn1, long, LongTag}}|Config]),

?line echo_packet([{packet, http}|SockOpts], EchoFun, Config),
?line echo_packet([{packet, http_bin}|SockOpts], EchoFun, Config),
ok.

echo_packet(SockOpts, EchoFun, Opts) ->
Expand Down
66 changes: 63 additions & 3 deletions lib/kernel/test/gen_tcp_misc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,8 @@
accept_timeouts_in_order3/1,accept_timeouts_mixed/1,
killing_acceptor/1,killing_multi_acceptors/1,killing_multi_acceptors2/1,
several_accepts_in_one_go/1,active_once_closed/1, send_timeout/1, send_timeout_active/1,
otp_7731/1, zombie_sockets/1, otp_7816/1, otp_8102/1]).
otp_7731/1, zombie_sockets/1, otp_7816/1, otp_8102/1,
otp_9389/1]).

%% Internal exports.
-export([sender/3, not_owner/1, passive_sockets_server/2, priority_server/1,
Expand Down Expand Up @@ -72,7 +73,7 @@ all() ->
killing_acceptor, killing_multi_acceptors,
killing_multi_acceptors2, several_accepts_in_one_go,
active_once_closed, send_timeout, send_timeout_active, otp_7731,
zombie_sockets, otp_7816, otp_8102].
zombie_sockets, otp_7816, otp_8102, otp_9389].

groups() ->
[].
Expand Down Expand Up @@ -2479,4 +2480,63 @@ otp_8102_do(LSocket, PortNum, {Bin,PType}) ->
io:format("Got error msg, ok.\n",[]),
gen_tcp:close(SSocket),
gen_tcp:close(RSocket).


otp_9389(doc) -> ["Verify packet_size handles long HTTP header lines"];
otp_9389(suite) -> [];
otp_9389(Config) when is_list(Config) ->
?line {ok, LS} = gen_tcp:listen(0, []),
?line {ok, {_, PortNum}} = inet:sockname(LS),
io:format("Listening on ~w with port number ~p\n", [LS, PortNum]),
OrigLinkHdr = "/" ++ string:chars($S, 8192),
_Server = spawn_link(
fun() ->
?line {ok, S} = gen_tcp:accept(LS),
?line ok = inet:setopts(S, [{packet_size, 16384}]),
?line ok = otp_9389_loop(S, OrigLinkHdr),
?line ok = gen_tcp:close(S)
end),
?line {ok, S} = gen_tcp:connect("localhost", PortNum,
[binary, {active, false}]),
Req = "GET / HTTP/1.1\r\n"
++ "Host: localhost\r\n"
++ "Link: " ++ OrigLinkHdr ++ "\r\n\r\n",
?line ok = gen_tcp:send(S, Req),
?line ok = inet:setopts(S, [{packet, http}]),
?line {ok, {http_response, {1,1}, 200, "OK"}} = gen_tcp:recv(S, 0),
?line ok = inet:setopts(S, [{packet, httph}, {packet_size, 16384}]),
?line {ok, {http_header, _, 'Content-Length', _, "0"}} = gen_tcp:recv(S, 0),
?line {ok, {http_header, _, "Link", _, LinkHdr}} = gen_tcp:recv(S, 0),
?line true = (LinkHdr == OrigLinkHdr),
ok = gen_tcp:close(S),
ok = gen_tcp:close(LS),
ok.

otp_9389_loop(S, OrigLinkHdr) ->
?line ok = inet:setopts(S, [{active,once},{packet,http}]),
receive
{http, S, {http_request, 'GET', _, _}} ->
?line ok = otp_9389_loop(S, OrigLinkHdr, undefined)
after
3000 ->
?line error({timeout,request_line})
end.
otp_9389_loop(S, OrigLinkHdr, ok) ->
?line Resp = "HTTP/1.1 200 OK\r\nContent-length: 0\r\n" ++
"Link: " ++ OrigLinkHdr ++ "\r\n\r\n",
?line ok = gen_tcp:send(S, Resp);
otp_9389_loop(S, OrigLinkHdr, State) ->
?line ok = inet:setopts(S, [{active,once}, {packet,httph}]),
receive
{http, S, http_eoh} ->
?line otp_9389_loop(S, OrigLinkHdr, ok);
{http, S, {http_header, _, "Link", _, LinkHdr}} ->
?line LinkHdr = OrigLinkHdr,
?line otp_9389_loop(S, OrigLinkHdr, State);
{http, S, {http_header, _, _Hdr, _, _Val}} ->
?line otp_9389_loop(S, OrigLinkHdr, State);
{http, S, {http_error, Err}} ->
?line error({error, Err})
after
3000 ->
?line error({timeout,header})
end.

0 comments on commit 5984409

Please sign in to comment.