File 1429-httpc-Allow-binary-header-values-in-request-5.patch of Package erlang

From ea8d06931255d5dff5d3747194651f1fba43d2f8 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Cons=20T=20=C3=85hs?= <cons@erlang.org>
Date: Wed, 15 Sep 2021 17:29:08 +0200
Subject: [PATCH 2/2] [httpc] Allow binary() header values in request/5

Fix a bug where using a binary() in a header value to request/5 would
cause the application to hang.  Now allow a binary() as a header
value.  Extend error checking of arguments to request/5 and be more
precise with returned errors when arguments have an invalid type.

* Add tests
  * Catch test problem earlier
  * Add new tests for header types and other arguments to request/5
  * Be more precise when checking the error returned

* Code
  * Abstract construction of header-value string for consistency
  * Make checking of headers values and arguments consistent and
    more precise.

* Update documentation
  * Correct types in documentation
  * Use http_string() instead of string() to avoid possible confusion
    due to using a well defined system wide type.
---
 lib/inets/doc/src/httpc.xml             |  24 +--
 lib/inets/src/http_client/httpc.erl     | 122 ++++++++-------
 lib/inets/src/http_lib/http_request.erl | 196 ++++++++++++------------
 lib/inets/test/httpc_SUITE.erl          | 138 +++++++++++++++--
 4 files changed, 293 insertions(+), 187 deletions(-)

diff --git a/lib/inets/doc/src/httpc.xml b/lib/inets/doc/src/httpc.xml
index 905cfb2465..34010b25e4 100644
--- a/lib/inets/doc/src/httpc.xml
+++ b/lib/inets/doc/src/httpc.xml
@@ -4,7 +4,7 @@
 <erlref>
   <header>
     <copyright>
-      <year>2004</year><year>2018</year>
+      <year>2004</year><year>2021</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -67,7 +67,7 @@
     <p>Type definitions that are used more than once in
       this module:</p>
     <p><c>boolean() = true | false</c></p>
-    <p><c>string()</c> = list of ASCII characters</p>
+    <p><c>http_string()</c> = list of ASCII characters</p>
     <p><c>request_id() = reference()</c></p>
     <p><c>profile() = atom()</c></p>
     <p><c>path() = string()</c> representing a file path or directory path</p>
@@ -90,7 +90,7 @@
       <p>| <c>{url(), headers(), content_type(), body()}</c></p>
       </item>
     </taglist>
-    <p><c>url() = string()</c> syntax according to the URI definition in
+    <p><c>url() = http_string()</c> syntax according to the URI definition in
     <url href="http://www.ietf.org/rfc/rfc3986.txt">RFC 3986</url>,
     for example <c>"http://www.erlang.org"</c></p>
     <warning><p>Please note that httpc normalizes input URIs before internal processing
@@ -102,17 +102,17 @@
     creating the request: <c>httpc:request("http://localhost/foo%2525bar").</c>
     </p></warning>
     <p><c>status_line() = {http_version(), status_code(), reason_phrase()}</c></p>
-    <p><c>http_version() = string()</c>, for example, <c>"HTTP/1.1"</c></p>
+    <p><c>http_version() = http_string()</c>, for example, <c>"HTTP/1.1"</c></p>
     <p><c>status_code() = integer()</c></p>
     <p><c>reason_phrase() = string()</c></p>
-    <p><c>content_type() = string()</c></p>
+    <p><c>content_type() = http_string()</c></p>
     <p><c>headers() = [header()]</c></p>
     <p><c>header() = {field(), value()}</c></p>
-    <p><c>field() = string()</c></p>
-    <p><c>value() = string()</c></p>
+    <p><c>field() = [byte()]</c></p>
+    <p><c>value() = binary() | iolist()</c></p>
     <taglist>
       <tag><c>body()</c></tag>
