File 3401-inets-remove-support-of-http-0.9-for-httpc-in-inets.patch of Package erlang
From 8c64b9200f2db2e0838c0debf63355f664c2821d Mon Sep 17 00:00:00 2001
From: Ao Song <andy@erlang.org>
Date: Mon, 27 Jul 2020 18:31:09 +0200
Subject: [PATCH] inets: remove support of http 0.9 for httpc in inets
Change-Id: If7a25822fffecedee60d2047681b2be3780f10b2
---
lib/inets/doc/src/httpc.xml | 10 ++++----
lib/inets/src/http_client/httpc.erl | 4 ----
lib/inets/src/http_client/httpc_handler.erl | 25 ++++----------------
lib/inets/src/http_client/httpc_internal.hrl | 2 +-
lib/inets/src/http_client/httpc_manager.erl | 13 ----------
lib/inets/src/http_client/httpc_request.erl | 17 +------------
lib/inets/src/http_client/httpc_response.erl | 2 --
lib/inets/test/httpc_SUITE.erl | 5 +---
8 files changed, 13 insertions(+), 65 deletions(-)
diff --git a/lib/inets/doc/src/httpc.xml b/lib/inets/doc/src/httpc.xml
index 42a6a5b43d..f579acf7ce 100644
--- a/lib/inets/doc/src/httpc.xml
+++ b/lib/inets/doc/src/httpc.xml
@@ -373,11 +373,11 @@
<tag><c><![CDATA[version]]></c></tag>
<item>
- <p>Can be used to make the client act as an <c>HTTP/1.0</c> or
- <c>HTTP/0.9</c> client. By default this is an <c>HTTP/1.1</c>
- client. When using <c>HTTP/1.0</c> persistent connections are
- not used.</p>
- <p>Default is the string <c>"HTTP/1.1"</c>.</p>
+ <p>Can be used to make the client act as an <c>HTTP/1.0</c>
+ client. By default this is an <c>HTTP/1.1</c>
+ client. When using <c>HTTP/1.0</c> persistent connections are
+ not used.</p>
+ <p>Default is the string <c>"HTTP/1.1"</c>.</p>
</item>
<tag><c><![CDATA[relaxed]]></c></tag>
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index 28dd97b155..2cb982ab83 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -638,10 +638,6 @@ handle_answer(RequestId, true, Options) ->
{error, Reason}
end.
-return_answer(Options, {{"HTTP/0.9",_,_}, _, BinBody}) ->
- Body = maybe_format_body(BinBody, Options),
- {ok, Body};
-
return_answer(Options, {StatusLine, Headers, BinBody}) ->
Body = maybe_format_body(BinBody, Options),
case proplists:get_value(full_result, Options, true) of
diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index 9135935567..74f01bea62 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -833,7 +833,7 @@ connect_and_send_first_request(Address, Request, #state{options = Options0} = St
TmpState = State#state{request = Request,
session = Session,
mfa = init_mfa(Request, State),
- status_line = init_status_line(Request),
+ status_line = undefined,
headers = undefined,
body = undefined,
status = new},
@@ -1467,21 +1467,8 @@ is_no_proxy_dest_address(Dest, AddressPart) ->
lists:prefix(AddressPart, Dest).
init_mfa(#request{settings = Settings}, State) ->
- case Settings#http_options.version of
- "HTTP/0.9" ->
- {httpc_response, whole_body, [<<>>, -1]};
- _ ->
- Relaxed = Settings#http_options.relaxed,
- {httpc_response, parse, [State#state.max_header_size, Relaxed]}
- end.
-
-init_status_line(#request{settings = Settings}) ->
- case Settings#http_options.version of
- "HTTP/0.9" ->
- {"HTTP/0.9", 200, "OK"};
- _ ->
- undefined
- end.
+ Relaxed = Settings#http_options.relaxed,
+ {httpc_response, parse, [State#state.max_header_size, Relaxed]}.
socket_type(#request{scheme = http}) ->
ip_comm;
@@ -1599,8 +1586,7 @@ tls_tunnel(Address, Request, #state{session = #session{} = Session} = State,
TmpState = State#state{request = UpgradeRequest,
%% session = Session,
mfa = init_mfa(UpgradeRequest, State),
- status_line =
- init_status_line(UpgradeRequest),
+ status_line = undefined,
headers = undefined,
body = undefined},
activate_once(Session),
@@ -1673,8 +1659,7 @@ tls_upgrade(#state{status =
NewState = State#state{session = Session,
request = Request,
mfa = init_mfa(Request, State),
- status_line =
- init_status_line(Request),
+ status_line = undefined,
headers = undefined,
body = undefined,
status = new
diff --git a/lib/inets/src/http_client/httpc_internal.hrl b/lib/inets/src/http_client/httpc_internal.hrl
index a14d8aa71b..31a4e0d350 100644
--- a/lib/inets/src/http_client/httpc_internal.hrl
+++ b/lib/inets/src/http_client/httpc_internal.hrl
@@ -43,7 +43,7 @@
%%% HTTP Client per request settings
-record(http_options,
{
- %% "HTTP/1.1" | "HTTP/1.0" | "HTTP/0.9"
+ %% "HTTP/1.1" | "HTTP/1.0"
version :: 'undefined' | string(),
%% ms before a request times out
diff --git a/lib/inets/src/http_client/httpc_manager.erl b/lib/inets/src/http_client/httpc_manager.erl
index ba561100a1..542269f0ea 100644
--- a/lib/inets/src/http_client/httpc_manager.erl
+++ b/lib/inets/src/http_client/httpc_manager.erl
@@ -724,19 +724,6 @@ get_handler_info(Tab) ->
Handlers2 = sort_handlers(Handlers1),
[{Pid, Reqs, httpc_handler:info(Pid)} || {Pid, Reqs} <- Handlers2].
-handle_request(#request{settings =
- #http_options{version = "HTTP/0.9"}} = Request,
- State) ->
- %% Act as an HTTP/0.9 client that does not know anything
- %% about persistent connections
-
- NewRequest = handle_cookies(generate_request_id(Request), State),
- NewHeaders =
- (NewRequest#request.headers)#http_request_h{connection
- = undefined},
- start_handler(NewRequest#request{headers = NewHeaders}, State),
- {reply, {ok, NewRequest#request.id}, State};
-
handle_request(#request{settings =
#http_options{version = "HTTP/1.0"}} = Request,
State) ->
diff --git a/lib/inets/src/http_client/httpc_request.erl b/lib/inets/src/http_client/httpc_request.erl
index 0f20d93bc1..a0bd1b6471 100644
--- a/lib/inets/src/http_client/httpc_request.erl
+++ b/lib/inets/src/http_client/httpc_request.erl
@@ -120,8 +120,7 @@ do_send_body(SocketType, Socket, Method, Uri, Version, Headers,
do_send_body(SocketType, Socket, Method, Uri, Version, Headers, Body) ->
?hcrt("create message", [{body, Body}]),
Message = [method(Method), " ", Uri, " ",
- version(Version), ?CRLF,
- headers(Headers, Version), ?CRLF, Body],
+ Version, ?CRLF, Headers, ?CRLF, Body],
?hcrd("send", [{message, Message}]),
http_transport:send(SocketType, Socket, Message).
@@ -256,20 +255,6 @@ handle_content_type(Headers, ContentType) ->
method(Method) ->
http_util:to_upper(atom_to_list(Method)).
-version("HTTP/0.9") ->
- "";
-version(Version) ->
- Version.
-
-headers(_, "HTTP/0.9") ->
- "";
-%% HTTP 1.1 headers not present in HTTP 1.0 should be
-%% consider as unknown extension headers that should be
-%% ignored.
-headers(Headers, _) ->
- Headers.
-
-
http_headers([], Headers) ->
lists:flatten(Headers);
http_headers([{Key,Value} | Rest], Headers) ->
diff --git a/lib/inets/src/http_client/httpc_response.erl b/lib/inets/src/http_client/httpc_response.erl
index 538cdd0e87..ca138c9a3d 100644
--- a/lib/inets/src/http_client/httpc_response.erl
+++ b/lib/inets/src/http_client/httpc_response.erl
@@ -587,8 +587,6 @@ is_server_closing(Headers) when is_record(Headers, http_response_h) ->
false
end.
-format_response({{"HTTP/0.9", _, _} = StatusLine, _, Body}) ->
- {{StatusLine, [], Body}, <<>>};
format_response({StatusLine, Headers, Body = <<>>}) ->
{{StatusLine, http_response:header_list(Headers), Body}, <<>>};
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index bfe3980727..19d749e93d 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -1057,14 +1057,11 @@ invalid_chunk_size(Config) when is_list(Config) ->
%%-------------------------------------------------------------------------
emulate_lower_versions(doc) ->
- [{doc, "Perform request as 0.9 and 1.0 clients."}];
+ [{doc, "Perform request as 1.0 clients."}];
emulate_lower_versions(Config) when is_list(Config) ->
URL = url(group_name(Config), "/dummy.html", Config),
- {ok, Body0} =
- httpc:request(get, {URL, []}, [{version, "HTTP/0.9"}], []),
- inets_test_lib:check_body(Body0),
{ok, {{"HTTP/1.0", 200, _}, [_ | _], Body1 = [_ | _]}} =
httpc:request(get, {URL, []}, [{version, "HTTP/1.0"}], []),
inets_test_lib:check_body(Body1),
--
2.26.2