File 0633-inets-Add-tests-for-erl_script_timeout.patch of Package erlang

From e160c628f4305dd603c24ab6d208db57ce15b23b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?P=C3=A9ter=20Dimitrov?= <peterdmv@users.noreply.github.com>
Date: Sun, 14 Apr 2019 16:35:51 +0200
Subject: [PATCH 2/2] inets: Add tests for erl_script_timeout

---
 lib/inets/src/http_server/httpd_example.erl |  21 +++-
 lib/inets/test/httpd_SUITE.erl              | 165 ++++++++++++++++++++++++++--
 2 files changed, 178 insertions(+), 8 deletions(-)

diff --git a/lib/inets/src/http_server/httpd_example.erl b/lib/inets/src/http_server/httpd_example.erl
index 37e4f97bc0..aaa7e428c2 100644
--- a/lib/inets/src/http_server/httpd_example.erl
+++ b/lib/inets/src/http_server/httpd_example.erl
@@ -24,7 +24,7 @@
 
 -export([newformat/3]).
 %% These are used by the inets test-suite
--export([delay/1, chunk_timeout/3]).
+-export([delay/1, chunk_timeout/3, get_chunks/3]).
 
 
 print(String) ->
@@ -171,3 +171,22 @@ chunk_timeout(SessionID, _, _StrInt) ->
     mod_esi:deliver(SessionID, top("Test chunk encoding timeout")),
     timer:sleep(20000),
     mod_esi:deliver(SessionID, footer()).
+
+get_chunks(Sid, _Env, In) ->
+    Tokens = string:tokens(In, [$&]),
+    PropList = lists:map(fun(E) ->
+                                 list_to_tuple(string:tokens(E,[$=])) end,
+                         Tokens),
+    HeaderDelay =
+        list_to_integer(proplists:get_value("header_delay", PropList, "0")),
+    ChunkDelay =
+        list_to_integer(proplists:get_value("chunk_delay", PropList, "0")),
+    BadChunkDelay =
+        list_to_integer(proplists:get_value("bad_chunk_delay", PropList, "0")),
+    timer:sleep(HeaderDelay),
+    mod_esi:deliver(Sid, ["Content-Type: text/plain\r\n\r\n"]),
+    mod_esi:deliver(Sid, "Chunk 0 ms\r\n"),
+    timer:sleep(ChunkDelay),
+    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").
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index fcb9ad7905..fc5ca14dcd 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -79,7 +79,10 @@ all() ->
      {group, http_mime_types},
      {group, http_logging},
      mime_types_format,
-     erl_script_timeout_option
+     erl_script_timeout_default,
+     erl_script_timeout_option,
+     erl_script_timeout_proplist,
+     erl_script_timeout_apache
     ].
 
 groups() ->
@@ -384,6 +387,10 @@ init_per_testcase(disk_log_bad_file, Config0) ->
     ct:timetrap({seconds, 20}),
     dbg(disk_log_internal, Config1, init);
 
+init_per_testcase(erl_script_timeout_default, Config) ->
+    ct:timetrap({seconds, 60}),
+    dbg(erl_script_timeout_default, Config, init);
+
 init_per_testcase(Case, Config) ->
     ct:timetrap({seconds, 20}),
     dbg(Case, Config, init).
@@ -1777,16 +1784,128 @@ mime_types_format(Config) when is_list(Config) ->
      {"cpt","application/mac-compactpro"},
      {"hqx","application/mac-binhex40"}]} = httpd_conf:load_mime_types(MimeTypes).
 
+erl_script_timeout_default(Config) when is_list(Config) ->
+    inets:start(),
+    {ok, Pid} =	inets:start(httpd,
+                            [{port, 0},
+                             {server_name,"localhost"},
+                             {server_root,"./"},
+                             {document_root,"./"},
+                             {bind_address, any},
+                             {mimetypes, [{"html", "text/html"}]},
+                             {modules,[mod_esi]},
+                             {erl_script_alias, {"/erl", [httpd_example]}}
+                            ]),
+    Info = httpd:info(Pid),
+
+    Port = proplists:get_value(port, Info),
+
+    %% Default erl_script_timeout is 15.
+    %% Verify:  13 =< erl_script_timeout =< 17
+    Url = http_get_url(Port, 500, 13000, 4000),
+
+    {ok, {_, _, Body}} = httpc:request(get, {Url, []}, [{timeout, 45000}], []),
+    ct:log("Response: ~p~n", [Body]),
+    verify_body(Body, 13000),
+    inets:stop().
 
 erl_script_timeout_option(Config) when is_list(Config) ->
     inets:start(),
-    {ok, Pid} = inets:start(httpd, [{erl_script_timeout, 215},
-                                    {server_name, "test"},
-                                    {port,0},
-                                    {server_root, "."},
-                                    {document_root, "."}]),
+    {ok, Pid} =	inets:start(httpd,
+                            [{port, 0},
+                             {server_name,"localhost"},
+                             {server_root,"./"},
+                             {document_root,"./"},
+                             {bind_address, any},
+                             {mimetypes, [{"html", "text/html"}]},
+                             {modules,[mod_esi]},
+                             {erl_script_timeout, 2},
+                             {erl_script_alias, {"/erl", [httpd_example]}}
+                            ]),
     Info = httpd:info(Pid),