-      <item><p>= <c>string() | binary()</c></p>
+      <item><p>= <c>http_string() | binary()</c></p>
       <p>| <c>{fun(accumulator())</c></p>
       <p><c> -> body_processing_result(), accumulator()}</c></p>
       <p>| <c>{chunkify, fun(accumulator())</c></p>
@@ -269,7 +269,7 @@
         <v>Url = url()</v> 
 	<v>Result = {status_line(), headers(), Body} | 
                     {status_code(), Body} | request_id()</v>
-	<v>Body = string() | binary()</v>
+	<v>Body = http_string() | binary()</v>
 	<v>Profile = profile() | pid()</v>
 	<d>When started <c>stand_alone</c> only the pid can be used.</d>
 	<v>Reason = term()</v>
@@ -317,7 +317,7 @@
 	<v>body_format() = string | binary</v>
         <v>Result = {status_line(), headers(), Body} | 
                     {status_code(), Body} | request_id()</v>
-        <v>Body = string() | binary()</v>
+        <v>Body = http_string() | binary()</v>
         <v>Profile = profile() | pid()</v>
 	<d>When started <c>stand_alone</c> only the pid can be used.</d>
         <v>Reason = term()</v>
@@ -549,7 +549,7 @@
 	<v>| {verbose, VerboseMode}</v>
 	<v>| {unix_socket, UnixSocket}</v>
         <v>Proxy = {Hostname, Port}</v>
-        <v>Hostname = string()</v>
+        <v>Hostname = http_string()</v>
         <d>Example: "localhost" or "foo.bar.se"</d>
         <v>Port = integer()</v>
         <d>Example: 8080</d>
@@ -557,7 +557,7 @@
         <v>NoProxyDesc = DomainDesc | HostName | IPDesc</v>
         <v>DomainDesc = "*.Domain"</v>
         <d>Example: "*.ericsson.se"</d>
-        <v>IpDesc = string()</v>
+        <v>IpDesc = http_string()</v>
         <d>Example: "134.138" or "[FEDC:BA98" 
 	(all IP addresses starting with 134.138 or FEDC:BA98), 
 	"66.35.250.150" or "[2010:836B:4179::836B:4179]" (a complete IP address). 
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index 00e960cf71..1fd65027ee 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2009-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2009-2021. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -98,8 +98,11 @@ request(Url, Profile) ->
 
 %%--------------------------------------------------------------------------
 %% request(Method, Request, HTTPOptions, Options [, Profile]) ->
-%%           {ok, {StatusLine, Headers, Body}} | {ok, {Status, Body}} |
-%%           {ok, RequestId} | {error,Reason} | {ok, {saved_as, FilePath}
+%%           {ok, {StatusLine, Headers, Body}}
+%%         | {ok, {Status, Body}}
+%%         | {ok, RequestId}
+%%         | {ok, {saved_as, FilePath}
+%%         | {error, Reason}
 %%
 %%	Method - atom() = head | get | put | patch | post | trace |
 %%	                  options | delete 
@@ -129,10 +132,10 @@ request(Url, Profile) ->
 %%	ReasonPhrase = string()
 %%	Headers = [Header]
 %%      Header = {Field, Value}
-%%	Field = string()
-%%	Value = string()
+%%	Field = [byte()]
+%%	Value = binary() | iolist()
 %%	Body = string() | binary() | {fun(SendAcc) -> SendFunResult, SendAcc} |
-%%              {chunkify, fun(SendAcc) -> SendFunResult, SendAcc} - HTLM-code
+%%              {chunkify, fun(SendAcc) -> SendFunResult, SendAcc} - HTML-code
 %%      SendFunResult = eof | {ok, iolist(), NewSendAcc}
 %%      SendAcc = NewSendAcc = term()
 %%
@@ -140,42 +143,31 @@ request(Url, Profile) ->
 %% syncronus and asynchronous in the later case the function will
 %% return {ok, RequestId} and later on a message will be sent to the
 %% calling process on the format {http, {RequestId, {StatusLine,
-%% Headers, Body}}} or {http, {RequestId, {error, Reason}}}
+%% Headers, Body}}} or {http, {RequestId, {error, Reason}}}.
+%% Only octects are accepted in header fields and values.
 %%--------------------------------------------------------------------------
 
 request(Method, Request, HttpOptions, Options) ->
