39
39
% % Common Test interface functions -----------------------------------
40
40
% %--------------------------------------------------------------------
41
41
suite () ->
42
- [{timetrap , {minutes , 1 }},
43
- {ct_hooks ,[{ts_install_cth ,[{nodenames ,2 }]}]}].
42
+ [{timetrap , {minutes , 1 }}].
44
43
45
44
all () ->
46
45
[
@@ -210,7 +209,7 @@ server_name(Config, [Server | Rest]) ->
210
209
end .
211
210
212
211
server_name (httpd_pid ) ->
213
- " inets" ;
212
+ " inets" ;
214
213
server_name (nginx_port ) ->
215
214
" nginx" ;
216
215
server_name (dummy_pid ) ->
@@ -227,11 +226,10 @@ setup(_Config, _LocalNode) ->
227
226
RemHost
228
227
end ,
229
228
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 ,
235
233
Prog =
236
234
case os :find_executable (" erl" ) of
237
235
false -> " erl" ;
@@ -240,7 +238,14 @@ setup(_Config, _LocalNode) ->
240
238
case net_adm :ping (Node ) of
241
239
pong -> ok ;
242
240
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 )
244
249
end ,
245
250
Path = code :get_path (),
246
251
true = rpc :call (Node , code , set_path , [Path ]),
@@ -319,18 +324,19 @@ do_runs(Client, Config) ->
319
324
Name = filename :join (DataDir , File ),
320
325
Args = ? MODULE :Client (Config ),
321
326
? 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 ,
326
330
{ok , Info } = file :read_file_info (Name , []),
327
331
Length = Info # file_info .size ,
328
332
{TimeInMicro , _ } = timer :tc (Run ),
329
333
ReqPerSecond = (1000000 * N ) div TimeInMicro ,
330
334
BytesPerSecond = (1000000 * N * Length ) div TimeInMicro ,
331
335
{{tps , ReqPerSecond }, {mbps , BytesPerSecond }}.
332
336
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}.
334
340
httpc_client ({init , [_ , Profile , URL , Headers , HTTPOpts ]}) ->
335
341
% % Make sure pipelining feature will kick in when appropriate.
336
342
{ok , {{_ ,200 , " OK" }, _ ,_ }} = httpc :request (get ,{URL , Headers }, HTTPOpts ,
@@ -344,14 +350,30 @@ httpc_client(Config) ->
344
350
URL = (? config (urlfun ,Config ))(File ),
345
351
Headers = ? config (http_headers , Config ),
346
352
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 ,
347
363
[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.
348
367
httpc_client (_ ,0 ) ->
349
368
ok ;
350
369
httpc_client ([Protocol , Profile , URL , Headers , HTTPOpts ], N ) ->
351
370
{ok , {{_ ,200 ," OK" }, _ ,_ }} = httpc :request (get ,{URL , Headers }, HTTPOpts , [{body_format , binary },
352
371
{socket_opts , [{nodelay , true }]}], Profile ),
353
372
httpc_client ([Protocol , Profile , URL , Headers , HTTPOpts ], N - 1 ).
354
373
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}.
355
377
httpd_lib_client ({init , [_ , Type , Version , Request , Host , Port , Opts ]}) ->
356
378
ok = httpd_test_lib :verify_request (Type , Host ,
357
379
Port ,
@@ -388,6 +410,8 @@ httpd_lib_client(Config) ->
388
410
httpd_lib_client (Args , 1 ),
389
411
Args .
390
412
413
+ % % This will receive arguments (Args, N) where N is iterations count,
414
+ % % with Args produced by httpd_lib_client/1 above.
391
415
httpd_lib_client (_ , 0 ) ->
392
416
ok ;
393
417
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) ->
406
430
{version , Version }], infinity ),
407
431
httpd_lib_client (List , N - 1 ).
408
432
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}.
409
436
wget_client ({init ,_ }) ->
410
437
ok ;
411
438
wget_client (Config ) ->
@@ -424,7 +451,10 @@ wget_client(Config) ->
424
451
end ,
425
452
wget_req_file (FileName ,URL ,Iter ),
426
453
[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 ) ->
428
458
process_flag (trap_exit , true ),
429
459
Cmd = wget_N (KeepAlive , WgetFile , Protocol , ProtocolOpts ),
430
460
% %ct:log("Wget cmd: ~p", [Cmd]),
0 commit comments