Skip to content

Commit e7a2d1e

Browse files
committed
WIP
1 parent 1527d2a commit e7a2d1e

File tree

2 files changed

+46
-17
lines changed

2 files changed

+46
-17
lines changed

lib/inets/test/httpd_bench_SUITE.erl

Lines changed: 45 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -39,8 +39,7 @@
3939
%% Common Test interface functions -----------------------------------
4040
%%--------------------------------------------------------------------
4141
suite() ->
42-
[{timetrap, {minutes, 1}},
43-
{ct_hooks,[{ts_install_cth,[{nodenames,2}]}]}].
42+
[{timetrap, {minutes, 1}}].
4443

4544
all() ->
4645
[
@@ -210,7 +209,7 @@ server_name(Config, [Server | Rest]) ->
210209
end.
211210

212211
server_name(httpd_pid) ->
213-
"inets";
212+
"inets";
214213
server_name(nginx_port) ->
215214
"nginx";
216215
server_name(dummy_pid) ->
@@ -227,11 +226,10 @@ setup(_Config, _LocalNode) ->
227226
RemHost
228227
end,
229228
Node = list_to_atom("inets_perf_server@" ++ Host),
230-
SlaveArgs = case init:get_argument(pa) of
231-
{ok, PaPaths} ->
232-
lists:append([" -pa " ++ P || [P] <- PaPaths]);
233-
_ -> []
234-
end,
229+
PeerArgs = case init:get_argument(pa) of
230+
{ok, PaPaths} -> ["-pa" | PaPaths];
231+
_ -> []
232+
end,
235233
Prog =
236234
case os:find_executable("erl") of
237235
false -> "erl";
@@ -240,7 +238,14 @@ setup(_Config, _LocalNode) ->
240238
case net_adm:ping(Node) of
241239
pong -> ok;
242240
pang ->
243-
{ok, Node} = slave:start(Host, inets_perf_server, SlaveArgs, no_link, Prog)
241+
PeerOpts = #{
242+
host => Host,
243+
name => inets_perf_server,
244+
args => PeerArgs,
245+
peer_down => continue, % respect previously used no_link option
246+
exec => Prog
247+
},
248+
{ok, Node} = peer:start(PeerOpts)
244249
end,
245250
Path = code:get_path(),
246251
true = rpc:call(Node, code, set_path, [Path]),
@@ -319,18 +324,19 @@ do_runs(Client, Config) ->
319324
Name = filename:join(DataDir, File),
320325
Args = ?MODULE:Client(Config),
321326
?MODULE:Client({init, Args}),
322-
Run =
323-
fun() ->
324-
ok = ?MODULE:Client(Args, N)
325-
end,
327+
Run = fun() ->
328+
ok = ?MODULE:Client(Args, N)
329+
end,
326330
{ok, Info} = file:read_file_info(Name, []),
327331
Length = Info#file_info.size,
328332
{TimeInMicro, _} = timer:tc(Run),
329333
ReqPerSecond = (1000000 * N) div TimeInMicro,
330334
BytesPerSecond = (1000000 * N * Length) div TimeInMicro,
331335
{{tps, ReqPerSecond}, {mbps, BytesPerSecond}}.
332336

333-
337+
%% Client handler for httpc-based test cases
338+
%% httpc_client/1 is called once with the config, to create args which will be then passed
339+
%% again into httpc_client/1 as {init, Args}.
334340
httpc_client({init, [_, Profile, URL, Headers, HTTPOpts]}) ->
335341
%% Make sure pipelining feature will kick in when appropriate.
336342
{ok, {{_ ,200, "OK"}, _,_}} = httpc:request(get,{URL, Headers}, HTTPOpts,
@@ -344,14 +350,30 @@ httpc_client(Config) ->
344350
URL = (?config(urlfun,Config))(File),
345351
Headers = ?config(http_headers, Config),
346352
HTTPOpts = ?config(http_opts, Config),
353+
case Protocol of
354+
"http" -> [];
355+
"https" -> % httpc would like to know more about certificates used in the test
356+
AllCertOpts = proplists:get_value(client_verification_opts, cert_opts(Config)),
357+
SSLOpts = [
358+
{verify_peer, true},
359+
{cacertfile, proplists:get_value(cacertfile, AllCertOpts)}
360+
],
361+
[{ssl, SSLOpts}]
362+
end,
347363
[Protocol, Profile, URL, Headers, HTTPOpts].
364+
365+
%% This will receive arguments (Args, N) where N is iterations count,
366+
%% with Args produced by httpc_client/1 above.
348367
httpc_client(_,0) ->
349368
ok;
350369
httpc_client([Protocol, Profile, URL, Headers, HTTPOpts], N) ->
351370
{ok, {{_ ,200,"OK"}, _,_}} = httpc:request(get,{URL, Headers}, HTTPOpts, [{body_format, binary},
352371
{socket_opts, [{nodelay, true}]}], Profile),
353372
httpc_client([Protocol, Profile, URL, Headers, HTTPOpts], N-1).
354373

374+
%% Client handler based on httpd_test_lib
375+
%% httpd_lib_client/1 is called once with the config, to create args which will be then passed
376+
%% again into httpd_lib_client/1 as {init, Args}.
355377
httpd_lib_client({init, [_, Type, Version, Request, Host, Port, Opts]}) ->
356378
ok = httpd_test_lib:verify_request(Type, Host,
357379
Port,
@@ -388,6 +410,8 @@ httpd_lib_client(Config) ->
388410
httpd_lib_client(Args, 1),
389411
Args.
390412

413+
%% This will receive arguments (Args, N) where N is iterations count,
414+
%% with Args produced by httpd_lib_client/1 above.
391415
httpd_lib_client(_, 0) ->
392416
ok;
393417
httpd_lib_client([true, Type, Version, Request, Host, Port, Opts], N) ->
@@ -406,6 +430,9 @@ httpd_lib_client([false, Type, Version, Request, Host, Port, Opts] = List, N) ->
406430
{version, Version}], infinity),
407431
httpd_lib_client(List, N-1).
408432

433+
%% Client handler for wget-based test cases
434+
%% wget_client/1 is called once with the config, to create args which will be then passed
435+
%% again into wget_client/1 as {init, Args}.
409436
wget_client({init,_}) ->
410437
ok;
411438
wget_client(Config) ->
@@ -424,7 +451,10 @@ wget_client(Config) ->
424451
end,
425452
wget_req_file(FileName,URL,Iter),
426453
[KeepAlive, FileName, URL, Protocol, ProtocolOpts, Iter].
427-
wget_client([KeepAlive, WgetFile, _URL, Protocol, ProtocolOpts, _], _) ->
454+
455+
%% This will receive arguments (Args, N) where N is iterations count,
456+
%% with Args produced by wget_client/1 above.
457+
wget_client([KeepAlive, WgetFile, _URL, Protocol, ProtocolOpts, _], _Iter) ->
428458
process_flag(trap_exit, true),
429459
Cmd = wget_N(KeepAlive, WgetFile, Protocol, ProtocolOpts),
430460
%%ct:log("Wget cmd: ~p", [Cmd]),

lib/inets/test/inets.spec

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{suites,"../inets_test", all}.
2-
{skip_suites, "../inets_test", [httpd_bench_SUITE],
3-
"Benchmarks run separately"}.
2+
% {skip_suites, "../inets_test", [httpd_bench_SUITE], "Benchmarks run separately"}.
43
{event_handler, {cte_track, []}}.
54
{enable_builtin_hooks, false}.
65
{ct_hooks, [{cth_log_redirect, [{mode, replace}]}]}.

0 commit comments

Comments
 (0)