-    215 = proplists:get_value(erl_script_timeout, Info),
+    verify_timeout(Info, 2),
+
+    Port = proplists:get_value(port, Info),
+
+    %% Verify:  1 =< erl_script_timeout =< 3
+    Url = http_get_url(Port, 500, 1000, 2000),
+
+    {ok, {_, _, Body}} = httpc:request(Url),
+    ct:log("Response: ~p~n", [Body]),
+    verify_body(Body, 1000),
+    inets:stop().
+
+erl_script_timeout_proplist(Config) when is_list(Config) ->
+    HttpdConf = filename:join(get_tmp_dir(Config),
+                              "httpd_erl_script_timeout_proplist.conf"),
+    ServerConfig =
+        "[{port, 0},\n" ++
+        " {server_name,\"localhost\"},\n" ++
+        " {server_root,\"./\"},\n" ++
+        " {document_root,\"./\"},\n" ++
+        " {bind_address, any},\n" ++
+        " {mimetypes, [{\"html\", \"text/html\"}]},\n" ++
+        " {modules,[mod_esi]},\n" ++
+        " {erl_script_timeout, 5},\n" ++
+        " {erl_script_alias, {\"/erl\", [httpd_example]}}\n" ++
+        "].",
+    ok = file:write_file(HttpdConf, ServerConfig),
+
+    inets:start(),
+    {ok, Pid} =	inets:start(httpd,
+                            [{proplist_file, HttpdConf}]),
+    Info = httpd:info(Pid),
+    verify_timeout(Info, 5),
+
+    Port = proplists:get_value(port, Info),
+
+    %% Verify:  3 =< erl_script_timeout =< 7
+    Url = http_get_url(Port, 500, 3000, 4000),
+
+    {ok, {_, _, Body}} = httpc:request(Url),
+    ct:log("Response: ~p~n", [Body]),
+    verify_body(Body, 3000),
+    inets:stop().
+
+erl_script_timeout_apache(Config) when is_list(Config) ->
+    HttpdConf = filename:join(get_tmp_dir(Config),
+                              "httpd_erl_script_timeout.conf"),
+    MimeTypes = filename:join(get_tmp_dir(Config),
+                              "erl_script_timeout_mime_types.conf"),
+
+    MimeTypesConf =
+        "html\n" ++
+        "text/html\n",
+
+    ok = file:write_file(MimeTypes, MimeTypesConf),
+
+    ServerConfig =
+        "Port 0\n" ++
+        "ServerName localhost\n" ++
+        "ServerRoot ./\n" ++
+        "DocumentRoot ./\n" ++
+        "BindAddress 0.0.0.0\n" ++
+        "MimeTypes " ++ MimeTypes ++ "\n" ++
+        "Modules mod_esi\n" ++
+        "ErlScriptTimeout 8\n" ++
+        "ErlScriptAlias /erl httpd_example\n",
+
+    ok = file:write_file(HttpdConf, ServerConfig),
+
+    inets:start(),
+    {ok, Pid} =	inets:start(httpd,
+                            [{file, HttpdConf}]),
+    Info = httpd:info(Pid),
+    verify_timeout(Info, 8),
+
+    Port = proplists:get_value(port, Info),
+
+    %% Verify:  6 =< erl_script_timeout =< 10
+    Url = http_get_url(Port, 500, 6000, 4000),
+
+    {ok, {_, _, Body}} = httpc:request(Url),
+    ct:log("Response: ~p~n", [Body]),
+    verify_body(Body, 6000),
     inets:stop().
 
 
@@ -1798,6 +1917,41 @@ url(http, End, Config) ->
     {ok,Host} = inet:gethostname(),
     ?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ End.
 
+http_get_url(Port0, HeaderDelay, ChunkDelay, BadChunkDelay) ->
+    {ok, Host} = inet:gethostname(),
+    Port = integer_to_list(Port0),
+    HD = integer_to_list(HeaderDelay),
+    CD = integer_to_list(ChunkDelay),
+    BD = integer_to_list(BadChunkDelay),
+    "http://" ++ Host ++ ":" ++ Port ++
+        "/erl/httpd_example/get_chunks?header_delay=" ++ HD ++
+        "&chunk_delay=" ++ CD ++
+        "&bad_chunk_delay=" ++ BD.
+
+verify_body(Body, Timeout0) ->
+    Timeout = integer_to_list(Timeout0),
+    Res = case string:str(Body, Timeout)
+              0 -> nomatch;
+              P -> string:substr(Body, P)
+          end,
+    ct:log("Result: ~p~n", [Res]),
+    %% Fail if BAD chunk is found.
+    case Res =:= Timeout ++ " ms\r\n" of
+        true ->
+            ok;
+        false ->
+            ct:fail("Unexpected chunk received!")
+    end.
+
+verify_timeout(Info, Expected) ->
+    Timeout = proplists:get_value(erl_script_timeout, Info),
+    case Timeout =:= Expected of
+        true ->
+            ok;
+        false ->
+            ct:fail("Bad Timeout - Expected: ~p Got: ~p", [Expected, Timeout])
+    end.
+
 do_max_clients(Config) ->
     Version = proplists:get_value(http_version, Config),
     Host    = proplists:get_value(host, Config),
-- 
2.16.4

openSUSE Build Service is sponsored by