File 3181-inets-httpd-remove-use-of-http_uri-and-mod_esi-eval-.patch of Package erlang

From ef6c1910b6a8c05c6a40b50be9491fe13a6e0eab Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 18 Mar 2020 11:01:23 +0100
Subject: [PATCH] inets: httpd - remove use of http_uri and mod_esi eval API

Backport form OTP-23, this is potentially incompatible but
using mod_esi eval has been deprecated for many years and
may be considered a vulnerability.

The removal of http_uri also further motivates removal of deprecated
mod_esi eval API as it makes uses of non standard URIs
---
 lib/inets/doc/src/http_server.xml                  |  30 ----
 lib/inets/doc/src/http_uri.xml                     |   2 +-
 lib/inets/doc/src/httpd.xml                        |  10 +-
 lib/inets/src/http_client/httpc_handler.erl        |   2 +-
 lib/inets/src/http_client/httpc_manager.erl        |  35 +++--
 lib/inets/src/http_server/httpd.erl                |  15 +-
 lib/inets/src/http_server/httpd_example.erl        | 151 +++++++++++++--------
 lib/inets/src/http_server/httpd_request.erl        |  30 +---
 .../src/http_server/httpd_request_handler.erl      |   8 +-
 lib/inets/src/http_server/httpd_util.erl           | 115 +++++-----------
 lib/inets/src/http_server/mod_dir.erl              |   4 +-
 lib/inets/src/http_server/mod_esi.erl              | 123 +----------------
 lib/inets/src/inets_app/inets.app.src              |   4 +-
 lib/inets/test/http_format_SUITE.erl               |  52 ++++---
 lib/inets/test/httpd_SUITE.erl                     |  63 +++------
 lib/inets/test/httpd_basic_SUITE.erl               |   4 +-
 lib/inets/test/httpd_test_lib.erl                  |   4 +-
 17 files changed, 225 insertions(+), 427 deletions(-)

diff --git a/lib/inets/doc/src/http_server.xml b/lib/inets/doc/src/http_server.xml
index 65b3dcde95..d6fe9dc6a7 100644
--- a/lib/inets/doc/src/http_server.xml
+++ b/lib/inets/doc/src/http_server.xml
@@ -393,36 +393,6 @@ http://your.server.org/***/Module[:/]Function(?QueryString|/PathInfo)</code>
 	    see <seealso marker="mod_esi">mod_esi(3)</seealso>.</p>
         </section>
 
-        <section>
-          <title>EVAL Scheme</title>
-          <p>The eval scheme is straight-forward and does not mimic the
-            behavior of plain CGI. An URL that calls an Erlang <c>eval</c>
-            function has the following syntax:</p>
-          <code type="none">
-http://your.server.org/***/Mod:Func(Arg1,...,ArgN)</code>
-          <p>*** depends on how the ErlScriptAlias config
-            directive has been used.</p>
-          <p>The module <c>Mod</c> referred to must be found in the code
-            path and data returned by the function <c>Func</c> is passed
-            back to the client. Data returned from the
-            function must take the form as specified in
-            the CGI specification. For implementation details of the ESI 
-	    callback function, 
-	    see <seealso marker="mod_esi">mod_esi(3)</seealso>.</p>
-          <note>
-            <p>The eval scheme can seriously threaten the
-              integrity of the Erlang node housing a web server, for
-              example:</p>
-            <code type="none">
-http://your.server.org/eval?httpd_example:print(atom_to_list(apply(erlang,halt,[])))</code>
-            <p>This effectively closes down the Erlang node.
-              Therefore, use the erl scheme instead, until this
-              security breach is fixed.</p>
-            <p>Today there are no good ways of solving this problem
-              and therefore the eval scheme can be removed in future
-              release of <c>Inets</c>.</p>
-          </note>
-        </section>
       </section>
     </section>
 
diff --git a/lib/inets/doc/src/http_uri.xml b/lib/inets/doc/src/http_uri.xml
index 6d3547f4fe..eda477da0c 100644
--- a/lib/inets/doc/src/http_uri.xml
+++ b/lib/inets/doc/src/http_uri.xml
@@ -31,7 +31,7 @@
   </header>
 
   <module since="OTP R15B01">http_uri</module>
-  <modulesummary>URI utility module</modulesummary>
+  <modulesummary>Old URI utility module, use uri_string instead</modulesummary>
 
   <description>
     <p>This module provides utility functions for working with URIs, 
diff --git a/lib/inets/doc/src/httpd.xml b/lib/inets/doc/src/httpd.xml
index 987f0c3cf4..e30c63e03b 100644
--- a/lib/inets/doc/src/httpd.xml
+++ b/lib/inets/doc/src/httpd.xml
@@ -663,16 +663,8 @@ Transport: TLS
 	<c>mod_esi:deliver/2</c>. Default is <c>15</c>. This is only relevant
 	for scripts that use the erl scheme.</p>
       </item>
-
-      <tag><marker id="prop_esi_timeout"></marker>{eval_script_alias, {URLPath, [AllowedModule]}}</tag>
-      <item>
-	<p><c>URLPath = string()</c> and <c>AllowedModule = atom()</c>.
-	Same as <c>erl_script_alias</c> but for scripts
-	using the eval scheme. This is only supported
-	for backwards compatibility. The eval scheme is deprecated.</p>
-      </item>
     </taglist>
-
+    
     <marker id="props_log"></marker>
     <p><em>Log Properties - Requires mod_log</em></p>
     <taglist>
diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index b1c5cf13bb..3f91ae062c 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -1637,7 +1637,7 @@ host_header(#http_request_h{host = Host}, _) ->
 
 %% Handles headers_as_is
 host_header(_, URI) ->
-    {ok, {_, _, Host, _, _, _}} =  http_uri:parse(URI),
+    #{host := Host} = uri_string:parse(URI),
     Host.
 
 tls_upgrade(#state{status = 
diff --git a/lib/inets/src/http_client/httpc_manager.erl b/lib/inets/src/http_client/httpc_manager.erl
index 0dc0483fa9..ba561100a1 100644
--- a/lib/inets/src/http_client/httpc_manager.erl
+++ b/lib/inets/src/http_client/httpc_manager.erl
@@ -472,10 +472,10 @@ handle_call(which_cookies, _, #state{cookie_db = CookieDb} = State) ->
 handle_call({which_cookies, Url, Options}, _, 
 	    #state{cookie_db = CookieDb} = State) ->
     ?hcrv("which cookies", [{url, Url}, {options, Options}]),
-    case uri_parse(Url, Options) of
-	{ok, {Scheme, _, Host, Port, Path, _}} ->
+    case uri_parse(Url) of
+	{ok, {Scheme, Host, Port, Path}} ->
 	    CookieHeaders = 
-		httpc_cookie:header(CookieDb, Scheme, {Host, Port}, Path),
+		httpc_cookie:header(CookieDb, erlang:list_to_existing_atom(Scheme), {Host, Port}, Path),
 	    {reply, CookieHeaders, State};
 	{error, _} = ERROR ->
 	    {reply, ERROR, State}
@@ -948,14 +948,31 @@ make_db_name(ProfileName, Post) ->
 %%--------------------------------------------------------------------------
 %% These functions is just simple wrappers to parse specifically HTTP URIs
 %%--------------------------------------------------------------------------
+uri_parse(URI) ->
+    case uri_string:parse(uri_string:normalize(URI)) of
+        #{scheme := Scheme,
+          host := Host,
+          port := Port,
+          path := Path} ->
+            {ok, {Scheme, Host, Port, Path}};    
+        #{scheme := Scheme,
+          host := Host,
+          path := Path} ->
+            {ok, {Scheme, Host, scheme_default_port(Scheme), Path}};
+        Other ->
+            {error, maybe_error(Other)}
+    end.
 
-scheme_defaults() ->
-    [{http, 80}, {https, 443}].
-
-uri_parse(URI, Opts) ->
-    http_uri:parse(URI, [{scheme_defaults, scheme_defaults()} | Opts]).
-
+maybe_error({error, Atom, Term}) ->
+    {Atom, Term};
+maybe_error(Other) ->
+    {unexpected, Other}.
 
+scheme_default_port("http") ->
+    80;
+scheme_default_port("https") ->
+    443.
+                                
 %%--------------------------------------------------------------------------
 
 
diff --git a/lib/inets/src/http_server/httpd.erl b/lib/inets/src/http_server/httpd.erl
index f4b53ce129..b4d569491a 100644
--- a/lib/inets/src/http_server/httpd.erl
+++ b/lib/inets/src/http_server/httpd.erl
@@ -49,8 +49,7 @@
 %%%========================================================================
 
 parse_query(String) ->
-  SplitString = re:split(String,"[&;]", [{return, list}]),
-  foreach(SplitString).
+    uri_string:dissect_query(String).
 
 reload_config(Config = [Value| _], Mode) when is_tuple(Value) ->
     do_reload_config(Config, Mode);
@@ -260,18 +259,6 @@ unblock(Addr, Port, Profile) when is_integer(Port) ->
 	    {error,not_started}
     end.
 
-foreach([]) ->
-  [];
-foreach([KeyValue|Rest]) ->
-    Plus2Space = re:replace(KeyValue,"[\+]"," ", [{return,list}, global]),
-    case re:split(Plus2Space,"=", [{return, list}]) of
-	[Key|Value] ->
-	    [{http_uri:decode(Key),
-	      http_uri:decode(lists:flatten(Value))}|foreach(Rest)];
-	_ ->
-	    foreach(Rest)
-    end.
-
 
 make_name(Addr, Port, Profile) ->
     httpd_util:make_name("httpd", Addr, Port, Profile).
diff --git a/lib/inets/src/http_server/httpd_example.erl b/lib/inets/src/http_server/httpd_example.erl
index 3c25ca336f..78b781aa96 100644
--- a/lib/inets/src/http_server/httpd_example.erl
+++ b/lib/inets/src/http_server/httpd_example.erl
@@ -19,13 +19,27 @@
 %%
 %%
 -module(httpd_example).
--export([print/1]).
--export([get/2, put/2, post/2, yahoo/2, test1/2, get_bin/2, peer/2,new_status_and_location/2]).
 
--export([newformat/3, post_chunked/3, post_204/3, ignore_invalid_header/3]).
-%% These are used by the inets test-suite
--export([delay/1, chunk_timeout/3, get_chunks/3]).
+-export([print/3, 
+         get/3, 
+         put/3, 
+         post/3, 
+         yahoo/3, 
+         test1/3, 
+         get_bin/3, 
+         peer/3, 
+         new_status_and_location/3,
+         newformat/3, 
+         post_chunked/3, 
+         post_204/3, 
+         ignore_invalid_header/3, 
+         delay/3, 
+         chunk_timeout/3, 
+         get_chunks/3]).
 
+%% ------------------------------------------------------
+print(SessionID, _Env, Input) ->
+    mod_esi:deliver(SessionID, print(Input)).
 
 print(String) ->
   [header(),
@@ -33,7 +47,11 @@ print(String) ->
    String++"\n",
    footer()].
 
-test1(Env, []) ->
+%% ------------------------------------------------------
+test1(SessionID, Env, _Input) ->
+    mod_esi:deliver(SessionID, test1(Env)).
+
+test1(Env) ->
     io:format("Env:~p~n",[Env]),
     ["<html>",
      "<head>",
@@ -44,9 +62,10 @@ test1(Env, []) ->
      "<h2>Stuff</h2>",
      "</body>",
      "</html>"].
-
-
-get(_Env,[]) ->
+%% ------------------------------------------------------
+get(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, do_get(Env, Input)).
+do_get(_Env,[]) ->
   [header(),
    top("GET Example"),
    "<FORM ACTION=\"/cgi-bin/erl/httpd_example:get\" METHOD=GET>	
@@ -55,24 +74,35 @@ get(_Env,[]) ->
 <INPUT TYPE=\"submit\"><BR>
 </FORM>" ++ "\n",
    footer()];
-
-get(Env,Input) ->
+do_get(Env,Input) ->
   default(Env,Input).
+%% ------------------------------------------------------
+put(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, do_put(Env, Input)).
 
-put(Env,{Input,_Body}) ->
+do_put(Env,{Input,_Body}) ->
     default(Env,Input);
-put(Env,Input) ->
+do_put(Env,Input) ->
     default(Env,Input).
+%% ------------------------------------------------------
+get_bin(SessionID, Env, Input) ->
+    Header = header(),
+    IoData = get_bin(Env, Input),
+    Size = erlang:iolist_size(IoData),        
+    mod_esi:deliver(SessionID, ["Content-Length:" ++ erlang:integer_to_list(Size) ++ "\r\n", 
+                                Header, IoData]).
 
 get_bin(_Env,_Input) ->
-    [list_to_binary(header()),
-     list_to_binary(top("GET Example")),
+    [list_to_binary(top("GET Example")),
      list_to_binary("<FORM ACTION=\"/cgi-bin/erl/httpd_example:get\" METHOD=GET>	
 <B>Input:</B> <INPUT TYPE=\"text\" NAME=\"input1\">
 <INPUT TYPE=\"text\" NAME=\"input2\">
 <INPUT TYPE=\"submit\"><BR>
 </FORM>" ++ "\n"),
    list_to_binary(footer())].
+%% ------------------------------------------------------
+post(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, post(Env, Input)).
 
 post(_Env,[]) ->
   [header(),
@@ -86,21 +116,22 @@ post(_Env,[]) ->
 
 post(Env,Input) ->
   default(Env,Input).
+%% ------------------------------------------------------
+yahoo(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, yahoo(Env, Input)).
 
 yahoo(_Env,_Input) ->
   "Location: http://www.yahoo.com\r\n\r\n".
+%% ------------------------------------------------------
+new_status_and_location(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, new_status_and_location(Env, Input)).
 
 new_status_and_location(_Env,_Input) ->
   "status:201 Created\r\n Location: http://www.yahoo.com\r\n\r\n".
+%% ------------------------------------------------------
 
-default(Env,Input) ->
-  [header(),
-   top("Default Example"),
-   "<B>Environment:</B> ",io_lib:format("~p",[Env]),"<BR>\n",
-   "<B>Input:</B> ",Input,"<BR>\n",
-   "<B>Parsed Input:</B> ",
-   io_lib:format("~p",[httpd:parse_query(Input)]),"\n",
-   footer()].
+peer(SessionID, Env, Input) ->
+    mod_esi:deliver(SessionID, peer(Env, Input)).
 
 peer(Env, _Input) ->
    Header = 
@@ -116,23 +147,7 @@ peer(Env, _Input) ->
    io_lib:format("~p",[proplists:get_value(peer_cert, Env)]),"\n",
    footer()].	   	 
 
-header() ->
-  header("text/html").
-header(MimeType) ->
-  "Content-type: " ++ MimeType ++ "\r\n\r\n".
-header(MimeType, Other) ->
-  "Content-type: " ++ MimeType ++ "\r\n" ++ Other ++ "\r\n\r\n".			 
-
-top(Title) ->
-  "<HTML>
-<HEAD>
-<TITLE>" ++ Title ++ "</TITLE>
-</HEAD>
-<BODY>\n".
-
-footer() ->
-  "</BODY>
-</HTML>\n".
+%% ------------------------------------------------------
 
 post_chunked(_SessionID, _Env, {first, _Body} = _Bodychunk) ->
     {continue, {state, 1}};
@@ -150,11 +165,13 @@ post_chunked(SessionID, _Env, {last, _Body, undefined} = _Bodychunk) ->
     mod_esi:deliver(SessionID, footer());
 post_chunked(_, _, _Body) ->
     exit(body_not_chunked).
+%% ------------------------------------------------------
 
 post_204(SessionID, _Env, _Input) ->
     mod_esi:deliver(SessionID,
                     ["Status: 204 No Content" ++ "\r\n\r\n"]),
     mod_esi:deliver(SessionID, []).
+%% ------------------------------------------------------
 
 ignore_invalid_header(SessionID, Env, _Input) ->
     case proplists:get_value(content_length, Env, undefined) of
@@ -165,7 +182,8 @@ ignore_invalid_header(SessionID, Env, _Input) ->
             mod_esi:deliver(SessionID,
                             ["Status: 500 Internal Server Error" ++ "\r\n\r\n"])
     end.            
-                         
+%% ------------------------------------------------------
+                       
 newformat(SessionID,_,_) ->
     mod_esi:deliver(SessionID, "Content-Type:text/html\r\n\r\n"),
     mod_esi:deliver(SessionID, top("new esi format test")),
@@ -176,28 +194,16 @@ newformat(SessionID,_,_) ->
  
 %% ------------------------------------------------------
 
-delay(Time) when is_integer(Time) ->
-    i("httpd_example:delay(~p) -> do the delay",[Time]),
-    sleep(Time),
-    i("httpd_example:delay(~p) -> done, now reply",[Time]),
-    delay_reply("delay ok");
-delay(Time) when is_list(Time) ->
-    delay(list_to_integer(Time));
-delay({error,_Reason}) ->
-    i("delay -> called with invalid time"),
-    delay_reply("delay failed: invalid delay time").
+delay(SessionID,_, _) ->
+    sleep(10000),
+    Reply = delay_reply("delay ok"),
+    mod_esi:deliver(SessionID, Reply).
 
 delay_reply(Reply) ->
     [header(),
      top("delay"),
      Reply,
      footer()].
-
-i(F)   -> i(F,[]).
-i(F,A) -> io:format(F ++ "~n",A).
-
-sleep(T) -> receive after T -> ok end.
-
 %% ------------------------------------------------------
 
 chunk_timeout(SessionID, _, _StrInt) ->
@@ -224,3 +230,34 @@ get_chunks(Sid, _Env, In) ->
     mod_esi:deliver(Sid, io_lib:format("Chunk ~p ms\r\n", [ChunkDelay])),
     timer:sleep(ChunkDelay + BadChunkDelay),
     mod_esi:deliver(Sid, "BAD Chunk\r\n").
+
+%% ------------------------------------------------------
+default(Env,Input) ->
+  [header(),
+   top("Default Example"),
+   "<B>Environment:</B> ",io_lib:format("~p",[Env]),"<BR>\n",
+   "<B>Input:</B> ",Input,"<BR>\n",
+   "<B>Parsed Input:</B> ",
+   io_lib:format("~p",[uri_string:dissect_query(Input)]),"\n",
+   footer()].
+
+header() ->
+  header("text/html").
+header(MimeType) ->
+  "Content-type: " ++ MimeType ++ "\r\n\r\n".
+header(MimeType, Other) ->
+  "Content-type: " ++ MimeType ++ "\r\n" ++ Other ++ "\r\n\r\n".			 
+
+top(Title) ->
+  "<HTML>
+<HEAD>
+<TITLE>" ++ Title ++ "</TITLE>
+</HEAD>
+<BODY>\n".
+
+footer() ->
+  "</BODY>
+</HTML>\n".
+
+sleep(T) -> receive after T -> ok end.
+
diff --git a/lib/inets/src/http_server/httpd_request.erl b/lib/inets/src/http_server/httpd_request.erl
index 3df55c0f7a..958b122255 100644
--- a/lib/inets/src/http_server/httpd_request.erl
+++ b/lib/inets/src/http_server/httpd_request.erl
@@ -340,31 +340,13 @@ whole_body(Body, Length) ->
 %% Prevent people from trying to access directories/files
 %% relative to the ServerRoot.
 validate_uri(RequestURI) ->
-    UriNoQueryNoHex = 
-	case string:str(RequestURI, "?") of
-	    0 ->
-		(catch http_uri:decode(RequestURI));
-	    Ndx ->
-		(catch http_uri:decode(string:left(RequestURI, Ndx)))
-	end,
-    case UriNoQueryNoHex of
-	{'EXIT', _Reason} ->
-	    {error, {bad_request, {malformed_syntax, RequestURI}}};
-	_ ->
-	    Path  = format_request_uri(UriNoQueryNoHex),
-	    Path2 = [X||X<-string:tokens(Path, "/"),X=/="."], %% OTP-5938
-	    validate_path(Path2, 0, RequestURI)
+    case uri_string:normalize(RequestURI) of
+        {error, _, _} ->
+            {error, {bad_request, {malformed_syntax, RequestURI}}};
+        URI ->
+            {ok, URI}
     end.
-
-validate_path([], _, _) ->
-    ok;
-validate_path([".." | _], 0, RequestURI) ->
-    {error, {bad_request, {forbidden, RequestURI}}};
-validate_path([".." | Rest], N, RequestURI) ->
-    validate_path(Rest, N - 1, RequestURI);
-validate_path([_ | Rest], N, RequestURI) ->
-    validate_path(Rest, N + 1, RequestURI).
-
+   
 validate_version("HTTP/1.1") ->
     true;
 validate_version("HTTP/1.0") ->
diff --git a/lib/inets/src/http_server/httpd_request_handler.erl b/lib/inets/src/http_server/httpd_request_handler.erl
index e48555f4d7..e82b1c46e9 100644
--- a/lib/inets/src/http_server/httpd_request_handler.erl
+++ b/lib/inets/src/http_server/httpd_request_handler.erl
@@ -400,9 +400,9 @@ handle_http_msg({_, _, Version, {_, _}, _},
 handle_http_msg({Method, Uri, Version, {RecordHeaders, Headers}, Body},
 		#state{status = accept, mod = ModData} = State) ->        
     case httpd_request:validate(Method, Uri, Version) of
-	ok  ->
+	{ok, NormalizedURI}  ->
 	    {ok, NewModData} = 
-		httpd_request:update_mod_data(ModData, Method, Uri,
+		httpd_request:update_mod_data(ModData, Method, NormalizedURI,
 					      Version, Headers),
       
 	    case is_host_specified_if_required(NewModData#mod.absolute_uri,
@@ -421,10 +421,6 @@ handle_http_msg({Method, Uri, Version, {RecordHeaders, Headers}, Body},
 	    httpd_response:send_status(ModData#mod{http_version = Version},
 				       501, {Method, Uri, Version}, {not_sup, What}),
 	    {stop, normal, State#state{response_sent = true}};
-	{error, {bad_request, {forbidden, URI}}} ->
-	    httpd_response:send_status(ModData#mod{http_version = Version},
-				       403, URI),
-	    {stop, normal, State#state{response_sent = true}};
 	{error, {bad_request, {malformed_syntax, URI}}} ->
 	    httpd_response:send_status(ModData#mod{http_version = Version},
 				       400, URI, {malformed_syntax, URI}),
diff --git a/lib/inets/src/http_server/httpd_util.erl b/lib/inets/src/http_server/httpd_util.erl
index 6b3b2c9660..05cff30243 100644
--- a/lib/inets/src/http_server/httpd_util.erl
+++ b/lib/inets/src/http_server/httpd_util.erl
@@ -167,7 +167,7 @@ reason_phrase(_) -> "Internal Server Error".
 %% message
 
 message(301,URL,_) ->
-    "The document has moved <A HREF=\""++ maybe_encode(URL) ++"\">here</A>.";
+    "The document has moved <A HREF=\""++ html_encode(uri_string:normalize(URL)) ++"\">here</A>.";
 message(304, _URL,_) ->
     "The document has not been changed.";
 message(400, none, _) ->
@@ -184,11 +184,11 @@ browser doesn't understand how to supply
 the credentials required.";
 message(403,RequestURI,_) ->
     "You don't have permission to access " ++ 
-	html_encode(RequestURI) ++ 
+	html_encode(uri_string:normalize(RequestURI)) ++ 
 	" on this server.";
 message(404,RequestURI,_) ->
     "The requested URL " ++ 
-	html_encode(RequestURI) ++ 
+	html_encode(uri_string:normalize(RequestURI)) ++ 
 	" was not found on this server.";
 message(408, Timeout, _) ->
     Timeout;
@@ -212,7 +212,7 @@ message(501,{Method, RequestURI, HTTPVersion}, _ConfigDB) ->
 	is_atom(Method) ->
 	    atom_to_list(Method) ++
 		" to " ++ 
-		html_encode(RequestURI) ++ 
+		html_encode(uri_string:normalize(RequestURI)) ++ 
 		" (" ++ HTTPVersion ++ ") not supported.";
 	is_list(Method) ->
 	    Method ++
@@ -225,23 +225,9 @@ message(503, String, _ConfigDB) ->
     "This service in unavailable due to: " ++ html_encode(String);
 message(_, ReasonPhrase, _) ->
     html_encode(ReasonPhrase).
-
-maybe_encode(URI) ->
-    Decoded = try http_uri:decode(URI) of
-	N -> N
-    catch
-	error:_ -> URI
-    end,
-    http_uri:encode(Decoded).
-
+                
 html_encode(String) ->
-    try http_uri:decode(String) of
-	Decoded when is_list(Decoded) ->
-	    http_util:html_encode(Decoded)
-    catch 
-	_:_ ->
-	    http_util:html_encode(String)
-    end.
+    http_util:html_encode(String).
 
 %%convert_rfc_date(Date)->{{YYYY,MM,DD},{HH,MIN,SEC}}
 
@@ -422,21 +408,26 @@ flatlength([],L) ->
 
 %% split_path
 
-split_path(Path) ->
-    case re:run(Path,"[\?].*\$", [{capture, first}]) of
-	%% A QUERY_STRING exists!
-	{match,[{Start,Length}]} ->
-	    {http_uri:decode(string:substr(Path,1,Start)),
-	     string:substr(Path,Start+1,Length)};
-	%% A possible PATH_INFO exists!
-	nomatch ->
-	    split_path(Path,[])
+split_path(URI) -> 
+    case uri_string:normalize(URI, [return_map]) of
+       #{fragment := Fragment,
+         path := Path,
+         query := Query} ->
+            {Path, add_hashmark(Query, Fragment)};
+        #{path := Path,
+          query := Query} ->
+            {Path, Query};
+        #{path := Path} ->            
+            split_path(Path, [])
     end.
 
+add_hashmark(Query, Fragment) ->
+    Query ++ "#" ++ Fragment.
+   
 split_path([],SoFar) ->
-    {http_uri:decode(lists:reverse(SoFar)),[]};
+    {lists:reverse(SoFar),[]};
 split_path([$/|Rest],SoFar) ->
-    Path=http_uri:decode(lists:reverse(SoFar)),
+    Path=lists:reverse(SoFar),
     case file:read_file_info(Path) of
 	{ok,FileInfo} when FileInfo#file_info.type =:= regular ->
 	    {Path,[$/|Rest]};
@@ -450,56 +441,20 @@ split_path([C|Rest],SoFar) ->
 
 %% split_script_path
 
-split_script_path(Path) ->
-    case split_script_path(Path, []) of
-	{Script, AfterPath} ->
-	    {PathInfo, QueryString} = pathinfo_querystring(AfterPath),
-	    {Script, {PathInfo, QueryString}};
-	not_a_script ->
-	    not_a_script
-    end.
 
-pathinfo_querystring(Str) ->
-    pathinfo_querystring(Str, []).
-pathinfo_querystring([], SoFar) ->
-    {lists:reverse(SoFar), []};
-pathinfo_querystring([$?|Rest], SoFar) ->
-    {lists:reverse(SoFar), Rest};
-pathinfo_querystring([C|Rest], SoFar) ->
-    pathinfo_querystring(Rest, [C|SoFar]).
-
-split_script_path([$?|QueryString], SoFar) ->
-    Path = http_uri:decode(lists:reverse(SoFar)),
-    case file:read_file_info(Path) of
-	{ok,FileInfo} when FileInfo#file_info.type =:= regular ->
-	    {Path, [$?|QueryString]};
-	{ok, _FileInfo} ->
-	    not_a_script;
-	{error, _Reason} ->
-	    not_a_script
-    end;
-split_script_path([], SoFar) ->
-    Path = http_uri:decode(lists:reverse(SoFar)),
-    case file:read_file_info(Path) of
-	{ok,FileInfo} when FileInfo#file_info.type =:= regular ->
-	    {Path, []};
-	{ok, _FileInfo} ->
-	    not_a_script;
-	{error, _Reason} ->
-	    not_a_script
-    end;
-split_script_path([$/|Rest], SoFar) ->
-    Path = http_uri:decode(lists:reverse(SoFar)),
-    case file:read_file_info(Path) of
-	{ok, FileInfo} when FileInfo#file_info.type =:= regular ->
-	    {Path, [$/|Rest]};
-	{ok, _FileInfo} ->
-	    split_script_path(Rest, [$/|SoFar]);
-	{error, _Reason} ->
-	    split_script_path(Rest, [$/|SoFar])
-    end;
-split_script_path([C|Rest], SoFar) ->
-    split_script_path(Rest,[C|SoFar]).
+split_script_path(URI) -> 
+    case uri_string:normalize(URI, [return_map]) of
+       #{fragment := _Fragment,
+         path := _Path,
+         query := _Query} ->
+            not_a_script;
+        #{path := Path,
+          query := Query} ->
+            {Script, PathInfo} = split_path(Path, []),
+            {Script, {PathInfo, Query}};
+        #{path := Path} ->            
+            split_path(Path, [])
+    end.
 
 %% suffix
 
diff --git a/lib/inets/src/http_server/mod_dir.erl b/lib/inets/src/http_server/mod_dir.erl
index 2a90575e7d..ad2ee1d994 100644
--- a/lib/inets/src/http_server/mod_dir.erl
+++ b/lib/inets/src/http_server/mod_dir.erl
@@ -57,9 +57,7 @@ do_dir(Info) ->
     %% Is it a directory?
     case file:read_file_info(DefaultPath) of
 	{ok,FileInfo} when FileInfo#file_info.type == directory ->
-	    DecodedRequestURI =
-		http_uri:decode(Info#mod.request_uri),
-	    case dir(DefaultPath,string:strip(DecodedRequestURI,right,$/),
+	    case dir(DefaultPath,string:strip( Info#mod.request_uri,right,$/),
 		     Info#mod.config_db) of
 		{ok, Dir} ->
 		    LastModified =
diff --git a/lib/inets/src/http_server/mod_esi.erl b/lib/inets/src/http_server/mod_esi.erl
index 112e74575d..c1331e1df0 100644
--- a/lib/inets/src/http_server/mod_esi.erl
+++ b/lib/inets/src/http_server/mod_esi.erl
@@ -161,16 +161,6 @@ store({erl_script_alias, {Name, Modules}} = Conf, _)
    	    {error, {wrong_type, {erl_script_alias, Error}}}
     end;
 
-store({eval_script_alias, {Name, Modules}} = Conf, _)  
-  when is_list(Name)->
-    try httpd_util:modules_validate(Modules) of
-  	ok ->
-   	    {ok, Conf}
-    catch
-   	throw:Error ->
-   	    {error, {wrong_type, {eval_script_alias, Error}}}
-    end;
-
 store({erl_script_alias, Value}, _) ->
     {error, {wrong_type, {erl_script_alias, Value}}};
 store({erl_script_timeout, TimeoutSec}, _) 
@@ -190,8 +180,6 @@ store({erl_script_nocache, Value}, _) ->
 %%%========================================================================   
 generate_response(ModData) ->
     case scheme(ModData#mod.request_uri, ModData#mod.config_db) of
-	{eval, ESIBody, Modules} ->
-	    eval(ModData, ESIBody, Modules);
 	{erl, ESIBody, Modules} ->
 	    erl(ModData, ESIBody, Modules);
 	no_scheme ->
@@ -201,12 +189,7 @@ generate_response(ModData) ->
 scheme(RequestURI, ConfigDB) ->
     case match_script(RequestURI, ConfigDB, erl_script_alias) of
 	no_match ->
-	    case match_script(RequestURI, ConfigDB, eval_script_alias) of
-		no_match ->
-		    no_scheme;
-		{EsiBody, ScriptModules} ->
-		    {eval, EsiBody, ScriptModules}
-	    end;
+            no_scheme;
 	{EsiBody, ScriptModules} ->
 	    {erl, EsiBody, ScriptModules}
     end.
@@ -231,10 +214,7 @@ match_esi_script(RequestURI, [{Alias,Modules} | Rest], AliasType) ->
     end.
 
 alias_match_str(Alias, erl_script_alias) ->
-    "^" ++ Alias ++ "/";
-alias_match_str(Alias, eval_script_alias) ->
-    "^" ++ Alias ++ "\\?".
-
+    "^" ++ Alias ++ "/".
 
 %%------------------------ Erl mechanism --------------------------------
 
@@ -315,8 +295,8 @@ generate_webpage(ModData, ESIBody, Modules, Module, FunctionName,
 	    case erl_scheme_webpage_chunk(Module, Function, 
 					  Env, Input, ModData) of
 		{error, erl_scheme_webpage_chunk_undefined} ->
-		    erl_scheme_webpage_whole(Module, Function, Env, Input,
-					     ModData);
+                    {proceed, [{status, {404, ModData#mod.request_uri, "Not found"}}
+                               | ModData#mod.data]};
 		ResponseResult ->
 		    ResponseResult
 	    end;
@@ -326,38 +306,7 @@ generate_webpage(ModData, ESIBody, Modules, Module, FunctionName,
                       | ModData#mod.data]}
     end.
 
-%% Old API that waits for the dymnamic webpage to be totally generated
-%% before anythig is sent back to the client.
-erl_scheme_webpage_whole(Mod, Func, Env, Input, ModData) ->
-    case (catch Mod:Func(Env, Input)) of
-	{'EXIT',{undef, _}} ->
-	    {proceed, [{status, {404, ModData#mod.request_uri, "Not found"}}
-		       | ModData#mod.data]};
-	{'EXIT',Reason} ->
-	    {proceed, [{status, {500, none, Reason}} |
-		       ModData#mod.data]};
-	Response ->
-	    {Headers, Body} = 
-		httpd_esi:parse_headers(lists:flatten(Response)),
-	    Length =  httpd_util:flatlength(Body),
-            {ok, NewHeaders, StatusCode} = httpd_esi:handle_headers(Headers), 
-            send_headers(ModData, StatusCode, 
-                         [{"content-length", 
-                           integer_to_list(Length)}| NewHeaders]),
-            case ModData#mod.method of
-                "HEAD" ->
-                    {proceed, [{response, {already_sent, StatusCode, 0}} | 
-                               ModData#mod.data]};
-                _ ->
-                    httpd_response:send_body(ModData, 
-                                             StatusCode, Body),
-                    {proceed, [{response, {already_sent, StatusCode, 
-                                           Length}} | 
-                               ModData#mod.data]}
-            end
-    end.
-
-%% New API that allows the dynamic wepage to be sent back to the client 
+%% API that allows the dynamic wepage to be sent back to the client 
 %% in small chunks at the time during generation.
 erl_scheme_webpage_chunk(Mod, Func, Env, Input, ModData) -> 
     process_flag(trap_exit, true),
@@ -369,7 +318,6 @@ erl_scheme_webpage_chunk(Mod, Func, Env, Input, ModData) ->
 	    fun() ->
 		    case catch Mod:Func(Self, Env, Input) of
 			{'EXIT', {undef,_}} ->
-			    %% Will force fallback on the old API
 			    exit(erl_scheme_webpage_chunk_undefined);
 			{continue, _} = Continue ->
                             exit(Continue);
@@ -523,64 +471,3 @@ input_type([$?|_Rest]) ->
 input_type([_First|Rest]) ->
     input_type(Rest).
 
-%%------------------------ Eval mechanism --------------------------------
-
-eval(#mod{request_uri  = ReqUri, 
-	  method       = "PUT",
-	  http_version = Version, 
-	  data         = Data}, _ESIBody, _Modules) ->
-    {proceed,[{status,{501,{"PUT", ReqUri, Version},
-		       ?NICE("Eval mechanism doesn't support method PUT")}}|
-	      Data]};
-
-eval(#mod{request_uri  = ReqUri, 
-	  method       = "DELETE",
-	  http_version = Version, 
-	  data         = Data}, _ESIBody, _Modules) ->
-    {proceed,[{status,{501,{"DELETE", ReqUri, Version},
-		       ?NICE("Eval mechanism doesn't support method DELETE")}}|
-	      Data]};
-
-eval(#mod{request_uri  = ReqUri, 
-	  method       = "POST",
-	  http_version = Version, 
-	  data         = Data}, _ESIBody, _Modules) ->
-    {proceed,[{status,{501,{"POST", ReqUri, Version},
-		       ?NICE("Eval mechanism doesn't support method POST")}}|
-	      Data]};
-
-eval(#mod{method = Method} = ModData, ESIBody, Modules) 
-  when (Method =:= "GET") orelse (Method =:= "HEAD") ->
-    case is_authorized(ESIBody, Modules) of
-	true ->
-	    case generate_webpage(ESIBody) of
-		{error, Reason} ->
-		    {proceed, [{status, {500, none, Reason}} | 
-			       ModData#mod.data]};
-		{ok, Response} ->
-		    {Headers, _} = 
-			httpd_esi:parse_headers(lists:flatten(Response)),
-                    {ok, _, StatusCode} =httpd_esi:handle_headers(Headers), 
-                    {proceed,[{response, {StatusCode, Response}} | 
-                              ModData#mod.data]}
-            end;
-	false ->
-	    {proceed,[{status,
-		       {403, ModData#mod.request_uri,
-			?NICE("Client not authorized to evaluate: "
-			      ++ ESIBody)}} | ModData#mod.data]}
-    end.
-
-generate_webpage(ESIBody) ->
-    (catch erl_eval:eval_str(string:concat(ESIBody,". "))).
-
-is_authorized(_ESIBody, [all]) ->
-    true;
-is_authorized(ESIBody, Modules) ->
-    case re:run(ESIBody, "^[^\:(%3A)]*", [{capture, first}]) of
-	{match, [{Start, Length}]} ->
-	    lists:member(list_to_atom(string:substr(ESIBody, Start+1, Length)),
-			 Modules);
-	nomatch ->
-	    false
-    end.
diff --git a/lib/inets/src/inets_app/inets.app.src b/lib/inets/src/inets_app/inets.app.src
index 41b2ab950f..ac5a2dd2d5 100644
--- a/lib/inets/src/inets_app/inets.app.src
+++ b/lib/inets/src/inets_app/inets.app.src
@@ -43,14 +43,14 @@
             httpc_sup,
             httpc_cookie,                
 
-	    http_uri, %% Proably will by used by server also in the future
-
             %% HTTP used by both client and server 
             http_chunk,
             http_request,
             http_response,      
             http_transport,
             http_util,  
+
+            http_uri, %% Deprecated
             
             %% HTTP server:
             httpd,
diff --git a/lib/inets/test/http_format_SUITE.erl b/lib/inets/test/http_format_SUITE.erl
index 3ff3ed4e97..6492325701 100644
--- a/lib/inets/test/http_format_SUITE.erl
+++ b/lib/inets/test/http_format_SUITE.erl
@@ -454,7 +454,7 @@ validate_request_line() ->
 validate_request_line(Config) when is_list(Config) ->
 
     %% HTTP/0.9 only has GET requests
-    ok = 
+    {ok, "http://www.erlang/org"} = 
 	httpd_request:validate("GET", "http://www.erlang/org", "HTTP/0.9"),
     {error, {not_supported, 
 	     {"HEAD", "http://www.erlang/org", "HTTP/0.9"}}} =
@@ -467,43 +467,37 @@ validate_request_line(Config) when is_list(Config) ->
 	httpd_request:validate("POST", "http://www.erlang/org", "HTTP/0.9"),
 
     %% HTTP/1.* 
-    ok = httpd_request:validate("HEAD", "http://www.erlang/org", 
+    {ok, "http://www.erlang/org"} = httpd_request:validate("HEAD", "http://www.erlang/org", 
 			       "HTTP/1.1"),
-    ok = httpd_request:validate("GET", "http://www.erlang/org", 
+    {ok, "http://www.erlang/org"} = httpd_request:validate("GET", "http://www.erlang/org", 
 			       "HTTP/1.1"),  
-    ok = httpd_request:validate("POST","http://www.erlang/org", 
-			       "HTTP/1.1"),
-    ok = httpd_request:validate("TRACE","http://www.erlang/org",
+    {ok, "http://www.erlang/org"} = httpd_request:validate("POST","http://www.erlang/org", 
 			       "HTTP/1.1"),
+    {ok, "http://www.erlang/org"} = httpd_request:validate("TRACE","http://www.erlang/org",
+                                                           "HTTP/1.1"),
     {error, {not_supported, 
 	     {"FOOBAR", "http://www.erlang/org", "HTTP/1.1"}}} =
 	httpd_request:validate("FOOBAR", "http://www.erlang/org", 
 			       "HTTP/1.1"),
+    %%% Will work after normalization
+    Uri = "http://127.0.0.1:8888/../../../../../etc/passwd",
+    {ok, "http://127.0.0.1:8888/etc/passwd"} = httpd_request:validate("GET", Uri, "HTTP/1.1"),
 
-    %% Attempts to get outside of server_root directory by relative links 
-    ForbiddenUri = "http://127.0.0.1:8888/../../../../../etc/passwd",
-    {error, {bad_request, {forbidden, ForbiddenUri}}} = 
-	httpd_request:validate("GET", ForbiddenUri, "HTTP/1.1"),
-
-    ForbiddenUri2 = 
+    Uri2 = 
 	"http://127.0.0.1:8888/././././././../../../../../etc/passwd",
-    {error, {bad_request, {forbidden, ForbiddenUri2}}} = 
-	httpd_request:validate("GET", ForbiddenUri2, "HTTP/1.1"),
-
-    HexForbiddenUri = "http://127.0.0.1:8888/%2e%2e/%2e%2e/%2e%2e/" 
-	"home/ingela/test.html",
-    {error, {bad_request, {forbidden, HexForbiddenUri}}} = 
-	httpd_request:validate("GET", HexForbiddenUri, "HTTP/1.1"),
-
-    NewForbiddenUri = 
-	"http://127.0.0.1:8888/foobar/../../../home/ingela/test.html",
-    {error, {bad_request, {forbidden, NewForbiddenUri}}} = 
-	httpd_request:validate("GET", NewForbiddenUri, "HTTP/1.1"),
-
-    NewForbiddenUri1 = 
-	"http://127.0.0.1:8888/../home/ingela/test.html",
-    {error, {bad_request, {forbidden, NewForbiddenUri1}}} = 
-	httpd_request:validate("GET", NewForbiddenUri1, "HTTP/1.1").
+    {ok, "http://127.0.0.1:8888/etc/passwd"} = httpd_request:validate("GET", Uri2, "HTTP/1.1"),
+
+    HexUri = "http://127.0.0.1:8888/%2e%2e/%2e%2e/%2e%2e/" 
+	"home/foobar/test.html",
+    {ok, "http://127.0.0.1:8888/home/foobar/test.html"}  = httpd_request:validate("GET", HexUri, "HTTP/1.1"),
+
+    NewUri = 
+	"http://127.0.0.1:8888/foobar/../../../home/foobar/test.html",
+    {ok,"http://127.0.0.1:8888/home/foobar/test.html"} = httpd_request:validate("GET", NewUri, "HTTP/1.1"),
+    
+    Uri1 = 
+	"http://127.0.0.1:8888/../home/foobar/test.html",
+    {ok,"http://127.0.0.1:8888/home/foobar/test.html"}  = httpd_request:validate("GET", Uri1, "HTTP/1.1").
 
 %%-------------------------------------------------------------------------
 check_content_length_encoding() ->
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 1289432f0d..0634f6b63d 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -116,16 +116,16 @@ groups() ->
      {https_not_sup, [], [{group, not_sup}]},
      {https_alert, [], [tls_alert]},
      {http_mime_types, [], [alias_1_1, alias_1_0, alias_0_9]},
-     {limit, [],  [max_clients_1_1, max_clients_1_0, max_clients_0_9]},  
+     {limit, [],  [content_length, max_clients_1_1]},  
      {custom, [],  [customize, add_default]},  
      {reload, [], [non_disturbing_reconfiger_dies,
 		   disturbing_reconfiger_dies,
 		   non_disturbing_1_1, 
 		   non_disturbing_1_0, 
 		   non_disturbing_0_9,
-		   disturbing_1_1,
-		   disturbing_1_0, 
-		   disturbing_0_9,
+                   disturbing_1_1,
+                   disturbing_1_0, 
+                   disturbing_0_9,
 		   reload_config_file
 		  ]},
      {post, [], [chunked_post, chunked_chunked_encoded_post, post_204]},
@@ -163,7 +163,6 @@ http_get() ->
      get, 
      %%actions, Add configuration so that this test mod_action
      esi, 
-     content_length, 
      bad_hex, 
      missing_CR,
      max_header,
@@ -231,7 +230,7 @@ init_per_group(Group, Config0) when Group == https_basic;
     catch crypto:stop(),
     try crypto:start() of
         ok ->
-            init_ssl(Group, Config0)
+            init_ssl(Group,  [{http_version, "HTTP/1.0"} | Config0])
     catch
         _:_ ->
             {skip, "Crypto did not start"}
@@ -250,7 +249,7 @@ init_per_group(Group, Config0)  when  Group == http_basic;
                                       Group == http_mime_types
 				      ->
     ok = start_apps(Group),
-    init_httpd(Group, [{type, ip_comm} | Config0]);
+    init_httpd(Group, [{http_version, "HTTP/1.0"}, {type, ip_comm} | Config0]);
 init_per_group(http_1_1, Config) ->
     [{http_version, "HTTP/1.1"} | Config];
 init_per_group(http_1_0, Config) ->
@@ -960,19 +959,6 @@ max_clients_1_1() ->
 max_clients_1_1(Config) when is_list(Config) -> 
     do_max_clients([{http_version, "HTTP/1.1"} | Config]).
 
-max_clients_1_0() ->
-    [{doc, "Test max clients limit"}].
-
-max_clients_1_0(Config) when is_list(Config) -> 
-    do_max_clients([{http_version, "HTTP/1.0"} | Config]).
-
-max_clients_0_9() ->
-    [{doc, "Test max clients limit"}].
-
-max_clients_0_9(Config) when is_list(Config) -> 
-    do_max_clients([{http_version, "HTTP/0.9"} | Config]).
-
-
 %%-------------------------------------------------------------------------
 put_not_sup() ->
     [{doc, "Test unhandled request"}].
@@ -1003,12 +989,6 @@ esi() ->
     [{doc, "Test mod_esi"}].
 
 esi(Config) when is_list(Config) -> 
-    ok = http_status("GET /eval?httpd_example:print(\"Hi!\") ",
-		     Config, [{statuscode, 200}]),
-    ok = http_status("GET /eval?not_allowed:print(\"Hi!\") ",
-		     Config, [{statuscode, 403}]),
-    ok = http_status("GET /eval?httpd_example:undef(\"Hi!\") ",
-		      Config, [{statuscode, 500}]),
     ok = http_status("GET /cgi-bin/erl/httpd_example ", 
 		     Config, [{statuscode, 400}]),
     ok = http_status("GET /cgi-bin/erl/httpd_example:get ",
@@ -1590,20 +1570,20 @@ do_reconfiger_dies(Config, DisturbingType) ->
     Type = proplists:get_value(type, Config),
 
     HttpdConfig = httpd:info(Server), 
-    BlockRequest = http_request("GET /eval?httpd_example:delay(2000) ", Version, Host),
+    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version, Host),
     {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
     inets_test_lib:send(Type, Socket, BlockRequest),
     ct:sleep(100), %% Avoid possible timing issues
     Pid = spawn(fun() -> httpd:reload_config([{server_name, "httpd_kill_" ++ Version}, 
-					      {port, Port}|
-					      proplists:delete(server_name, HttpdConfig)], DisturbingType) 
-	  end),
+                                              {port, Port}|
+                                              proplists:delete(server_name, HttpdConfig)], DisturbingType) 
+                end),
     
     monitor(process, Pid),
     exit(Pid, kill),
     receive 
-	{'DOWN', _, _, _, _} ->
-	    ok
+        {'DOWN', _, _, _, _} ->
+            ok
     end,
     inets_test_lib:close(Type, Socket),
     [{server_name, "httpd_test"}] =  httpd:info(Server, [server_name]).
@@ -1624,7 +1604,8 @@ disturbing(Config) when is_list(Config)->
     Port = proplists:get_value(port, Config),
     Type = proplists:get_value(type, Config),
     HttpdConfig = httpd:info(Server), 
-    BlockRequest = http_request("GET /eval?httpd_example:delay(2000) ", Version,  Host),
+
+    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version,  Host),
     {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
     inets_test_lib:send(Type, Socket, BlockRequest),
     ct:sleep(100), %% Avoid possible timing issues
@@ -1657,7 +1638,7 @@ non_disturbing(Config) when is_list(Config)->
     Type = proplists:get_value(type, Config),
 
     HttpdConfig = httpd:info(Server), 
-    BlockRequest = http_request("GET /eval?httpd_example:delay(2000) ", Version, Host),
+    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version, Host),
     {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
     inets_test_lib:send(Type, Socket, BlockRequest),
     ct:sleep(100), %% Avoid possible timing issues
@@ -1999,10 +1980,9 @@ do_max_clients(Config) ->
     Type    = proplists:get_value(type, Config),
     
     Request = http_request("GET /index.html ", Version, Host),
-    BlockRequest = http_request("GET /eval?httpd_example:delay(2000) ", Version, Host),
+    BlockRequest = http_request("GET /cgi_bin/erl/httpd_example:delay ", Version, Host),
     {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
     inets_test_lib:send(Type, Socket, BlockRequest),
-    ct:sleep(100), %% Avoid possible timing issues
     ok = httpd_test_lib:verify_request(Type, Host, 
 				       Port,
 				       transport_opts(Type, Config),
@@ -2151,6 +2131,7 @@ server_config(https_reload, Config) ->
     [{keep_alive_timeout, 2}]  ++ server_config(https, Config);
 server_config(http_limit, Config) ->
     Conf = [{max_clients, 1},
+            {disable_chunked_transfer_encoding_send, true},
 	    %% Make sure option checking code is run
 	    {max_content_length, 100000002}]  ++ server_config(http, Config),
     ct:pal("Received message ~p~n", [Conf]),
@@ -2160,7 +2141,9 @@ server_config(http_custom, Config) ->
 server_config(https_custom, Config) ->
     [{customize, ?MODULE}]  ++ server_config(https, Config);
 server_config(https_limit, Config) ->
-    [{max_clients, 1}]  ++ server_config(https, Config);
+    [{max_clients, 1},
+     {disable_chunked_transfer_encoding_send, true}
+    ]  ++ server_config(https, Config);
 server_config(http_basic_auth, Config) ->
     ServerRoot = proplists:get_value(server_root, Config),
     auth_conf(ServerRoot)  ++  server_config(http, Config);
@@ -2222,8 +2205,7 @@ server_config(http, Config) ->
      {alias, {"/pics/",  filename:join(ServerRoot,"icons") ++ "/"}},
      {script_alias, {"/cgi-bin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}},
      {script_alias, {"/htbin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}},
-     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}},
-     {eval_script_alias, {"/eval", [httpd_example, io]}}
+     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}}
     ];
 server_config(http_rel_path_script_alias, Config) ->
     ServerRoot = proplists:get_value(server_root, Config),
@@ -2243,8 +2225,7 @@ server_config(http_rel_path_script_alias, Config) ->
      {alias, {"/pics/",  filename:join(ServerRoot,"icons") ++ "/"}},
      {script_alias, {"/cgi-bin/", "./cgi-bin/"}},
      {script_alias, {"/htbin/", "./cgi-bin/"}},
-     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}},
-     {eval_script_alias, {"/eval", [httpd_example, io]}}
+     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}}
     ];
 server_config(https, Config) ->
     SSLConf = proplists:get_value(ssl_conf, Config),
diff --git a/lib/inets/test/httpd_basic_SUITE.erl b/lib/inets/test/httpd_basic_SUITE.erl
index 94d22ea76c..1d3be6de57 100644
--- a/lib/inets/test/httpd_basic_SUITE.erl
+++ b/lib/inets/test/httpd_basic_SUITE.erl
@@ -302,11 +302,13 @@ escaped_url_in_error_body(Config) when is_list(Config) ->
     
     %% Ask for a non-existing page(1)
     Path            = "/<b>this_is_bold<b>",
-    HTMLEncodedPath = http_util:html_encode(Path),
     URL2 = uri_string:recompose(#{scheme => "http",
                                   host => "localhost",
                                   port => Port,
                                   path => Path}),
+    
+    #{path := EncodedPath} = uri_string:parse(URL2),
+    HTMLEncodedPath =  http_util:html_encode(EncodedPath),
     {ok, {404, Body3}} = httpc:request(get, {URL2, []},
 				       [{url_encode,  true}, 
 					{version,     "HTTP/1.0"}],
diff --git a/lib/inets/test/httpd_test_lib.erl b/lib/inets/test/httpd_test_lib.erl
index b6525037b2..c5efe98555 100644
--- a/lib/inets/test/httpd_test_lib.erl
+++ b/lib/inets/test/httpd_test_lib.erl
@@ -388,8 +388,8 @@ is_expect(RequestStr) ->
     end.
 
 %% OTP-5775, content-length
-check_body("GET /cgi-bin/erl/httpd_example:get_bin HTTP/1.0\r\n\r\n", 200, "text/html", Length, _Body) when (Length =/= 274) ->
-    ct:fail(content_length_error);
+check_body("GET /cgi-bin/erl/httpd_example:get_bin HTTP/1.1\r\n\r\n", 200, "text/html", Length, _Body) when (Length =/= 274) ->
+    ct:fail({content_length_error, Length});
 check_body("GET /cgi-bin/cgi_echo HTTP/1.0\r\n\r\n", 200, "text/plain", 
 	   _, Body) ->
     case size(Body) of
-- 
2.16.4

openSUSE Build Service is sponsored by