-    request(Method, Request, HttpOptions, Options, default_profile()). 
-
-request(Method, 
-	{Url, Headers, ContentType, TupleBody}, 
-	HTTPOptions, Options, Profile) 
-  when ((Method =:= post) orelse (Method =:= patch) orelse (Method =:= put) orelse (Method =:= delete)) 
-       andalso (is_atom(Profile) orelse is_pid(Profile)) andalso
-       is_list(ContentType)  andalso is_tuple(TupleBody)->
-    case check_body_gen(TupleBody) of
-	ok ->
-	    do_request(Method, {Url, Headers, ContentType, TupleBody}, HTTPOptions, Options, Profile);
-	Error ->
-	    Error
-    end;
-request(Method, 
-	{Url, Headers, ContentType, Body}, 
-	HTTPOptions, Options, Profile) 
-  when ((Method =:= post) orelse (Method =:= patch) orelse (Method =:= put) orelse (Method =:= delete)) 
-       andalso (is_atom(Profile) orelse is_pid(Profile)) andalso
-       is_list(ContentType) andalso (is_list(Body) orelse is_binary(Body)) ->
-    do_request(Method, {Url, Headers, ContentType, Body}, HTTPOptions, Options, Profile);
-
-request(Method, 
-	{Url, Headers}, 
-	HTTPOptions, Options, Profile) 
-  when (Method =:= options) orelse 
-       (Method =:= get) orelse 
-       (Method =:= put) orelse
-       (Method =:= head) orelse 
-       (Method =:= delete) orelse 
-       (Method =:= trace) andalso 
-       (is_atom(Profile) orelse is_pid(Profile)) ->
+    request(Method, Request, HttpOptions, Options, default_profile()).
+
+-define(WITH_BODY, [post, put, patch, delete]).
+-define(WITHOUT_BODY, [get, head, options, trace, put, delete]).
+
+request(Method, Request, HTTPOptions, Options, Profile)
+  when is_atom(Profile) orelse is_pid(Profile) ->
+    WithBody = lists:member(Method, ?WITH_BODY),
+    WithoutBody = lists:member(Method, ?WITHOUT_BODY),
+    case check_request(WithBody, WithoutBody, Request) of
+        ok ->
+            do_request(Method, Request,
+                       HTTPOptions, Options, Profile);
+        {error, _} = Error ->
+            Error
+    end.
+
+do_request(Method, {Url, Headers}, HTTPOptions, Options, Profile) ->
+    do_request(Method, {Url, Headers, [], []}, HTTPOptions, Options, Profile);
+do_request(Method, {Url, Headers, ContentType, Body}, HTTPOptions, Options, Profile) ->
     case normalize_and_parse_url(Url) of
 	{error, Reason, _} ->
 	    {error, Reason};
