Skip to content

Commit

Permalink
inets: httpc - enhance error handling
Browse files Browse the repository at this point in the history
closes #7482
  • Loading branch information
IngelaAndin committed Aug 1, 2023
1 parent 6022f86 commit 9f5ce0b
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 15 deletions.
28 changes: 17 additions & 11 deletions lib/inets/src/http_client/httpc_request.erl
Original file line number Diff line number Diff line change
Expand Up @@ -95,17 +95,23 @@ send(SendAddr, Socket, SocketType,
{TmpHdrs2, Path ++ Query}
end,

FinalHeaders =
case NewHeaders of
HeaderList when is_list(HeaderList) ->
http_headers(HeaderList, []);
_ ->
http_request:http_headers(NewHeaders)
end,
Version = HttpOptions#http_options.version,

do_send_body(SocketType, Socket, Method, Uri, Version, FinalHeaders, Body).

FinalHeaders = try
case NewHeaders of
HeaderList when is_list(HeaderList) ->
http_headers(HeaderList, []);
_ ->
http_request:http_headers(NewHeaders)
end
catch throw:{invalid_header, _} = Bad ->
{error, Bad}
end,
case FinalHeaders of
{error,_} = InvalidHeaders ->
InvalidHeaders;
_ ->
Version = HttpOptions#http_options.version,
do_send_body(SocketType, Socket, Method, Uri, Version, FinalHeaders, Body)
end.

do_send_body(SocketType, Socket, Method, Uri, Version, Headers,
{ProcessBody, Acc}) when is_function(ProcessBody, 1) ->
Expand Down
11 changes: 9 additions & 2 deletions lib/inets/src/http_lib/http_request.erl
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,8 @@ headers(Key, Value, Headers) ->

key_value_str(Key, Headers) ->
case key_value(Key, Headers) of
undefined -> undefined;
undefined ->
undefined;
Value ->
mk_key_value_str(atom_to_list(Key), Value)
end.
Expand Down Expand Up @@ -289,7 +290,13 @@ headers_other([{Key, Value} | Rest], Headers) ->
headers_other(Rest, [mk_key_value_str(Key, Value) | Headers]).

mk_key_value_str(Key, Value) ->
Key ++ ": " ++ value_to_list(Value) ++ ?CRLF.
try Key ++ ": " ++ value_to_list(Value) ++ ?CRLF of
HeaderStr ->
HeaderStr
catch
error:_ ->
throw({invalid_header, {Key, Value}})
end.

value_to_list(Binary) when is_binary(Binary) ->
binary_to_list(Binary);
Expand Down
13 changes: 11 additions & 2 deletions lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,6 @@ real_requests()->
persistent_connection,
save_to_file,
save_to_file_async,
headers_as_is,
page_does_not_exist,
emulate_lower_versions,
headers,
Expand Down Expand Up @@ -134,6 +133,7 @@ real_requests()->
stream_through_mfa,
streaming_error,
inet_opts,
invalid_headers,
invalid_headers_key,
invalid_headers_value,
invalid_body,
Expand Down Expand Up @@ -944,6 +944,7 @@ headers_as_is(Config) when is_list(Config) ->

{ok, {{_,400,_}, [_|_], [_|_]}} =
httpc:request(get, {URL, [{"Te", ""}]}, [?SSL_NO_VERIFY], [{headers_as_is, true}]).

%%-------------------------------------------------------------------------

userinfo(doc) ->
Expand Down Expand Up @@ -1281,8 +1282,16 @@ headers_conflict_chunked_with_length(Config) when is_list(Config) ->
ok.

%%-------------------------------------------------------------------------
invalid_headers(doc) ->
["Test invalid header format"];
invalid_headers(Config) when is_list(Config) ->
URL = url(group_name(Config), "/dummy.html", Config),
{error,{invalid_header,{"headers",
[{"user-agent","httpc"}]}}} =
httpc:request(get, {URL, [{"headers", [{"user-agent", "httpc"}]},
[?SSL_NO_VERIFY], []).


%%-------------------------------------------------------------------------
invalid_headers_key(Config) ->
Request = {url(group_name(Config), "/dummy.html", Config),
[{cookie, "valid cookie"}]},
Expand Down

0 comments on commit 9f5ce0b

Please sign in to comment.