@@ -183,21 +175,27 @@ request(Method,
 	    case header_parse(Headers) of
 		{error, Reason} ->
 		    {error, Reason};
-		_ ->
-		    handle_request(Method, Url, ParsedUrl, Headers, [], [], 
-				   HTTPOptions, Options, Profile)
-	    end
+                ok ->
+                    handle_request(Method, Url,
+                                   ParsedUrl, Headers, ContentType, Body,
+                                   HTTPOptions, Options, Profile)
+            end
     end.
 
-do_request(Method, {Url, Headers, ContentType, Body}, HTTPOptions, Options, Profile) ->
-    case normalize_and_parse_url(Url) of
-	{error, Reason, _} ->
-	    {error, Reason};
-	ParsedUrl ->
-	    handle_request(Method, Url, 
-			   ParsedUrl, Headers, ContentType, Body, 
-			   HTTPOptions, Options, Profile)
-    end.
+%% Check combination of method and presence of body
+check_request(false, false, _Request) ->
+    {error, invalid_method};
+check_request(_, true, {_URL, _Headers}) ->
+    ok;
+check_request(true, _, {_URL, _Headers, ContentType, Body})
+  when is_list(ContentType)
+       andalso (is_list(Body) orelse is_binary(Body)) ->
+    ok;
+check_request(true, _, {_URL, _Headers, ContentType, Body})
+  when is_list(ContentType) andalso is_tuple(Body) ->
+    check_body_gen(Body);
+check_request(_, _, _Request) ->
+    {error, invalid_request}.
 
 %%--------------------------------------------------------------------------
 %% cancel_request(RequestId) -> ok
@@ -1253,15 +1251,21 @@ validate_headers(RequestHeaders, _, _) ->
 
 
 %%--------------------------------------------------------------------------
-%% These functions is just simple wrappers to parse specifically HTTP URIs
+%% These functions are just simple wrappers to parse specifically HTTP URIs
 %%--------------------------------------------------------------------------
 
 header_parse([]) ->
     ok;
-header_parse([{Field, Value}|T]) when is_list(Field), is_list(Value) ->    
+header_parse([{Field, Value}|T])
+  when is_list(Field)
+       andalso (is_list(Value) orelse is_binary(Value)) ->
     header_parse(T);
-header_parse(_) -> 
-    {error, {headers_error, not_strings}}.
+header_parse([{Field, _Value}| _ ])
+  when not is_list(Field) ->
+    {error, {headers_error, invalid_field}};
+header_parse([{_, _}| _]) ->
+    {error, {headers_error, invalid_value}}.
+
 child_name2info(undefined) ->
     {error, no_such_service};
 child_name2info(httpc_manager) ->
@@ -1277,9 +1281,9 @@ child_name(Pid, [_ | Children]) ->
     child_name(Pid, Children).
 
 
-check_body_gen({Fun, _}) when is_function(Fun) -> 
+check_body_gen({Fun, _}) when is_function(Fun, 1) ->
     ok;
-check_body_gen({chunkify, Fun, _}) when is_function(Fun) -> 
+check_body_gen({chunkify, Fun, _}) when is_function(Fun, 1) ->
     ok;
-check_body_gen(Gen) -> 
+check_body_gen(Gen) ->
     {error, {bad_body_generator, Gen}}.
diff --git a/lib/inets/src/http_lib/http_request.erl b/lib/inets/src/http_lib/http_request.erl
index 2510cdede2..02fa8acb80 100644
--- a/lib/inets/src/http_lib/http_request.erl
+++ b/lib/inets/src/http_lib/http_request.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %% 
-%% Copyright Ericsson AB 2005-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2005-2021. All Rights Reserved.
 %% 
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -201,107 +201,99 @@ headers(Key, Value, Headers) ->
     Headers#http_request_h{other=
 			   [{Key, Value} | Headers#http_request_h.other]}.
 
-key_value_str(Key = 'cache-control', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'cache-control');
-key_value_str(Key = connection, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.connection);
-key_value_str(Key = date, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.date);
-key_value_str(Key = pragma, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.pragma);
-key_value_str(Key = trailer, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.trailer);
-key_value_str(Key = 'transfer-encoding', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'transfer-encoding');
-key_value_str(Key = upgrade, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.upgrade);
-key_value_str(Key = via, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.via);
-key_value_str(Key = warning, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.warning);
-key_value_str(Key = accept, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.accept);
-key_value_str(Key = 'accept-charset', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'accept-charset');
-key_value_str(Key = 'accept-encoding', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'accept-encoding');
-key_value_str(Key = 'accept-language', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'accept-language');
-key_value_str(Key = authorization, Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.authorization);
-key_value_str(Key = expect, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.expect);
-key_value_str(Key = from, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.from);
-key_value_str(Key = host, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.host);
-key_value_str(Key = 'if-match', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'if-match');
-key_value_str(Key = 'if-modified-since', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'if-modified-since');
-key_value_str(Key = 'if-none-match', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'if-none-match');
-key_value_str(Key = 'if-range', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'if-range');
-key_value_str(Key = 'if-unmodified-since', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'if-unmodified-since');
-key_value_str(Key = 'max-forwards', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'max-forwards');
-key_value_str(Key = 'proxy-authorization', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'proxy-authorization');
-key_value_str(Key = range, Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.range);
-key_value_str(Key = referer, Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.referer);
-key_value_str(Key = te, Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.te);
-key_value_str(Key = 'user-agent', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'user-agent');
-key_value_str(Key = allow, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.allow);
-key_value_str(Key = 'content-encoding', Headers) ->
-    key_value_str(atom_to_list(Key), 
-		    Headers#http_request_h.'content-encoding');
-key_value_str(Key = 'content-language', Headers) ->
-    key_value_str(atom_to_list(Key), 
-		    Headers#http_request_h.'content-language');
-key_value_str(Key = 'content-length', Headers) ->
-    key_value_str(atom_to_list(Key), 
-		    Headers#http_request_h.'content-length');
-key_value_str(Key = 'content-location', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'content-location');
-key_value_str(Key = 'content-md5', Headers) ->
-    key_value_str(atom_to_list(Key),
-		    Headers#http_request_h.'content-md5');
-key_value_str(Key = 'content-range', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'content-range');
-key_value_str(Key = 'content-type', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'content-type');
-key_value_str(Key = expires, Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.expires);
-key_value_str(Key = 'last-modified', Headers) ->
-    key_value_str(atom_to_list(Key), Headers#http_request_h.'last-modified');
-key_value_str(_, undefined) ->
-    undefined;
-key_value_str(Key, Value)  ->
-    Key ++ ": " ++ Value ++ ?CRLF.
+key_value_str(Key, Headers) ->
+    case key_value(Key, Headers) of
+        undefined -> undefined;
+        Value ->
+            mk_key_value_str(atom_to_list(Key), Value)
+    end.
+
+key_value('cache-control', Headers) ->
+    Headers#http_request_h.'cache-control';
+key_value(connection, Headers) ->
+    Headers#http_request_h.connection;
+key_value(date, Headers) ->
+    Headers#http_request_h.date;
+key_value(pragma, Headers) ->
+    Headers#http_request_h.pragma;
+key_value(trailer, Headers) ->
+    Headers#http_request_h.trailer;
+key_value('transfer-encoding', Headers) ->
+    Headers#http_request_h.'transfer-encoding';
+key_value(upgrade, Headers) ->
+    Headers#http_request_h.upgrade;
+key_value(via, Headers) ->
+    Headers#http_request_h.via;
+key_value(warning, Headers) ->
+    Headers#http_request_h.warning;
+key_value(accept, Headers) ->
+    Headers#http_request_h.accept;
+key_value('accept-charset', Headers) ->
+    Headers#http_request_h.'accept-charset';
+key_value('accept-encoding', Headers) ->
+    Headers#http_request_h.'accept-encoding';
+key_value('accept-language', Headers) ->
+    Headers#http_request_h.'accept-language';
+key_value(authorization, Headers) ->
+    Headers#http_request_h.authorization;
+key_value(expect, Headers) ->
+    Headers#http_request_h.expect;
+key_value(from, Headers) ->
+    Headers#http_request_h.from;
+key_value(host, Headers) ->
+    Headers#http_request_h.host;
+key_value('if-match', Headers) ->
+    Headers#http_request_h.'if-match';
+key_value('if-modified-since', Headers) ->
+    Headers#http_request_h.'if-modified-since';
+key_value('if-none-match', Headers) ->
+    Headers#http_request_h.'if-none-match';
+key_value('if-range', Headers) ->
+    Headers#http_request_h.'if-range';
+key_value('if-unmodified-since', Headers) ->
+    Headers#http_request_h.'if-unmodified-since';
+key_value('max-forwards', Headers) ->
+    Headers#http_request_h.'max-forwards';
+key_value('proxy-authorization', Headers) ->
+    Headers#http_request_h.'proxy-authorization';
+key_value(range, Headers) ->
+    Headers#http_request_h.range;
+key_value(referer, Headers) ->
+    Headers#http_request_h.referer;
+key_value(te, Headers) ->
+    Headers#http_request_h.te;
+key_value('user-agent', Headers) ->
+    Headers#http_request_h.'user-agent';
+key_value(allow, Headers) ->
+    Headers#http_request_h.allow;
+key_value('content-encoding', Headers) ->
+    Headers#http_request_h.'content-encoding';
+key_value('content-language', Headers) ->
+    Headers#http_request_h.'content-language';
+key_value('content-length', Headers) ->
+    Headers#http_request_h.'content-length';
+key_value('content-location', Headers) ->
+    Headers#http_request_h.'content-location';
+key_value('content-md5', Headers) ->
+    Headers#http_request_h.'content-md5';
+key_value('content-range', Headers) ->
+    Headers#http_request_h.'content-range';
+key_value('content-type', Headers) ->
+    Headers#http_request_h.'content-type';
+key_value(expires, Headers) ->
+    Headers#http_request_h.expires;
+key_value('last-modified', Headers) ->
+    Headers#http_request_h.'last-modified'.
 
 headers_other([], Headers) ->
     Headers;
-headers_other([{Key,Value} | Rest], Headers) ->
-    Header = Key ++ ": " ++ Value ++ ?CRLF,
-    headers_other(Rest, [Header | Headers]).
+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.
+
+value_to_list(Binary) when is_binary(Binary) ->
+    binary_to_list(Binary);
+value_to_list(List) when is_list(List) ->
+    binary_to_list(iolist_to_binary(List)).
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index b755c2ebef..f7eff5822d 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %% 
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2021. All Rights Reserved.
 %% 
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -98,6 +98,30 @@ real_requests()->
      emulate_lower_versions,
      headers,
      headers_as_is,
+     header_type_0,
+     header_type_1,
+     header_type_2,
+     header_type_3,
+     header_type_4,
+     header_type_5,
+     header_type_6,
+     header_type_7,
+     header_type_8,
+     header_type_9,
+     header_type_10,
+     header_type_11,
+     header_type_12,
+     header_type_13,
+     header_type_14,
+     header_type_15,
+     header_type_16,
+     header_type_17,
+     header_type_18,
+     header_type_19,
+     header_type_20,
+     header_type_21,
+     header_type_22,
+     header_type_23,
      empty_body,
      stream,
      stream_to_pid,
@@ -105,8 +129,11 @@ real_requests()->
      stream_through_mfa,
      streaming_error,
      inet_opts,
-     invalid_headers,
+     invalid_headers_key,
+     invalid_headers_value,
      invalid_body,
+     invalid_body_fun,
+     invalid_method,
      no_scheme,
      invalid_uri,
      binary_url
@@ -1217,23 +1244,106 @@ headers_conflict_chunked_with_length(Config) when is_list(Config) ->
 
 %%-------------------------------------------------------------------------
 
-invalid_headers(Config) ->
-    Request  = {url(group_name(Config), "/dummy.html", Config), [{"cookie", undefined}]},
-    {error, _} = httpc:request(get, Request, [], []).
+
+invalid_headers_key(Config) ->
+    Request  = {url(group_name(Config), "/dummy.html", Config),
+                [{cookie, "valid cookie"}]},
+    {error, {headers_error, invalid_field}} =
+        httpc:request(get, Request, [], []).
+
+invalid_headers_value(Config) ->
+    Request  = {url(group_name(Config), "/dummy.html", Config),
+                [{"cookie", atom_value}]},
+    {error, {headers_error, invalid_value}} =
+        httpc:request(get, Request, [], []).
 
 %%-------------------------------------------------------------------------
 
-invalid_body(Config) ->
+%% Doc not generated, but we can live without that.  It should be
+%%  [{doc, "Header type test"}].
+-define(HDR_TYPE_TEST(Name, Method, Value),
+        Name(Config) when is_list(Config) ->
+            test_header_type(Config, Method, Value)).
+
+?HDR_TYPE_TEST(header_type_0, get, "stringheader").
+?HDR_TYPE_TEST(header_type_1, get, <<"binary">>).
+?HDR_TYPE_TEST(header_type_2, get, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_3, head, "stringheader").
+?HDR_TYPE_TEST(header_type_4, head, <<"binary">>).
+?HDR_TYPE_TEST(header_type_5, head, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_6, post, "stringheader").
+?HDR_TYPE_TEST(header_type_7, post, <<"binary">>).
+?HDR_TYPE_TEST(header_type_8, post, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_9, put, "stringheader").
+?HDR_TYPE_TEST(header_type_10, put, <<"binary">>).
+?HDR_TYPE_TEST(header_type_11, put, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_12, delete, "stringheader").
+?HDR_TYPE_TEST(header_type_13, delete, <<"binary">>).
+?HDR_TYPE_TEST(header_type_14, delete, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_15, trace, "stringheader").
+?HDR_TYPE_TEST(header_type_16, trace, <<"binary">>).
+?HDR_TYPE_TEST(header_type_17, trace, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_18, patch, "stringheader").
+?HDR_TYPE_TEST(header_type_19, patch, <<"binary">>).
+?HDR_TYPE_TEST(header_type_20, patch, ["an", <<"iolist">>]).
+?HDR_TYPE_TEST(header_type_21, options, "stringheader").
+?HDR_TYPE_TEST(header_type_22, options, <<"binary">>).
+?HDR_TYPE_TEST(header_type_23, options, ["an", <<"iolist">>]).
+
+test_header_type(Config, Method, Value) ->
+    {Method, Value, {ok, _Data}} =
+        {Method, Value,
+         httpc:request(Method,
+                      make_request(Config, Method, Value),
+                      [],
+                      [])}.
+
+make_request(Config, Method, Value) ->
     URL = url(group_name(Config), "/dummy.html", Config),
-    try 
-	httpc:request(post, {URL, [], <<"text/plain">>, "foobar"},
-		      [], []),
-	ct:fail(accepted_invalid_input)
-    catch 
-	error:function_clause ->
-	    ok
+    Headers = [{"other-header", Value},
+               {"user-agent", Value}],
+    %% Generate request with or without body, depending on method.
+    case method_type(Method) of
+        read ->
+            {URL, Headers};
+        write ->
+            {URL, Headers, "text/plain", ""}
     end.
 
+method_type(Method) ->
+    case Method of
+        get -> read;
+        head -> read;
+        options -> read;
+        trace -> read;
+        post -> write;
+        put -> write;
+        delete -> write;
+        patch -> write
+    end.
+
+%%-------------------------------------------------------------------------
+
+invalid_body(Config) ->
+    URL = url(group_name(Config), "/dummy.html", Config),
+    {error, invalid_request} =
+        httpc:request(post, {URL, [], <<"text/plain">>, "foobar"},
+                      [], []).
+
+invalid_body_fun(Config) ->
+    URL = url(group_name(Config), "/dummy.html", Config),
+    BodyFun = fun() -> body_part end,
+    {error, {bad_body_generator, _}} =
+        httpc:request(post, {URL, [], "text/plain", {BodyFun, init}},
+                      [], []).
+
+
+invalid_method(Config) ->
+    URL = url(group_name(Config), "/dummy.html", Config),
+    {error, invalid_method} =
+        httpc:request(past, {URL, [], <<"text/plain">>, "foobar"},
+                      [], []).
+
 %%-------------------------------------------------------------------------
 
 binary_url(Config) ->
@@ -1948,7 +2058,7 @@ setup_server_dirs(ServerRoot, DocRoot, DataDir) ->
 		  "cgi_echo"
 	  end,
     
-    inets_test_lib:copy_file(Cgi, DataDir, CgiDir),
+    {ok, _} = inets_test_lib:copy_file(Cgi, DataDir, CgiDir),
     AbsCgi = filename:join([CgiDir, Cgi]),
     {ok, FileInfo} = file:read_file_info(AbsCgi),
     ok = file:write_file_info(AbsCgi, FileInfo#file_info{mode = 8#00755}).
-- 
2.31.1

openSUSE Build Service is sponsored by