File 2391-kernel-test-Extend-gen-tcp-socket-ttest-tests.patch of Package erlang
From 4b48ff129cbc0fc467faa84d95c6b2fc074d71bd Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Fri, 25 Jul 2025 16:42:44 +0200
Subject: [PATCH] [kernel|test] Extend gen-tcp-socket ttest tests
Extend gen-tcp-socket (gs) ttest test cases.
The (ttest-) suite is now "complete" with server/client combinations.
Also fixed node handling. It turned out the server and client where
*not* actually running in separate nodes (all where running in the
same node).
Also fixed ( = "improved") global syncing which was off.
---
.../test/kernel_test_global_sys_monitor.erl | 12 +-
lib/kernel/test/kernel_test_lib.erl | 37 +-
lib/kernel/test/kernel_test_lib.hrl | 1 +
lib/kernel/test/kernel_test_sys_monitor.erl | 43 +-
lib/kernel/test/socket_test_ttest_tcp_gen.erl | 7 +-
lib/kernel/test/socket_test_ttest_tcp_gs.erl | 24 +-
.../test/socket_test_ttest_tcp_socket.erl | 7 +-
lib/kernel/test/socket_ttest_SUITE.erl | 11031 +++++++++++-----
8 files changed, 8028 insertions(+), 3134 deletions(-)
diff --git a/lib/kernel/test/kernel_test_global_sys_monitor.erl b/lib/kernel/test/kernel_test_global_sys_monitor.erl
index 340ef0970b..e115e98f57 100644
--- a/lib/kernel/test/kernel_test_global_sys_monitor.erl
+++ b/lib/kernel/test/kernel_test_global_sys_monitor.erl
@@ -126,7 +126,7 @@ loop(State) ->
{nodedown = Event, Node} ->
State2 = process_event(State, Node, Event),
- loop(State2);
+ loop(State2);
_ ->
loop(State)
@@ -149,6 +149,11 @@ process_event(State, Node, {TS, starting}) ->
end,
State;
+process_event(State, Node, {TS, started}) ->
+ FTS = format_timestamp(TS),
+ info_msg("System Monitor started on node ~p at ~s", [Node, FTS]),
+ State;
+
process_event(State, Node, {TS, stopping}) ->
FTS = format_timestamp(TS),
info_msg("System Monitor stopping on node ~p at ~s", [Node, FTS]),
@@ -160,6 +165,11 @@ process_event(State, Node, {TS, stopping}) ->
end,
State;
+process_event(State, Node, {TS, ping}) ->
+ FTS = format_timestamp(TS),
+ info_msg("System Monitor on node ~p was pinged at ~s", [Node, FTS]),
+ State;
+
process_event(State, Node, {TS, already_started}) ->
FTS = format_timestamp(TS),
info_msg("System Monitor already started on node ~p at ~s", [Node, FTS]),
diff --git a/lib/kernel/test/kernel_test_lib.erl b/lib/kernel/test/kernel_test_lib.erl
index cd41c3e9ef..86d54e94cb 100644
--- a/lib/kernel/test/kernel_test_lib.erl
+++ b/lib/kernel/test/kernel_test_lib.erl
@@ -29,6 +29,7 @@
listen/3,
connect/4, connect/5,
open/3,
+ ttest_condition/0,
is_socket_backend/1,
inet_backend_opts/1,
explicit_inet_backend/0, explicit_inet_backend/1,
@@ -2561,6 +2562,9 @@ start_node(Name, Args, Opts) ->
" -pa " ++ Pa ++
" -s " ++ atom_to_list(kernel_test_sys_monitor) ++ " start" ++
" -s global sync",
+ print("~w -> try start node ~p with"
+ "~n Args: ~p"
+ "~n Opts: ~p", [?FUNCTION_NAME, Name, A, Opts]),
case test_server:start_node(Name, peer, [{args, A}|Opts]) of
{ok, _Node} = OK ->
global:sync(),
@@ -2619,15 +2623,19 @@ socket_type(Config) ->
listen(Config, Port, Opts) ->
InetBackendOpts = inet_backend_opts(Config),
- gen_tcp:listen(Port, InetBackendOpts ++ Opts).
+ gen_tcp:listen(Port,
+ InetBackendOpts ++ Opts).
connect(Config, Host, Port, Opts) ->
InetBackendOpts = inet_backend_opts(Config),
- gen_tcp:connect(Host, Port, InetBackendOpts ++ Opts).
+ gen_tcp:connect(Host, Port,
+ InetBackendOpts ++ Opts).
connect(Config, Host, Port, Opts, Timeout) ->
InetBackendOpts = inet_backend_opts(Config),
- gen_tcp:connect(Host, Port, InetBackendOpts ++ Opts, Timeout).
+ gen_tcp:connect(Host, Port,
+ InetBackendOpts ++ Opts,
+ Timeout).
%% gen_udp wrappers
@@ -2638,7 +2646,12 @@ open(Config, Port, Opts) ->
inet_backend_opts(Config) when is_list(Config) ->
+ inet_backend_opts(Config, any).
+
+inet_backend_opts(Config, Proto) when is_list(Config) ->
case lists:keyfind(socket_create_opts, 1, Config) of
+ {_, [{inet_backend, socket}] = InetBackendOpts} when (Proto =:= tcp) ->
+ InetBackendOpts ++ [{erb, 10}];
{_, InetBackendOpts} ->
InetBackendOpts;
false ->
@@ -2654,6 +2667,24 @@ is_socket_backend(Config) when is_list(Config) ->
end.
+%% ESOCK_TTEST_CONDITION
+
+ttest_condition() ->
+ case application:get_all_env(kernel) of
+ Env when is_list(Env) ->
+ case lists:keyfind(esock_ttest_condition, 1, Env) of
+ {_, infinity = Factor} ->
+ Factor;
+ {_, Factor} when is_integer(Factor) andalso (Factor > 0) ->
+ Factor;
+ _ ->
+ undefined
+ end;
+ _ ->
+ undefined
+ end.
+
+
explicit_inet_backend() ->
case application:get_all_env(kernel) of
Env when is_list(Env) ->
diff --git a/lib/kernel/test/kernel_test_lib.hrl b/lib/kernel/test/kernel_test_lib.hrl
index 372df79e80..0e048a1860 100644
--- a/lib/kernel/test/kernel_test_lib.hrl
+++ b/lib/kernel/test/kernel_test_lib.hrl
@@ -52,6 +52,7 @@
-define(OPEN(C, P), ?LIB:open(C, P, [])).
-define(OPEN(C, P, O), ?LIB:open(C, P, O)).
+-define(TTEST_CONDITION(), ?LIB:ttest_condition()).
-define(INET_BACKEND_OPTS(C), ?LIB:inet_backend_opts(C)).
-define(EXPLICIT_INET_BACKEND(), ?LIB:explicit_inet_backend()).
-define(EXPLICIT_INET_BACKEND(C), ?LIB:explicit_inet_backend(C)).
diff --git a/lib/kernel/test/kernel_test_sys_monitor.erl b/lib/kernel/test/kernel_test_sys_monitor.erl
index bf822af79c..5dfe7ef52c 100644
--- a/lib/kernel/test/kernel_test_sys_monitor.erl
+++ b/lib/kernel/test/kernel_test_sys_monitor.erl
@@ -23,6 +23,7 @@
-module(kernel_test_sys_monitor).
-export([start/0, stop/0,
+ ping/0, ping/1,
init/1]).
-define(NAME, ?MODULE).
@@ -48,6 +49,27 @@ stop() ->
end.
+ping(Node) when is_atom(Node) andalso (Node =/= node()) ->
+ case rpc:call(Node, ?MODULE, ping, []) of
+ {badrpc, nodedown} ->
+ pang;
+ Reply ->
+ Reply
+ end.
+
+ping() ->
+ case whereis(?NAME) of
+ Pid when is_pid(Pid) ->
+ Pid ! {?MODULE, self(), ping},
+ receive
+ {?MODULE, Pid, Reply} ->
+ Reply
+ end;
+ _ ->
+ pang
+ end.
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -55,7 +77,8 @@ init(Parent) ->
process_flag(priority, high),
try register(?NAME, self()) of
true ->
- global:sync(),
+ await_synced(),
+ ?GSM:log({?GSM:timestamp(), starting}),
MonSettings = [
busy_port,
busy_dist_port,
@@ -64,8 +87,8 @@ init(Parent) ->
{large_heap, 8*1024*1024} % 8 MB
],
erlang:system_monitor(self(), MonSettings),
- ?GSM:log({?GSM:timestamp(), starting}),
proc_lib:init_ack(Parent, {ok, self()}),
+ ?GSM:log({?GSM:timestamp(), started}),
loop(#{parent => Parent})
catch
_:_:_ ->
@@ -75,6 +98,17 @@ init(Parent) ->
end.
+await_synced() ->
+ case global:whereis_name(?GSM) of
+ Pid when is_pid(Pid) ->
+ ok;
+ undefined ->
+ global:sync(),
+ receive after 1000 -> ok end,
+ await_synced()
+ end.
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
loop(State) ->
@@ -88,6 +122,11 @@ loop(State) ->
From ! {?MODULE, self(), stop},
exit(normal);
+ {?MODULE, From, ping} ->
+ ?GSM:log({?GSM:timestamp(), ping}),
+ From ! {?MODULE, self(), pong},
+ loop(State);
+
_ ->
loop(State)
end.
diff --git a/lib/kernel/test/socket_test_ttest_tcp_gen.erl b/lib/kernel/test/socket_test_ttest_tcp_gen.erl
index 333f744b88..6d9a8444c1 100644
--- a/lib/kernel/test/socket_test_ttest_tcp_gen.erl
+++ b/lib/kernel/test/socket_test_ttest_tcp_gen.erl
@@ -38,7 +38,8 @@
recv/2, recv/3,
send/2,
shutdown/2,
- sockname/1
+ sockname/1,
+ info/1
]).
@@ -139,6 +140,10 @@ sockname(Sock) ->
inet:sockname(Sock).
+info(Sock) ->
+ inet:info(Sock).
+
+
%% ==========================================================================
diff --git a/lib/kernel/test/socket_test_ttest_tcp_gs.erl b/lib/kernel/test/socket_test_ttest_tcp_gs.erl
index 2ec3a4fdd7..98abfed132 100644
--- a/lib/kernel/test/socket_test_ttest_tcp_gs.erl
+++ b/lib/kernel/test/socket_test_ttest_tcp_gs.erl
@@ -39,7 +39,8 @@
recv/2, recv/3,
send/2,
shutdown/2,
- sockname/1
+ sockname/1,
+ info/1
]).
@@ -87,11 +88,17 @@ connect(Addr, Port, #{domain := Domain}) ->
do_connect(Addr, Port, Opts).
do_connect(Addr, Port, Opts) ->
- case gen_tcp:connect(Addr, Port, Opts) of
+ %% Since this (usually) is run on a remote node,
+ %% we try-catch the call so that we can re-through
+ %% with as much info as possible.
+ try gen_tcp:connect(Addr, Port, Opts) of
{ok, Sock} ->
{ok, Sock};
{error, _} = ERROR ->
ERROR
+ catch
+ C:E:S ->
+ exit({catched, {C, E, S}})
end.
controlling_process(Sock, NewPid) ->
@@ -112,7 +119,14 @@ listen(Port, #{domain := Domain}) when is_integer(Port) andalso (Port >= 0) ->
Domain,
binary, {ip, Addr}, {packet, raw}, {active, false},
{buffer, 32*1024}],
- gen_tcp:listen(Port, Opts);
+ %% Since this (usually) is run on a remote node,
+ %% we try-catch the call so that we can re-through
+ %% with as much info as possible.
+ try gen_tcp:listen(Port, Opts)
+ catch
+ C:E:S ->
+ exit({catched, {C, E, S}})
+ end;
{error, _} = ERROR ->
ERROR
end.
@@ -144,6 +158,10 @@ sockname(Sock) ->
inet:sockname(Sock).
+info(Sock) ->
+ inet:info(Sock).
+
+
%% ==========================================================================
diff --git a/lib/kernel/test/socket_test_ttest_tcp_socket.erl b/lib/kernel/test/socket_test_ttest_tcp_socket.erl
index 578b9faf9c..b1eb60e7a3 100644
--- a/lib/kernel/test/socket_test_ttest_tcp_socket.erl
+++ b/lib/kernel/test/socket_test_ttest_tcp_socket.erl
@@ -39,7 +39,8 @@
recv/2, recv/3,
send/2,
shutdown/2,
- sockname/1
+ sockname/1,
+ info/1
]).
@@ -387,6 +388,10 @@ sockname(#{sock := Sock}) ->
end.
+info(#{sock := Sock}) ->
+ socket:info(Sock).
+
+
%% ==========================================================================
reader_init(ControllingProcess, Sock, Async, Active, Method)
diff --git a/lib/kernel/test/socket_ttest_SUITE.erl b/lib/kernel/test/socket_ttest_SUITE.erl
index 72f9abeca1..9fedbcd139 100644
--- a/lib/kernel/test/socket_ttest_SUITE.erl
+++ b/lib/kernel/test/socket_ttest_SUITE.erl
@@ -118,6 +118,29 @@
ttest_sgenf_cgent_large_tcp4/1,
ttest_sgenf_cgent_large_tcp6/1,
+ %% Server: transport = gen_tcp, active = false
+ %% Client: transport = gen_tcp(socket)
+ ttest_sgenf_cgsf_small_tcp4/1,
+ ttest_sgenf_cgsf_small_tcp6/1,
+ ttest_sgenf_cgsf_medium_tcp4/1,
+ ttest_sgenf_cgsf_medium_tcp6/1,
+ ttest_sgenf_cgsf_large_tcp4/1,
+ ttest_sgenf_cgsf_large_tcp6/1,
+
+ ttest_sgenf_cgso_small_tcp4/1,
+ ttest_sgenf_cgso_small_tcp6/1,
+ ttest_sgenf_cgso_medium_tcp4/1,
+ ttest_sgenf_cgso_medium_tcp6/1,
+ ttest_sgenf_cgso_large_tcp4/1,
+ ttest_sgenf_cgso_large_tcp6/1,
+
+ ttest_sgenf_cgst_small_tcp4/1,
+ ttest_sgenf_cgst_small_tcp6/1,
+ ttest_sgenf_cgst_medium_tcp4/1,
+ ttest_sgenf_cgst_medium_tcp6/1,
+ ttest_sgenf_cgst_large_tcp4/1,
+ ttest_sgenf_cgst_large_tcp6/1,
+
%% Server: transport = gen_tcp, active = false
%% Client: transport = socket(tcp)
ttest_sgenf_csockf_small_tcp4/1,
@@ -141,15 +164,6 @@
ttest_sgenf_csockt_large_tcp4/1,
ttest_sgenf_csockt_large_tcp6/1,
- %% Server: transport = gen_tcp(socket), active = false
- %% Client: transport = socket(tcp)
- ttest_sgsf_csockf_small_tcp4/1,
- ttest_sgsf_csockf_small_tcp6/1,
- ttest_sgsf_csockf_medium_tcp4/1,
- ttest_sgsf_csockf_medium_tcp6/1,
- ttest_sgsf_csockf_large_tcp4/1,
- ttest_sgsf_csockf_large_tcp6/1,
-
%% Server: transport = gen_tcp, active = once
%% Client: transport = gen_tcp
ttest_sgeno_cgenf_small_tcp4/1,
@@ -173,6 +187,29 @@
ttest_sgeno_cgent_large_tcp4/1,
ttest_sgeno_cgent_large_tcp6/1,
+ %% Server: transport = gen_tcp, active = once
+ %% Client: transport = gen_tcp(socket)
+ ttest_sgeno_cgsf_small_tcp4/1,
+ ttest_sgeno_cgsf_small_tcp6/1,
+ ttest_sgeno_cgsf_medium_tcp4/1,
+ ttest_sgeno_cgsf_medium_tcp6/1,
+ ttest_sgeno_cgsf_large_tcp4/1,
+ ttest_sgeno_cgsf_large_tcp6/1,
+
+ ttest_sgeno_cgso_small_tcp4/1,
+ ttest_sgeno_cgso_small_tcp6/1,
+ ttest_sgeno_cgso_medium_tcp4/1,
+ ttest_sgeno_cgso_medium_tcp6/1,
+ ttest_sgeno_cgso_large_tcp4/1,
+ ttest_sgeno_cgso_large_tcp6/1,
+
+ ttest_sgeno_cgst_small_tcp4/1,
+ ttest_sgeno_cgst_small_tcp6/1,
+ ttest_sgeno_cgst_medium_tcp4/1,
+ ttest_sgeno_cgst_medium_tcp6/1,
+ ttest_sgeno_cgst_large_tcp4/1,
+ ttest_sgeno_cgst_large_tcp6/1,
+
%% Server: transport = gen_tcp, active = once
%% Client: transport = socket(tcp)
ttest_sgeno_csockf_small_tcp4/1,
@@ -219,6 +256,29 @@
ttest_sgent_cgent_large_tcp4/0, ttest_sgent_cgent_large_tcp4/1,
ttest_sgent_cgent_large_tcp6/0, ttest_sgent_cgent_large_tcp6/1,
+ %% Server: transport = gen_tcp, active = true
+ %% Client: transport = gen_tcp(socket)
+ ttest_sgent_cgsf_small_tcp4/1,
+ ttest_sgent_cgsf_small_tcp6/1,
+ ttest_sgent_cgsf_medium_tcp4/1,
+ ttest_sgent_cgsf_medium_tcp6/1,
+ ttest_sgent_cgsf_large_tcp4/1,
+ ttest_sgent_cgsf_large_tcp6/1,
+
+ ttest_sgent_cgso_small_tcp4/1,
+ ttest_sgent_cgso_small_tcp6/1,
+ ttest_sgent_cgso_medium_tcp4/1,
+ ttest_sgent_cgso_medium_tcp6/1,
+ ttest_sgent_cgso_large_tcp4/1,
+ ttest_sgent_cgso_large_tcp6/1,
+
+ ttest_sgent_cgst_small_tcp4/1,
+ ttest_sgent_cgst_small_tcp6/1,
+ ttest_sgent_cgst_medium_tcp4/1,
+ ttest_sgent_cgst_medium_tcp6/1,
+ ttest_sgent_cgst_large_tcp4/1,
+ ttest_sgent_cgst_large_tcp6/1,
+
%% Server: transport = gen_tcp, active = true
%% Client: transport = socket(tcp)
ttest_sgent_csockf_small_tcp4/1,
@@ -242,6 +302,213 @@
ttest_sgent_csockt_large_tcp4/1,
ttest_sgent_csockt_large_tcp6/1,
+ %% Server: transport = gen_tcp(socket), active = false
+ %% Client: transport = gen_tcp
+ ttest_sgsf_cgenf_small_tcp4/1,
+ ttest_sgsf_cgenf_small_tcp6/1,
+ ttest_sgsf_cgenf_medium_tcp4/1,
+ ttest_sgsf_cgenf_medium_tcp6/1,
+ ttest_sgsf_cgenf_large_tcp4/1,
+ ttest_sgsf_cgenf_large_tcp6/1,
+
+ ttest_sgsf_cgeno_small_tcp4/1,
+ ttest_sgsf_cgeno_small_tcp6/1,
+ ttest_sgsf_cgeno_medium_tcp4/1,
+ ttest_sgsf_cgeno_medium_tcp6/1,
+ ttest_sgsf_cgeno_large_tcp4/1,
+ ttest_sgsf_cgeno_large_tcp6/1,
+
+ ttest_sgsf_cgent_small_tcp4/1,
+ ttest_sgsf_cgent_small_tcp6/1,
+ ttest_sgsf_cgent_medium_tcp4/1,
+ ttest_sgsf_cgent_medium_tcp6/1,
+ ttest_sgsf_cgent_large_tcp4/1,
+ ttest_sgsf_cgent_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = false
+ %% Client: transport = gen_tcp(socket),
+ ttest_sgsf_cgsf_small_tcp4/1,
+ ttest_sgsf_cgsf_small_tcp6/1,
+ ttest_sgsf_cgsf_medium_tcp4/1,
+ ttest_sgsf_cgsf_medium_tcp6/1,
+ ttest_sgsf_cgsf_large_tcp4/1,
+ ttest_sgsf_cgsf_large_tcp6/1,
+
+ ttest_sgsf_cgso_small_tcp4/1,
+ ttest_sgsf_cgso_small_tcp6/1,
+ ttest_sgsf_cgso_medium_tcp4/1,
+ ttest_sgsf_cgso_medium_tcp6/1,
+ ttest_sgsf_cgso_large_tcp4/1,
+ ttest_sgsf_cgso_large_tcp6/1,
+
+ ttest_sgsf_cgst_small_tcp4/1,
+ ttest_sgsf_cgst_small_tcp6/1,
+ ttest_sgsf_cgst_medium_tcp4/1,
+ ttest_sgsf_cgst_medium_tcp6/1,
+ ttest_sgsf_cgst_large_tcp4/1,
+ ttest_sgsf_cgst_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = false
+ %% Client: transport = socket(tcp)
+ ttest_sgsf_csockf_small_tcp4/1,
+ ttest_sgsf_csockf_small_tcp6/1,
+ ttest_sgsf_csockf_medium_tcp4/1,
+ ttest_sgsf_csockf_medium_tcp6/1,
+ ttest_sgsf_csockf_large_tcp4/1,
+ ttest_sgsf_csockf_large_tcp6/1,
+
+ ttest_sgsf_csocko_small_tcp4/1,
+ ttest_sgsf_csocko_small_tcp6/1,
+ ttest_sgsf_csocko_medium_tcp4/1,
+ ttest_sgsf_csocko_medium_tcp6/1,
+ ttest_sgsf_csocko_large_tcp4/1,
+ ttest_sgsf_csocko_large_tcp6/1,
+
+ ttest_sgsf_csockt_small_tcp4/1,
+ ttest_sgsf_csockt_small_tcp6/1,
+ ttest_sgsf_csockt_medium_tcp4/1,
+ ttest_sgsf_csockt_medium_tcp6/1,
+ ttest_sgsf_csockt_large_tcp4/1,
+ ttest_sgsf_csockt_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = once
+ %% Client: transport = gen_tcp
+ ttest_sgso_cgenf_small_tcp4/1,
+ ttest_sgso_cgenf_small_tcp6/1,
+ ttest_sgso_cgenf_medium_tcp4/1,
+ ttest_sgso_cgenf_medium_tcp6/1,
+ ttest_sgso_cgenf_large_tcp4/1,
+ ttest_sgso_cgenf_large_tcp6/1,
+
+ ttest_sgso_cgeno_small_tcp4/1,
+ ttest_sgso_cgeno_small_tcp6/1,
+ ttest_sgso_cgeno_medium_tcp4/1,
+ ttest_sgso_cgeno_medium_tcp6/1,
+ ttest_sgso_cgeno_large_tcp4/1,
+ ttest_sgso_cgeno_large_tcp6/1,
+
+ ttest_sgso_cgent_small_tcp4/1,
+ ttest_sgso_cgent_small_tcp6/1,
+ ttest_sgso_cgent_medium_tcp4/1,
+ ttest_sgso_cgent_medium_tcp6/1,
+ ttest_sgso_cgent_large_tcp4/1,
+ ttest_sgso_cgent_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = once
+ %% Client: transport = gen_tcp(socket)
+ ttest_sgso_cgsf_small_tcp4/1,
+ ttest_sgso_cgsf_small_tcp6/1,
+ ttest_sgso_cgsf_medium_tcp4/1,
+ ttest_sgso_cgsf_medium_tcp6/1,
+ ttest_sgso_cgsf_large_tcp4/1,
+ ttest_sgso_cgsf_large_tcp6/1,
+
+ ttest_sgso_cgso_small_tcp4/1,
+ ttest_sgso_cgso_small_tcp6/1,
+ ttest_sgso_cgso_medium_tcp4/1,
+ ttest_sgso_cgso_medium_tcp6/1,
+ ttest_sgso_cgso_large_tcp4/1,
+ ttest_sgso_cgso_large_tcp6/1,
+
+ ttest_sgso_cgst_small_tcp4/1,
+ ttest_sgso_cgst_small_tcp6/1,
+ ttest_sgso_cgst_medium_tcp4/1,
+ ttest_sgso_cgst_medium_tcp6/1,
+ ttest_sgso_cgst_large_tcp4/1,
+ ttest_sgso_cgst_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = once
+ %% Client: transport = socket(tcp)
+ ttest_sgso_csockf_small_tcp4/1,
+ ttest_sgso_csockf_small_tcp6/1,
+ ttest_sgso_csockf_medium_tcp4/1,
+ ttest_sgso_csockf_medium_tcp6/1,
+ ttest_sgso_csockf_large_tcp4/1,
+ ttest_sgso_csockf_large_tcp6/1,
+
+ ttest_sgso_csocko_small_tcp4/1,
+ ttest_sgso_csocko_small_tcp6/1,
+ ttest_sgso_csocko_medium_tcp4/1,
+ ttest_sgso_csocko_medium_tcp6/1,
+ ttest_sgso_csocko_large_tcp4/1,
+ ttest_sgso_csocko_large_tcp6/1,
+
+ ttest_sgso_csockt_small_tcp4/1,
+ ttest_sgso_csockt_small_tcp6/1,
+ ttest_sgso_csockt_medium_tcp4/1,
+ ttest_sgso_csockt_medium_tcp6/1,
+ ttest_sgso_csockt_large_tcp4/1,
+ ttest_sgso_csockt_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = true
+ %% Client: transport = gen_tcp
+ ttest_sgst_cgenf_small_tcp4/1,
+ ttest_sgst_cgenf_small_tcp6/1,
+ ttest_sgst_cgenf_medium_tcp4/1,
+ ttest_sgst_cgenf_medium_tcp6/1,
+ ttest_sgst_cgenf_large_tcp4/1,
+ ttest_sgst_cgenf_large_tcp6/1,
+
+ ttest_sgst_cgeno_small_tcp4/1,
+ ttest_sgst_cgeno_small_tcp6/1,
+ ttest_sgst_cgeno_medium_tcp4/1,
+ ttest_sgst_cgeno_medium_tcp6/1,
+ ttest_sgst_cgeno_large_tcp4/1,
+ ttest_sgst_cgeno_large_tcp6/1,
+
+ ttest_sgst_cgent_small_tcp4/1,
+ ttest_sgst_cgent_small_tcp6/1,
+ ttest_sgst_cgent_medium_tcp4/1,
+ ttest_sgst_cgent_medium_tcp6/1,
+ ttest_sgst_cgent_large_tcp4/1,
+ ttest_sgst_cgent_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = true
+ %% Client: transport = gen_tcp(socket)
+ ttest_sgst_cgsf_small_tcp4/1,
+ ttest_sgst_cgsf_small_tcp6/1,
+ ttest_sgst_cgsf_medium_tcp4/1,
+ ttest_sgst_cgsf_medium_tcp6/1,
+ ttest_sgst_cgsf_large_tcp4/1,
+ ttest_sgst_cgsf_large_tcp6/1,
+
+ ttest_sgst_cgso_small_tcp4/1,
+ ttest_sgst_cgso_small_tcp6/1,
+ ttest_sgst_cgso_medium_tcp4/1,
+ ttest_sgst_cgso_medium_tcp6/1,
+ ttest_sgst_cgso_large_tcp4/1,
+ ttest_sgst_cgso_large_tcp6/1,
+
+ ttest_sgst_cgst_small_tcp4/1,
+ ttest_sgst_cgst_small_tcp6/1,
+ ttest_sgst_cgst_medium_tcp4/1,
+ ttest_sgst_cgst_medium_tcp6/1,
+ ttest_sgst_cgst_large_tcp4/1,
+ ttest_sgst_cgst_large_tcp6/1,
+
+ %% Server: transport = gen_tcp(socket), active = true
+ %% Client: transport = socket(tcp)
+ ttest_sgst_csockf_small_tcp4/1,
+ ttest_sgst_csockf_small_tcp6/1,
+ ttest_sgst_csockf_medium_tcp4/1,
+ ttest_sgst_csockf_medium_tcp6/1,
+ ttest_sgst_csockf_large_tcp4/1,
+ ttest_sgst_csockf_large_tcp6/1,
+
+ ttest_sgst_csocko_small_tcp4/1,
+ ttest_sgst_csocko_small_tcp6/1,
+ ttest_sgst_csocko_medium_tcp4/1,
+ ttest_sgst_csocko_medium_tcp6/1,
+ ttest_sgst_csocko_large_tcp4/1,
+ ttest_sgst_csocko_large_tcp6/1,
+
+ ttest_sgst_csockt_small_tcp4/1,
+ ttest_sgst_csockt_small_tcp6/1,
+ ttest_sgst_csockt_medium_tcp4/1,
+ ttest_sgst_csockt_medium_tcp6/1,
+ ttest_sgst_csockt_large_tcp4/1,
+ ttest_sgst_csockt_large_tcp6/1,
+
%% Server: transport = socket(tcp), active = false
%% Client: transport = gen_tcp
ttest_ssockf_cgenf_small_tcp4/1,
@@ -273,6 +540,18 @@
ttest_ssockf_cgsf_medium_tcp6/1,
ttest_ssockf_cgsf_large_tcp4/1,
ttest_ssockf_cgsf_large_tcp6/1,
+ ttest_ssockf_cgso_small_tcp4/1,
+ ttest_ssockf_cgso_small_tcp6/1,
+ ttest_ssockf_cgso_medium_tcp4/1,
+ ttest_ssockf_cgso_medium_tcp6/1,
+ ttest_ssockf_cgso_large_tcp4/1,
+ ttest_ssockf_cgso_large_tcp6/1,
+ ttest_ssockf_cgst_small_tcp4/1,
+ ttest_ssockf_cgst_small_tcp6/1,
+ ttest_ssockf_cgst_medium_tcp4/1,
+ ttest_ssockf_cgst_medium_tcp6/1,
+ ttest_ssockf_cgst_large_tcp4/1,
+ ttest_ssockf_cgst_large_tcp6/1,
%% Server: transport = socket(tcp), active = false
%% Client: transport = socket(tcp)
@@ -329,6 +608,29 @@
ttest_ssocko_cgent_large_tcp4/1,
ttest_ssocko_cgent_large_tcp6/1,
+ %% Server: transport = socket(tcp), active = once
+ %% Client: transport = gen_tcp(socket)
+ ttest_ssocko_cgsf_small_tcp4/1,
+ ttest_ssocko_cgsf_small_tcp6/1,
+ ttest_ssocko_cgsf_medium_tcp4/1,
+ ttest_ssocko_cgsf_medium_tcp6/1,
+ ttest_ssocko_cgsf_large_tcp4/1,
+ ttest_ssocko_cgsf_large_tcp6/1,
+
+ ttest_ssocko_cgso_small_tcp4/1,
+ ttest_ssocko_cgso_small_tcp6/1,
+ ttest_ssocko_cgso_medium_tcp4/1,
+ ttest_ssocko_cgso_medium_tcp6/1,
+ ttest_ssocko_cgso_large_tcp4/1,
+ ttest_ssocko_cgso_large_tcp6/1,
+
+ ttest_ssocko_cgst_small_tcp4/1,
+ ttest_ssocko_cgst_small_tcp6/1,
+ ttest_ssocko_cgst_medium_tcp4/1,
+ ttest_ssocko_cgst_medium_tcp6/1,
+ ttest_ssocko_cgst_large_tcp4/1,
+ ttest_ssocko_cgst_large_tcp6/1,
+
%% Server: transport = socket(tcp), active = once
%% Client: transport = socket(tcp)
ttest_ssocko_csockf_small_tcp4/1,
@@ -384,6 +686,29 @@
ttest_ssockt_cgent_large_tcp4/1,
ttest_ssockt_cgent_large_tcp6/1,
+ %% Server: transport = socket(tcp), active = true
+ %% Client: transport = gen_tcp(socket)
+ ttest_ssockt_cgsf_small_tcp4/1,
+ ttest_ssockt_cgsf_small_tcp6/1,
+ ttest_ssockt_cgsf_medium_tcp4/1,
+ ttest_ssockt_cgsf_medium_tcp6/1,
+ ttest_ssockt_cgsf_large_tcp4/1,
+ ttest_ssockt_cgsf_large_tcp6/1,
+
+ ttest_ssockt_cgso_small_tcp4/1,
+ ttest_ssockt_cgso_small_tcp6/1,
+ ttest_ssockt_cgso_medium_tcp4/1,
+ ttest_ssockt_cgso_medium_tcp6/1,
+ ttest_ssockt_cgso_large_tcp4/1,
+ ttest_ssockt_cgso_large_tcp6/1,
+
+ ttest_ssockt_cgst_small_tcp4/1,
+ ttest_ssockt_cgst_small_tcp6/1,
+ ttest_ssockt_cgst_medium_tcp4/1,
+ ttest_ssockt_cgst_medium_tcp6/1,
+ ttest_ssockt_cgst_large_tcp4/1,
+ ttest_ssockt_cgst_large_tcp6/1,
+
%% Server: transport = socket(tcp), active = true
%% Client: transport = socket(tcp)
ttest_ssockt_csockf_small_tcp4/1,
@@ -460,6 +785,19 @@
1
end).
+-define(TTEST_TCP(C, D, ST, SA, CT, CA, MSZ, MO),
+ ttest_tcp(?FUNCTION_NAME, which_ttest_runtime((C)),
+ (D), (ST), (SA), (CT), (CA), (MSZ), (MO))).
+-define(TTEST_TCP_SMALL(C, D, ST, SA, CT, CA),
+ ?TTEST_TCP((C), (D), (ST), (SA), (CT), (CA),
+ 1, ttest_small_max_outstanding((C)))).
+-define(TTEST_TCP_MEDIUM(C, D, ST, SA, CT, CA),
+ ?TTEST_TCP((C), (D), (ST), (SA), (CT), (CA),
+ 2, ttest_medium_max_outstanding((C)))).
+-define(TTEST_TCP_LARGE(C, D, ST, SA, CT, CA),
+ ?TTEST_TCP((C), (D), (ST), (SA), (CT), (CA),
+ 3, ttest_large_max_outstanding((C)))).
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -469,29 +807,6 @@ suite() ->
all() ->
[{group, standard}].
- %% Groups = [{ttest, "ESOCK_TEST_TTEST", include}],
- %% [use_group(Group, Env, Default) || {Group, Env, Default} <- Groups].
-
-%% use_group(_Group, undefined, exclude) ->
-%% [];
-%% use_group(Group, undefined, _Default) ->
-%% [{group, Group}];
-%% use_group(Group, Env, Default) ->
-%% case os:getenv(Env) of
-%% false when (Default =:= include) ->
-%% [{group, Group}];
-%% false ->
-%% [];
-%% Val ->
-%% case list_to_atom(string:to_lower(Val)) of
-%% Use when (Use =:= include) orelse
-%% (Use =:= enable) orelse
-%% (Use =:= true) ->
-%% [{group, Group}];
-%% _ ->
-%% []
-%% end
-%% end.
groups() ->
@@ -503,18 +818,23 @@ groups() ->
{ttest_sgenf_cgenf, [], ttest_sgenf_cgenf_cases()},
{ttest_sgenf_cgeno, [], ttest_sgenf_cgeno_cases()},
{ttest_sgenf_cgent, [], ttest_sgenf_cgent_cases()},
+ {ttest_sgenf_cgs, [], ttest_sgenf_cgs_cases()},
+ {ttest_sgenf_cgsf, [], ttest_sgenf_cgsf_cases()},
+ {ttest_sgenf_cgso, [], ttest_sgenf_cgso_cases()},
+ {ttest_sgenf_cgst, [], ttest_sgenf_cgst_cases()},
{ttest_sgenf_csock, [], ttest_sgenf_csock_cases()},
{ttest_sgenf_csockf, [], ttest_sgenf_csockf_cases()},
{ttest_sgenf_csocko, [], ttest_sgenf_csocko_cases()},
{ttest_sgenf_csockt, [], ttest_sgenf_csockt_cases()},
- {ttest_sgsf, [], ttest_sgsf_cases()},
- {ttest_sgsf_csock, [], ttest_sgsf_csock_cases()},
- {ttest_sgsf_csockf, [], ttest_sgsf_csockf_cases()},
{ttest_sgeno, [], ttest_sgeno_cases()},
{ttest_sgeno_cgen, [], ttest_sgeno_cgen_cases()},
{ttest_sgeno_cgenf, [], ttest_sgeno_cgenf_cases()},
{ttest_sgeno_cgeno, [], ttest_sgeno_cgeno_cases()},
{ttest_sgeno_cgent, [], ttest_sgeno_cgent_cases()},
+ {ttest_sgeno_cgs, [], ttest_sgeno_cgs_cases()},
+ {ttest_sgeno_cgsf, [], ttest_sgeno_cgsf_cases()},
+ {ttest_sgeno_cgso, [], ttest_sgeno_cgso_cases()},
+ {ttest_sgeno_cgst, [], ttest_sgeno_cgst_cases()},
{ttest_sgeno_csock, [], ttest_sgeno_csock_cases()},
{ttest_sgeno_csockf, [], ttest_sgeno_csockf_cases()},
{ttest_sgeno_csocko, [], ttest_sgeno_csocko_cases()},
@@ -524,10 +844,55 @@ groups() ->
{ttest_sgent_cgenf, [], ttest_sgent_cgenf_cases()},
{ttest_sgent_cgeno, [], ttest_sgent_cgeno_cases()},
{ttest_sgent_cgent, [], ttest_sgent_cgent_cases()},
+ {ttest_sgent_cgs, [], ttest_sgent_cgs_cases()},
+ {ttest_sgent_cgsf, [], ttest_sgent_cgsf_cases()},
+ {ttest_sgent_cgso, [], ttest_sgent_cgso_cases()},
+ {ttest_sgent_cgst, [], ttest_sgent_cgst_cases()},
{ttest_sgent_csock, [], ttest_sgent_csock_cases()},
{ttest_sgent_csockf, [], ttest_sgent_csockf_cases()},
{ttest_sgent_csocko, [], ttest_sgent_csocko_cases()},
{ttest_sgent_csockt, [], ttest_sgent_csockt_cases()},
+
+ {ttest_sgsf, [], ttest_sgsf_cases()},
+ {ttest_sgsf_cgen, [], ttest_sgsf_cgen_cases()},
+ {ttest_sgsf_cgenf, [], ttest_sgsf_cgenf_cases()},
+ {ttest_sgsf_cgeno, [], ttest_sgsf_cgeno_cases()},
+ {ttest_sgsf_cgent, [], ttest_sgsf_cgent_cases()},
+ {ttest_sgsf_cgs, [], ttest_sgsf_cgs_cases()},
+ {ttest_sgsf_cgsf, [], ttest_sgsf_cgsf_cases()},
+ {ttest_sgsf_cgso, [], ttest_sgsf_cgso_cases()},
+ {ttest_sgsf_cgst, [], ttest_sgsf_cgst_cases()},
+ {ttest_sgsf_csock, [], ttest_sgsf_csock_cases()},
+ {ttest_sgsf_csockf, [], ttest_sgsf_csockf_cases()},
+ {ttest_sgsf_csocko, [], ttest_sgsf_csocko_cases()},
+ {ttest_sgsf_csockt, [], ttest_sgsf_csockt_cases()},
+ {ttest_sgso, [], ttest_sgso_cases()},
+ {ttest_sgso_cgen, [], ttest_sgso_cgen_cases()},
+ {ttest_sgso_cgenf, [], ttest_sgso_cgenf_cases()},
+ {ttest_sgso_cgeno, [], ttest_sgso_cgeno_cases()},
+ {ttest_sgso_cgent, [], ttest_sgso_cgent_cases()},
+ {ttest_sgso_cgs, [], ttest_sgso_cgs_cases()},
+ {ttest_sgso_cgsf, [], ttest_sgso_cgsf_cases()},
+ {ttest_sgso_cgso, [], ttest_sgso_cgso_cases()},
+ {ttest_sgso_cgst, [], ttest_sgso_cgst_cases()},
+ {ttest_sgso_csock, [], ttest_sgso_csock_cases()},
+ {ttest_sgso_csockf, [], ttest_sgso_csockf_cases()},
+ {ttest_sgso_csocko, [], ttest_sgso_csocko_cases()},
+ {ttest_sgso_csockt, [], ttest_sgso_csockt_cases()},
+ {ttest_sgst, [], ttest_sgst_cases()},
+ {ttest_sgst_cgen, [], ttest_sgst_cgen_cases()},
+ {ttest_sgst_cgenf, [], ttest_sgst_cgenf_cases()},
+ {ttest_sgst_cgeno, [], ttest_sgst_cgeno_cases()},
+ {ttest_sgst_cgent, [], ttest_sgst_cgent_cases()},
+ {ttest_sgst_cgs, [], ttest_sgst_cgs_cases()},
+ {ttest_sgst_cgsf, [], ttest_sgst_cgsf_cases()},
+ {ttest_sgst_cgso, [], ttest_sgst_cgso_cases()},
+ {ttest_sgst_cgst, [], ttest_sgst_cgst_cases()},
+ {ttest_sgst_csock, [], ttest_sgst_csock_cases()},
+ {ttest_sgst_csockf, [], ttest_sgst_csockf_cases()},
+ {ttest_sgst_csocko, [], ttest_sgst_csocko_cases()},
+ {ttest_sgst_csockt, [], ttest_sgst_csockt_cases()},
+
{ttest_ssockf, [], ttest_ssockf_cases()},
{ttest_ssockf_cgen, [], ttest_ssockf_cgen_cases()},
{ttest_ssockf_cgenf, [], ttest_ssockf_cgenf_cases()},
@@ -535,6 +900,8 @@ groups() ->
{ttest_ssockf_cgent, [], ttest_ssockf_cgent_cases()},
{ttest_ssockf_cgs, [], ttest_ssockf_cgs_cases()},
{ttest_ssockf_cgsf, [], ttest_ssockf_cgsf_cases()},
+ {ttest_ssockf_cgso, [], ttest_ssockf_cgso_cases()},
+ {ttest_ssockf_cgst, [], ttest_ssockf_cgst_cases()},
{ttest_ssockf_csock, [], ttest_ssockf_csock_cases()},
{ttest_ssockf_csockf, [], ttest_ssockf_csockf_cases()},
{ttest_ssockf_csocko, [], ttest_ssockf_csocko_cases()},
@@ -544,6 +911,10 @@ groups() ->
{ttest_ssocko_cgenf, [], ttest_ssocko_cgenf_cases()},
{ttest_ssocko_cgeno, [], ttest_ssocko_cgeno_cases()},
{ttest_ssocko_cgent, [], ttest_ssocko_cgent_cases()},
+ {ttest_ssocko_cgs, [], ttest_ssocko_cgs_cases()},
+ {ttest_ssocko_cgsf, [], ttest_ssocko_cgsf_cases()},
+ {ttest_ssocko_cgso, [], ttest_ssocko_cgso_cases()},
+ {ttest_ssocko_cgst, [], ttest_ssocko_cgst_cases()},
{ttest_ssocko_csock, [], ttest_ssocko_csock_cases()},
{ttest_ssocko_csockf, [], ttest_ssocko_csockf_cases()},
{ttest_ssocko_csocko, [], ttest_ssocko_csocko_cases()},
@@ -553,6 +924,10 @@ groups() ->
{ttest_ssockt_cgenf, [], ttest_ssockt_cgenf_cases()},
{ttest_ssockt_cgeno, [], ttest_ssockt_cgeno_cases()},
{ttest_ssockt_cgent, [], ttest_ssockt_cgent_cases()},
+ {ttest_ssockt_cgs, [], ttest_ssockt_cgs_cases()},
+ {ttest_ssockt_cgsf, [], ttest_ssockt_cgsf_cases()},
+ {ttest_ssockt_cgso, [], ttest_ssockt_cgso_cases()},
+ {ttest_ssockt_cgst, [], ttest_ssockt_cgst_cases()},
{ttest_ssockt_csock, [], ttest_ssockt_csock_cases()},
{ttest_ssockt_csockf, [], ttest_ssockt_csockf_cases()},
{ttest_ssockt_csocko, [], ttest_ssockt_csocko_cases()},
@@ -572,12 +947,25 @@ ttest_condition(Config) ->
Factor when (OsType =:= ?WINDOWS) andalso
is_integer(Factor) andalso
(Factor =< ?TTEST_MIN_FACTOR_WIN) ->
+ ?P("~w -> (win) passed", [?FUNCTION_NAME]),
ok;
Factor when is_integer(Factor) andalso (Factor =< ?TTEST_MIN_FACTOR) ->
+ ?P("~w -> passed", [?FUNCTION_NAME]),
ok;
Factor when is_integer(Factor) ->
- {skip, ?F("Too slow for TTest (~w)", [Factor])};
+ ?P("~w -> ~w => check special condition", [?FUNCTION_NAME, Factor]),
+ case ?TTEST_CONDITION() of
+ infinity ->
+ ?P("~w -> unlimited", [?FUNCTION_NAME]),
+ ok;
+ F when is_integer(F) andalso (F > Factor) ->
+ ?P("~w -> ~w > ~w", [?FUNCTION_NAME, F, Factor]),
+ ok;
+ _ ->
+ {skip, ?F("Too slow for TTest (~w)", [Factor])}
+ end;
_ ->
+ ?P("~w -> undefined", [?FUNCTION_NAME]),
{skip, "Too slow for TTest (undef)"}
end.
@@ -662,6 +1050,12 @@ ttest_cases() ->
%% Server: transport = gen_tcp(socket), active = false
{group, ttest_sgsf},
+ %% Server: transport = gen_tcp(socket), active = once
+ {group, ttest_sgso},
+
+ %% Server: transport = gen_tcp(socket), active = true
+ {group, ttest_sgst},
+
%% Server: transport = socket(tcp), active = false
{group, ttest_ssockf},
@@ -677,32 +1071,6 @@ ttest_cases() ->
].
-%% Server: transport = gen_tcp, active = false
-ttest_sgenf_cases() ->
- [
- {group, ttest_sgenf_cgen},
- {group, ttest_sgenf_csock}
- ].
-
-%% Server: transport = gen_tcp, active = false
-%% Client: transport = gen_tcp
-ttest_sgenf_cgen_cases() ->
- [
- {group, ttest_sgenf_cgenf},
- {group, ttest_sgenf_cgeno},
- {group, ttest_sgenf_cgent}
- ].
-
-%% Server: transport = gen_tcp(socket), active = false
-ttest_sgsf_cases() ->
- [
- %% {group, ttest_sgenf_cgen},
- {group, ttest_sgsf_csock}
- ].
-
-%% Server: transport = gen_tcp, active = false
-%% Client: transport = gen_tcp, active = false
-
ttest_conditional_cases(Env, Default, Cases) ->
case os:getenv(Env) of
false ->
@@ -732,6 +1100,26 @@ ttest_select_conditional_cases(Small, Medium, Large) ->
ttest_medium_conditional_cases(Medium) ++
ttest_large_conditional_cases(Large).
+
+%% Server: transport = gen_tcp, active = false
+ttest_sgenf_cases() ->
+ [
+ {group, ttest_sgenf_cgen},
+ {group, ttest_sgenf_cgs},
+ {group, ttest_sgenf_csock}
+ ].
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp
+ttest_sgenf_cgen_cases() ->
+ [
+ {group, ttest_sgenf_cgenf},
+ {group, ttest_sgenf_cgeno},
+ {group, ttest_sgenf_cgent}
+ ].
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp, active = false
ttest_sgenf_cgenf_cases() ->
ttest_select_conditional_cases(
%% Small
@@ -772,6 +1160,58 @@ ttest_sgenf_cgent_cases() ->
[ttest_sgenf_cgent_large_tcp4,
ttest_sgenf_cgent_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp(socket)
+ttest_sgenf_cgs_cases() ->
+ [
+ {group, ttest_sgenf_cgsf},
+ {group, ttest_sgenf_cgso},
+ {group, ttest_sgenf_cgst}
+ ].
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp(socket), active = once
+ttest_sgenf_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgenf_cgsf_small_tcp4,
+ ttest_sgenf_cgsf_small_tcp6],
+ %% Medium
+ [ttest_sgenf_cgsf_medium_tcp4,
+ ttest_sgenf_cgsf_medium_tcp6],
+ %% Large
+ [ttest_sgenf_cgsf_large_tcp4,
+ ttest_sgenf_cgsf_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp(socket), active = once
+ttest_sgenf_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgenf_cgso_small_tcp4,
+ ttest_sgenf_cgso_small_tcp6],
+ %% Medium
+ [ttest_sgenf_cgso_medium_tcp4,
+ ttest_sgenf_cgso_medium_tcp6],
+ %% Large
+ [ttest_sgenf_cgso_large_tcp4,
+ ttest_sgenf_cgso_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = false
+%% Client: transport = gen_tcp(socket), active = true
+ttest_sgenf_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgenf_cgst_small_tcp4,
+ ttest_sgenf_cgst_small_tcp6],
+ %% Medium
+ [ttest_sgenf_cgst_medium_tcp4,
+ ttest_sgenf_cgst_medium_tcp6],
+ %% Large
+ [ttest_sgenf_cgst_large_tcp4,
+ ttest_sgenf_cgst_large_tcp6]).
+
%% Server: transport = gen_tcp, active = false
%% Client: transport = socket(tcp)
ttest_sgenf_csock_cases() ->
@@ -817,3075 +1257,7601 @@ ttest_sgenf_csockt_cases() ->
[ttest_sgenf_csockt_large_tcp4,
ttest_sgenf_csockt_large_tcp6]).
+
%% Server: transport = gen_tcp(socket), active = false
-%% Client: transport = socket(tcp)
-ttest_sgsf_csock_cases() ->
+ttest_sgsf_cases() ->
[
- {group, ttest_sgsf_csockf}%% ,
- %% {group, ttest_sgsf_csocko},
- %% {group, ttest_sgsf_csockt}
+ {group, ttest_sgsf_cgen},
+ {group, ttest_sgsf_cgs},
+ {group, ttest_sgsf_csock}
].
-ttest_sgsf_csockf_cases() ->
+%% Server: transport = gen_tcp(socket), active = false
+%% Client: transport = gen_tcp
+ttest_sgsf_cgen_cases() ->
+ [
+ {group, ttest_sgsf_cgenf},
+ {group, ttest_sgsf_cgeno},
+ {group, ttest_sgsf_cgent}
+ ].
+
+ttest_sgsf_cgenf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgsf_csockf_small_tcp4,
- ttest_sgsf_csockf_small_tcp6],
+ [ttest_sgsf_cgenf_small_tcp4,
+ ttest_sgsf_cgenf_small_tcp6],
%% Medium
- [ttest_sgsf_csockf_medium_tcp4,
- ttest_sgsf_csockf_medium_tcp6],
+ [ttest_sgsf_cgenf_medium_tcp4,
+ ttest_sgsf_cgenf_medium_tcp6],
%% Large
- [ttest_sgsf_csockf_large_tcp4,
- ttest_sgsf_csockf_large_tcp6]).
+ [ttest_sgsf_cgenf_large_tcp4,
+ ttest_sgsf_cgenf_large_tcp6]).
-%% Server: transport = gen_tcp, active = once
-ttest_sgeno_cases() ->
- [
- {group, ttest_sgeno_cgen},
- {group, ttest_sgeno_csock}
- ].
+ttest_sgsf_cgeno_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgsf_cgeno_small_tcp4,
+ ttest_sgsf_cgeno_small_tcp6],
+ %% Medium
+ [ttest_sgsf_cgeno_medium_tcp4,
+ ttest_sgsf_cgeno_medium_tcp6],
+ %% Large
+ [ttest_sgsf_cgeno_large_tcp4,
+ ttest_sgsf_cgeno_large_tcp6]).
-%% Server: transport = gen_tcp, active = once
-%% Client: transport = gen_tcp
-ttest_sgeno_cgen_cases() ->
+ttest_sgsf_cgent_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgsf_cgent_small_tcp4,
+ ttest_sgsf_cgent_small_tcp6],
+ %% Medium
+ [ttest_sgsf_cgent_medium_tcp4,
+ ttest_sgsf_cgent_medium_tcp6],
+ %% Large
+ [ttest_sgsf_cgent_large_tcp4,
+ ttest_sgsf_cgent_large_tcp6]).
+
+%% Server: transport = gen_tcp(socket), active = false
+%% Client: transport = gen_tcp(socket)
+ttest_sgsf_cgs_cases() ->
[
- {group, ttest_sgeno_cgenf},
- {group, ttest_sgeno_cgeno},
- {group, ttest_sgeno_cgent}
+ {group, ttest_sgsf_cgsf},
+ {group, ttest_sgsf_cgso},
+ {group, ttest_sgsf_cgst}
].
-%% Server: transport = gen_tcp, active = once
-%% Client: transport = gen_tcp, active = false
-ttest_sgeno_cgenf_cases() ->
+ttest_sgsf_cgsf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_cgenf_small_tcp4,
- ttest_sgeno_cgenf_small_tcp6],
+ [ttest_sgsf_cgsf_small_tcp4,
+ ttest_sgsf_cgsf_small_tcp6],
%% Medium
- [ttest_sgeno_cgenf_medium_tcp4,
- ttest_sgeno_cgenf_medium_tcp6],
+ [ttest_sgsf_cgsf_medium_tcp4,
+ ttest_sgsf_cgsf_medium_tcp6],
%% Large
- [ttest_sgeno_cgenf_large_tcp4,
- ttest_sgeno_cgenf_large_tcp6]).
+ [ttest_sgsf_cgsf_large_tcp4,
+ ttest_sgsf_cgsf_large_tcp6]).
-%% Server: transport = gen_tcp, active = once
-%% Client: transport = gen_tcp, active = once
-ttest_sgeno_cgeno_cases() ->
+ttest_sgsf_cgso_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_cgeno_small_tcp4,
- ttest_sgeno_cgeno_small_tcp6],
+ [ttest_sgsf_cgso_small_tcp4,
+ ttest_sgsf_cgso_small_tcp6],
%% Medium
- [ttest_sgeno_cgeno_medium_tcp4,
- ttest_sgeno_cgeno_medium_tcp6],
+ [ttest_sgsf_cgso_medium_tcp4,
+ ttest_sgsf_cgso_medium_tcp6],
%% Large
- [ttest_sgeno_cgeno_large_tcp4,
- ttest_sgeno_cgeno_large_tcp6]).
+ [ttest_sgsf_cgso_large_tcp4,
+ ttest_sgsf_cgso_large_tcp6]).
-%% Server: transport = gen_tcp, active = once
-%% Client: transport = gen_tcp, active = true
-ttest_sgeno_cgent_cases() ->
+ttest_sgsf_cgst_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_cgent_small_tcp4,
- ttest_sgeno_cgent_small_tcp6],
+ [ttest_sgsf_cgst_small_tcp4,
+ ttest_sgsf_cgst_small_tcp6],
%% Medium
- [ttest_sgeno_cgent_medium_tcp4,
- ttest_sgeno_cgent_medium_tcp6],
+ [ttest_sgsf_cgst_medium_tcp4,
+ ttest_sgsf_cgst_medium_tcp6],
%% Large
- [ttest_sgeno_cgent_large_tcp4,
- ttest_sgeno_cgent_large_tcp6]).
+ [ttest_sgsf_cgst_large_tcp4,
+ ttest_sgsf_cgst_large_tcp6]).
-%% Server: transport = gen_tcp, active = once
+%% Server: transport = gen_tcp(socket), active = false
%% Client: transport = socket(tcp)
-ttest_sgeno_csock_cases() ->
+ttest_sgsf_csock_cases() ->
[
- {group, ttest_sgeno_csockf},
- {group, ttest_sgeno_csocko},
- {group, ttest_sgeno_csockt}
+ {group, ttest_sgsf_csockf},
+ {group, ttest_sgsf_csocko},
+ {group, ttest_sgsf_csockt}
].
-ttest_sgeno_csockf_cases() ->
+ttest_sgsf_csockf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_csockf_small_tcp4,
- ttest_sgeno_csockf_small_tcp6],
+ [ttest_sgsf_csockf_small_tcp4,
+ ttest_sgsf_csockf_small_tcp6],
%% Medium
- [ttest_sgeno_csockf_medium_tcp4,
- ttest_sgeno_csockf_medium_tcp6],
+ [ttest_sgsf_csockf_medium_tcp4,
+ ttest_sgsf_csockf_medium_tcp6],
%% Large
- [ttest_sgeno_csockf_large_tcp4,
- ttest_sgeno_csockf_large_tcp6]).
+ [ttest_sgsf_csockf_large_tcp4,
+ ttest_sgsf_csockf_large_tcp6]).
-ttest_sgeno_csocko_cases() ->
+ttest_sgsf_csocko_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_csocko_small_tcp4,
- ttest_sgeno_csocko_small_tcp6],
+ [ttest_sgsf_csocko_small_tcp4,
+ ttest_sgsf_csocko_small_tcp6],
%% Medium
- [ttest_sgeno_csocko_medium_tcp4,
- ttest_sgeno_csocko_medium_tcp6],
+ [ttest_sgsf_csocko_medium_tcp4,
+ ttest_sgsf_csocko_medium_tcp6],
%% Large
- [ttest_sgeno_csocko_large_tcp4,
- ttest_sgeno_csocko_large_tcp6]).
+ [ttest_sgsf_csocko_large_tcp4,
+ ttest_sgsf_csocko_large_tcp6]).
-ttest_sgeno_csockt_cases() ->
+ttest_sgsf_csockt_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgeno_csockt_small_tcp4,
- ttest_sgeno_csockt_small_tcp6],
+ [ttest_sgsf_csockt_small_tcp4,
+ ttest_sgsf_csockt_small_tcp6],
%% Medium
- [ttest_sgeno_csockt_medium_tcp4,
- ttest_sgeno_csockt_medium_tcp6],
+ [ttest_sgsf_csockt_medium_tcp4,
+ ttest_sgsf_csockt_medium_tcp6],
%% Large
- [ttest_sgeno_csockt_large_tcp4,
- ttest_sgeno_csockt_large_tcp6]).
+ [ttest_sgsf_csockt_large_tcp4,
+ ttest_sgsf_csockt_large_tcp6]).
-%% Server: transport = gen_tcp, active = true
-ttest_sgent_cases() ->
+%% Server: transport = gen_tcp(socket), active = once
+ttest_sgso_cases() ->
[
- {group, ttest_sgent_cgen},
- {group, ttest_sgent_csock}
+ {group, ttest_sgso_cgen},
+ {group, ttest_sgso_cgs},
+ {group, ttest_sgso_csock}
].
-%% Server: transport = gen_tcp, active = true
+%% Server: transport = gen_tcp(socket), active = once
%% Client: transport = gen_tcp
-ttest_sgent_cgen_cases() ->
+ttest_sgso_cgen_cases() ->
[
- {group, ttest_sgent_cgenf},
- {group, ttest_sgent_cgeno},
- {group, ttest_sgent_cgent}
+ {group, ttest_sgso_cgenf},
+ {group, ttest_sgso_cgeno},
+ {group, ttest_sgso_cgent}
].
-%% Server: transport = gen_tcp, active = true
-%% Client: transport = gen_tcp, active = false
-ttest_sgent_cgenf_cases() ->
+ttest_sgso_cgenf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_cgenf_small_tcp4,
- ttest_sgent_cgenf_small_tcp6],
+ [ttest_sgso_cgenf_small_tcp4,
+ ttest_sgso_cgenf_small_tcp6],
%% Medium
- [ttest_sgent_cgenf_medium_tcp4,
- ttest_sgent_cgenf_medium_tcp6],
+ [ttest_sgso_cgenf_medium_tcp4,
+ ttest_sgso_cgenf_medium_tcp6],
%% Large
- [ttest_sgent_cgenf_large_tcp4,
- ttest_sgent_cgenf_large_tcp6]).
+ [ttest_sgso_cgenf_large_tcp4,
+ ttest_sgso_cgenf_large_tcp6]).
-%% Server: transport = gen_tcp, active = true
-%% Client: transport = gen_tcp, active = once
-ttest_sgent_cgeno_cases() ->
+ttest_sgso_cgeno_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_cgeno_small_tcp4,
- ttest_sgent_cgeno_small_tcp6],
+ [ttest_sgso_cgeno_small_tcp4,
+ ttest_sgso_cgeno_small_tcp6],
%% Medium
- [ttest_sgent_cgeno_medium_tcp4,
- ttest_sgent_cgeno_medium_tcp6],
+ [ttest_sgso_cgeno_medium_tcp4,
+ ttest_sgso_cgeno_medium_tcp6],
%% Large
- [ttest_sgent_cgeno_large_tcp4,
- ttest_sgent_cgeno_large_tcp6]).
+ [ttest_sgso_cgeno_large_tcp4,
+ ttest_sgso_cgeno_large_tcp6]).
-%% Server: transport = gen_tcp, active = true
-%% Client: transport = gen_tcp, active = true
-ttest_sgent_cgent_cases() ->
+ttest_sgso_cgent_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_cgent_small_tcp4,
- ttest_sgent_cgent_small_tcp6],
+ [ttest_sgso_cgent_small_tcp4,
+ ttest_sgso_cgent_small_tcp6],
%% Medium
- [ttest_sgent_cgent_medium_tcp4,
- ttest_sgent_cgent_medium_tcp6],
+ [ttest_sgso_cgent_medium_tcp4,
+ ttest_sgso_cgent_medium_tcp6],
%% Large
- [ttest_sgent_cgent_large_tcp4,
- ttest_sgent_cgent_large_tcp6]).
+ [ttest_sgso_cgent_large_tcp4,
+ ttest_sgso_cgent_large_tcp6]).
-%% Server: transport = gen_tcp, active = true
-%% Client: transport = socket(tcp)
-ttest_sgent_csock_cases() ->
+%% Server: transport = gen_tcp(socket), active = once
+%% Client: transport = gen_tcp(socket)
+ttest_sgso_cgs_cases() ->
[
- {group, ttest_sgent_csockf},
- {group, ttest_sgent_csocko},
- {group, ttest_sgent_csockt}
+ {group, ttest_sgso_cgsf},
+ {group, ttest_sgso_cgso},
+ {group, ttest_sgso_cgst}
].
-ttest_sgent_csockf_cases() ->
+ttest_sgso_cgsf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_csockf_small_tcp4,
- ttest_sgent_csockf_small_tcp6],
+ [ttest_sgso_cgsf_small_tcp4,
+ ttest_sgso_cgsf_small_tcp6],
%% Medium
- [ttest_sgent_csockf_medium_tcp4,
- ttest_sgent_csockf_medium_tcp6],
+ [ttest_sgso_cgsf_medium_tcp4,
+ ttest_sgso_cgsf_medium_tcp6],
%% Large
- [ttest_sgent_csockf_large_tcp4,
- ttest_sgent_csockf_large_tcp6]).
+ [ttest_sgso_cgsf_large_tcp4,
+ ttest_sgso_cgsf_large_tcp6]).
-ttest_sgent_csocko_cases() ->
+ttest_sgso_cgso_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_csocko_small_tcp4,
- ttest_sgent_csocko_small_tcp6],
+ [ttest_sgso_cgso_small_tcp4,
+ ttest_sgso_cgso_small_tcp6],
%% Medium
- [ttest_sgent_csocko_medium_tcp4,
- ttest_sgent_csocko_medium_tcp6],
+ [ttest_sgso_cgso_medium_tcp4,
+ ttest_sgso_cgso_medium_tcp6],
%% Large
- [ttest_sgent_csocko_large_tcp4,
- ttest_sgent_csocko_large_tcp6]).
+ [ttest_sgso_cgso_large_tcp4,
+ ttest_sgso_cgso_large_tcp6]).
-ttest_sgent_csockt_cases() ->
+ttest_sgso_cgst_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_sgent_csockt_small_tcp4,
- ttest_sgent_csockt_small_tcp6],
+ [ttest_sgso_cgst_small_tcp4,
+ ttest_sgso_cgst_small_tcp6],
%% Medium
- [ttest_sgent_csockt_medium_tcp4,
- ttest_sgent_csockt_medium_tcp6],
+ [ttest_sgso_cgst_medium_tcp4,
+ ttest_sgso_cgst_medium_tcp6],
%% Large
- [ttest_sgent_csockt_large_tcp4,
- ttest_sgent_csockt_large_tcp6]).
-
-%% Server: transport = socket(tcp), active = false
-ttest_ssockf_cases() ->
- [
- {group, ttest_ssockf_cgen},
- {group, ttest_ssockf_csock},
- {group, ttest_ssockf_cgsf}
- ].
+ [ttest_sgso_cgst_large_tcp4,
+ ttest_sgso_cgst_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp
-ttest_ssockf_cgen_cases() ->
+%% Server: transport = gen_tcp(socket), active = once
+%% Client: transport = socket(tcp)
+ttest_sgso_csock_cases() ->
[
- {group, ttest_ssockf_cgenf},
- {group, ttest_ssockf_cgeno},
- {group, ttest_ssockf_cgent}
+ {group, ttest_sgso_csockf},
+ {group, ttest_sgso_csocko},
+ {group, ttest_sgso_csockt}
].
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp, active = false
-ttest_ssockf_cgenf_cases() ->
+ttest_sgso_csockf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_cgenf_small_tcp4,
- ttest_ssockf_cgenf_small_tcp6],
+ [ttest_sgso_csockf_small_tcp4,
+ ttest_sgso_csockf_small_tcp6],
%% Medium
- [ttest_ssockf_cgenf_medium_tcp4,
- ttest_ssockf_cgenf_medium_tcp6],
+ [ttest_sgso_csockf_medium_tcp4,
+ ttest_sgso_csockf_medium_tcp6],
%% Large
- [ttest_ssockf_cgenf_large_tcp4,
- ttest_ssockf_cgenf_large_tcp6]).
+ [ttest_sgso_csockf_large_tcp4,
+ ttest_sgso_csockf_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp, active = once
-ttest_ssockf_cgeno_cases() ->
+ttest_sgso_csocko_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_cgeno_small_tcp4,
- ttest_ssockf_cgeno_small_tcp6],
+ [ttest_sgso_csocko_small_tcp4,
+ ttest_sgso_csocko_small_tcp6],
%% Medium
- [ttest_ssockf_cgeno_medium_tcp4,
- ttest_ssockf_cgeno_medium_tcp6],
+ [ttest_sgso_csocko_medium_tcp4,
+ ttest_sgso_csocko_medium_tcp6],
%% Large
- [ttest_ssockf_cgeno_large_tcp4,
- ttest_ssockf_cgeno_large_tcp6]).
+ [ttest_sgso_csocko_large_tcp4,
+ ttest_sgso_csocko_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp, active = true
-ttest_ssockf_cgent_cases() ->
+ttest_sgso_csockt_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_cgent_small_tcp4,
- ttest_ssockf_cgent_small_tcp6],
+ [ttest_sgso_csockt_small_tcp4,
+ ttest_sgso_csockt_small_tcp6],
%% Medium
- [ttest_ssockf_cgent_medium_tcp4,
- ttest_ssockf_cgent_medium_tcp6],
+ [ttest_sgso_csockt_medium_tcp4,
+ ttest_sgso_csockt_medium_tcp6],
%% Large
- [ttest_ssockf_cgent_large_tcp4,
- ttest_ssockf_cgent_large_tcp6]).
+ [ttest_sgso_csockt_large_tcp4,
+ ttest_sgso_csockt_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp(socket)
-ttest_ssockf_cgs_cases() ->
+%% Server: transport = gen_tcp(socket), active = true
+ttest_sgst_cases() ->
[
- {group, ttest_ssockf_cgsf}%% ,
- %% {group, ttest_ssockf_cgeno},
- %% {group, ttest_ssockf_cgent}
+ {group, ttest_sgst_cgen},
+ {group, ttest_sgst_cgs},
+ {group, ttest_sgst_csock}
].
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = gen_tcp(socket), active = false
-ttest_ssockf_cgsf_cases() ->
- ttest_select_conditional_cases(
- %% Small
- [ttest_ssockf_cgsf_small_tcp4,
- ttest_ssockf_cgsf_small_tcp6],
- %% Medium
- [ttest_ssockf_cgsf_medium_tcp4,
- ttest_ssockf_cgsf_medium_tcp6],
- %% Large
- [ttest_ssockf_cgsf_large_tcp4,
- ttest_ssockf_cgsf_large_tcp6]).
-
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = socket(tcp)
-ttest_ssockf_csock_cases() ->
+%% Server: transport = gen_tcp(socket), active = true
+%% Client: transport = gen_tcp
+ttest_sgst_cgen_cases() ->
[
- {group, ttest_ssockf_csockf},
- {group, ttest_ssockf_csocko},
- {group, ttest_ssockf_csockt}
+ {group, ttest_sgst_cgenf},
+ {group, ttest_sgst_cgeno},
+ {group, ttest_sgst_cgent}
].
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = socket(tcp), active = false
-ttest_ssockf_csockf_cases() ->
+ttest_sgst_cgenf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_csockf_small_tcp4,
- ttest_ssockf_csockf_small_tcp6,
- ttest_ssockf_csockf_small_tcpL],
+ [ttest_sgst_cgenf_small_tcp4,
+ ttest_sgst_cgenf_small_tcp6],
%% Medium
- [ttest_ssockf_csockf_medium_tcp4,
- ttest_ssockf_csockf_medium_tcp6,
- ttest_ssockf_csockf_medium_tcpL],
+ [ttest_sgst_cgenf_medium_tcp4,
+ ttest_sgst_cgenf_medium_tcp6],
%% Large
- [ttest_ssockf_csockf_large_tcp4,
- ttest_ssockf_csockf_large_tcp6,
- ttest_ssockf_csockf_large_tcpL]).
+ [ttest_sgst_cgenf_large_tcp4,
+ ttest_sgst_cgenf_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = socket(tcp), active = once
-ttest_ssockf_csocko_cases() ->
+ttest_sgst_cgeno_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_csocko_small_tcp4,
- ttest_ssockf_csocko_small_tcp6,
- ttest_ssockf_csocko_small_tcpL],
+ [ttest_sgst_cgeno_small_tcp4,
+ ttest_sgst_cgeno_small_tcp6],
%% Medium
- [ttest_ssockf_csocko_medium_tcp4,
- ttest_ssockf_csocko_medium_tcp6,
- ttest_ssockf_csocko_medium_tcpL],
+ [ttest_sgst_cgeno_medium_tcp4,
+ ttest_sgst_cgeno_medium_tcp6],
%% Large
- [ttest_ssockf_csocko_large_tcp4,
- ttest_ssockf_csocko_large_tcp6,
- ttest_ssockf_csocko_large_tcpL]).
+ [ttest_sgst_cgeno_large_tcp4,
+ ttest_sgst_cgeno_large_tcp6]).
-%% Server: transport = socket(tcp), active = false
-%% Client: transport = socket(tcp), active = true
-ttest_ssockf_csockt_cases() ->
+ttest_sgst_cgent_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockf_csockt_small_tcp4,
- ttest_ssockf_csockt_small_tcp6,
- ttest_ssockf_csockt_small_tcpL],
+ [ttest_sgst_cgent_small_tcp4,
+ ttest_sgst_cgent_small_tcp6],
%% Medium
- [ttest_ssockf_csockt_medium_tcp4,
- ttest_ssockf_csockt_medium_tcp6,
- ttest_ssockf_csockt_medium_tcpL],
+ [ttest_sgst_cgent_medium_tcp4,
+ ttest_sgst_cgent_medium_tcp6],
%% Large
- [ttest_ssockf_csockt_large_tcp4,
- ttest_ssockf_csockt_large_tcp6,
- ttest_ssockf_csockt_large_tcpL]).
+ [ttest_sgst_cgent_large_tcp4,
+ ttest_sgst_cgent_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
-ttest_ssocko_cases() ->
- [
- {group, ttest_ssocko_cgen},
- {group, ttest_ssocko_csock}
- ].
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = gen_tcp
-ttest_ssocko_cgen_cases() ->
+%% Server: transport = gen_tcp(socket), active = true
+%% Client: transport = gen_tcp(socket)
+ttest_sgst_cgs_cases() ->
[
- {group, ttest_ssocko_cgenf},
- {group, ttest_ssocko_cgeno},
- {group, ttest_ssocko_cgent}
+ {group, ttest_sgst_cgsf},
+ {group, ttest_sgst_cgso},
+ {group, ttest_sgst_cgst}
].
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = gen_tcp, active = false
-ttest_ssocko_cgenf_cases() ->
+ttest_sgst_cgsf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_cgenf_small_tcp4,
- ttest_ssocko_cgenf_small_tcp6],
+ [ttest_sgst_cgsf_small_tcp4,
+ ttest_sgst_cgsf_small_tcp6],
%% Medium
- [ttest_ssocko_cgenf_medium_tcp4,
- ttest_ssocko_cgenf_medium_tcp6],
+ [ttest_sgst_cgsf_medium_tcp4,
+ ttest_sgst_cgsf_medium_tcp6],
%% Large
- [ttest_ssocko_cgenf_large_tcp4,
- ttest_ssocko_cgenf_large_tcp6]).
+ [ttest_sgst_cgsf_large_tcp4,
+ ttest_sgst_cgsf_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = gen_tcp, active = once
-ttest_ssocko_cgeno_cases() ->
+ttest_sgst_cgso_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_cgeno_small_tcp4,
- ttest_ssocko_cgeno_small_tcp6],
+ [ttest_sgst_cgso_small_tcp4,
+ ttest_sgst_cgso_small_tcp6],
%% Medium
- [ttest_ssocko_cgeno_medium_tcp4,
- ttest_ssocko_cgeno_medium_tcp6],
+ [ttest_sgst_cgso_medium_tcp4,
+ ttest_sgst_cgso_medium_tcp6],
%% Large
- [ttest_ssocko_cgeno_large_tcp4,
- ttest_ssocko_cgeno_large_tcp6]).
+ [ttest_sgst_cgso_large_tcp4,
+ ttest_sgst_cgso_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = gen_tcp, active = true
-ttest_ssocko_cgent_cases() ->
+ttest_sgst_cgst_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_cgent_small_tcp4,
- ttest_ssocko_cgent_small_tcp6],
+ [ttest_sgst_cgst_small_tcp4,
+ ttest_sgst_cgst_small_tcp6],
%% Medium
- [ttest_ssocko_cgent_medium_tcp4,
- ttest_ssocko_cgent_medium_tcp6],
+ [ttest_sgst_cgst_medium_tcp4,
+ ttest_sgst_cgst_medium_tcp6],
%% Large
- [ttest_ssocko_cgent_large_tcp4,
- ttest_ssocko_cgent_large_tcp6]).
+ [ttest_sgst_cgst_large_tcp4,
+ ttest_sgst_cgst_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
+
+%% Server: transport = gen_tcp(socket), active = true
%% Client: transport = socket(tcp)
-ttest_ssocko_csock_cases() ->
+ttest_sgst_csock_cases() ->
[
- {group, ttest_ssocko_csockf},
- {group, ttest_ssocko_csocko},
- {group, ttest_ssocko_csockt}
+ {group, ttest_sgst_csockf},
+ {group, ttest_sgst_csocko},
+ {group, ttest_sgst_csockt}
].
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = socket(tcp), active = false
-ttest_ssocko_csockf_cases() ->
+ttest_sgst_csockf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_csockf_small_tcp4,
- ttest_ssocko_csockf_small_tcp6,
- ttest_ssocko_csockf_small_tcpL],
- %% Medium
- [ttest_ssocko_csockf_medium_tcp4,
- ttest_ssocko_csockf_medium_tcp6,
- ttest_ssocko_csockf_medium_tcpL],
+ [ttest_sgst_csockf_small_tcp4,
+ ttest_sgst_csockf_small_tcp6],
+ %% Medium
+ [ttest_sgst_csockf_medium_tcp4,
+ ttest_sgst_csockf_medium_tcp6],
%% Large
- [ttest_ssocko_csockf_large_tcp4,
- ttest_ssocko_csockf_large_tcp6,
- ttest_ssocko_csockf_large_tcpL]).
+ [ttest_sgst_csockf_large_tcp4,
+ ttest_sgst_csockf_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = socket(tcp), active = once
-ttest_ssocko_csocko_cases() ->
+ttest_sgst_csocko_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_csocko_small_tcp4,
- ttest_ssocko_csocko_small_tcp6,
- ttest_ssocko_csocko_small_tcpL],
+ [ttest_sgst_csocko_small_tcp4,
+ ttest_sgst_csocko_small_tcp6],
%% Medium
- [ttest_ssocko_csocko_medium_tcp4,
- ttest_ssocko_csocko_medium_tcp6,
- ttest_ssocko_csocko_medium_tcpL],
+ [ttest_sgst_csocko_medium_tcp4,
+ ttest_sgst_csocko_medium_tcp6],
%% Large
- [ttest_ssocko_csocko_large_tcp4,
- ttest_ssocko_csocko_large_tcp6,
- ttest_ssocko_csocko_large_tcpL]).
+ [ttest_sgst_csocko_large_tcp4,
+ ttest_sgst_csocko_large_tcp6]).
-%% Server: transport = socket(tcp), active = once
-%% Client: transport = socket(tcp), active = true
-ttest_ssocko_csockt_cases() ->
+ttest_sgst_csockt_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssocko_csockt_small_tcp4,
- ttest_ssocko_csockt_small_tcp6,
- ttest_ssocko_csockt_small_tcpL],
+ [ttest_sgst_csockt_small_tcp4,
+ ttest_sgst_csockt_small_tcp6],
%% Medium
- [ttest_ssocko_csockt_medium_tcp4,
- ttest_ssocko_csockt_medium_tcp6,
- ttest_ssocko_csockt_medium_tcpL],
+ [ttest_sgst_csockt_medium_tcp4,
+ ttest_sgst_csockt_medium_tcp6],
%% Large
- [ttest_ssocko_csockt_large_tcp4,
- ttest_ssocko_csockt_large_tcp6,
- ttest_ssocko_csockt_large_tcpL]).
+ [ttest_sgst_csockt_large_tcp4,
+ ttest_sgst_csockt_large_tcp6]).
-%% Server: transport = socket(tcp), active = true
-ttest_ssockt_cases() ->
+
+%% Server: transport = gen_tcp, active = once
+ttest_sgeno_cases() ->
[
- {group, ttest_ssockt_cgen},
- {group, ttest_ssockt_csock}
+ {group, ttest_sgeno_cgen},
+ {group, ttest_sgeno_cgs},
+ {group, ttest_sgeno_csock}
].
-%% Server: transport = socket(tcp), active = true
+%% Server: transport = gen_tcp, active = once
%% Client: transport = gen_tcp
-ttest_ssockt_cgen_cases() ->
+ttest_sgeno_cgen_cases() ->
[
- {group, ttest_ssockt_cgenf},
- {group, ttest_ssockt_cgeno},
- {group, ttest_ssockt_cgent}
+ {group, ttest_sgeno_cgenf},
+ {group, ttest_sgeno_cgeno},
+ {group, ttest_sgeno_cgent}
].
-%% Server: transport = socket(tcp), active = true
+%% Server: transport = gen_tcp, active = once
%% Client: transport = gen_tcp, active = false
-ttest_ssockt_cgenf_cases() ->
+ttest_sgeno_cgenf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockt_cgenf_small_tcp4,
- ttest_ssockt_cgenf_small_tcp6],
+ [ttest_sgeno_cgenf_small_tcp4,
+ ttest_sgeno_cgenf_small_tcp6],
%% Medium
- [ttest_ssockt_cgenf_medium_tcp4,
- ttest_ssockt_cgenf_medium_tcp6],
+ [ttest_sgeno_cgenf_medium_tcp4,
+ ttest_sgeno_cgenf_medium_tcp6],
%% Large
- [ttest_ssockt_cgenf_large_tcp4,
- ttest_ssockt_cgenf_large_tcp6]).
+ [ttest_sgeno_cgenf_large_tcp4,
+ ttest_sgeno_cgenf_large_tcp6]).
-%% Server: transport = socket(tcp), active = true
+%% Server: transport = gen_tcp, active = once
%% Client: transport = gen_tcp, active = once
-ttest_ssockt_cgeno_cases() ->
+ttest_sgeno_cgeno_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockt_cgeno_small_tcp4,
- ttest_ssockt_cgeno_small_tcp6],
+ [ttest_sgeno_cgeno_small_tcp4,
+ ttest_sgeno_cgeno_small_tcp6],
%% Medium
- [ttest_ssockt_cgeno_medium_tcp4,
- ttest_ssockt_cgeno_medium_tcp6],
+ [ttest_sgeno_cgeno_medium_tcp4,
+ ttest_sgeno_cgeno_medium_tcp6],
%% Large
- [ttest_ssockt_cgeno_large_tcp4,
- ttest_ssockt_cgeno_large_tcp6]).
+ [ttest_sgeno_cgeno_large_tcp4,
+ ttest_sgeno_cgeno_large_tcp6]).
-%% Server: transport = socket(tcp), active = true
+%% Server: transport = gen_tcp, active = once
%% Client: transport = gen_tcp, active = true
-ttest_ssockt_cgent_cases() ->
+ttest_sgeno_cgent_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockt_cgent_small_tcp4,
- ttest_ssockt_cgent_small_tcp6],
+ [ttest_sgeno_cgent_small_tcp4,
+ ttest_sgeno_cgent_small_tcp6],
%% Medium
- [ttest_ssockt_cgent_medium_tcp4,
- ttest_ssockt_cgent_medium_tcp6],
+ [ttest_sgeno_cgent_medium_tcp4,
+ ttest_sgeno_cgent_medium_tcp6],
%% Large
- [ttest_ssockt_cgent_large_tcp4,
- ttest_ssockt_cgent_large_tcp6]).
+ [ttest_sgeno_cgent_large_tcp4,
+ ttest_sgeno_cgent_large_tcp6]).
-%% Server: transport = socket(tcp), active = true
+%% Server: transport = gen_tcp, active = once
+%% Client: transport = gen_tcp(socket)(
+ttest_sgeno_cgs_cases() ->
+ [
+ {group, ttest_sgeno_cgsf},
+ {group, ttest_sgeno_cgso},
+ {group, ttest_sgeno_cgst}
+ ].
+
+%% Server: transport = gen_tcp, active = once
+%% Client: transport = gen_tcp(socket), active = false
+ttest_sgeno_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgeno_cgsf_small_tcp4,
+ ttest_sgeno_cgsf_small_tcp6],
+ %% Medium
+ [ttest_sgeno_cgsf_medium_tcp4,
+ ttest_sgeno_cgsf_medium_tcp6],
+ %% Large
+ [ttest_sgeno_cgsf_large_tcp4,
+ ttest_sgeno_cgsf_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = once
+%% Client: transport = gen_tcp(socket), active = once
+ttest_sgeno_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgeno_cgso_small_tcp4,
+ ttest_sgeno_cgso_small_tcp6],
+ %% Medium
+ [ttest_sgeno_cgso_medium_tcp4,
+ ttest_sgeno_cgso_medium_tcp6],
+ %% Large
+ [ttest_sgeno_cgso_large_tcp4,
+ ttest_sgeno_cgso_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = once
+%% Client: transport = gen_tcp(socket), active = true
+ttest_sgeno_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgeno_cgst_small_tcp4,
+ ttest_sgeno_cgst_small_tcp6],
+ %% Medium
+ [ttest_sgeno_cgst_medium_tcp4,
+ ttest_sgeno_cgst_medium_tcp6],
+ %% Large
+ [ttest_sgeno_cgst_large_tcp4,
+ ttest_sgeno_cgst_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = once
%% Client: transport = socket(tcp)
-ttest_ssockt_csock_cases() ->
+ttest_sgeno_csock_cases() ->
[
- {group, ttest_ssockt_csockf},
- {group, ttest_ssockt_csocko},
- {group, ttest_ssockt_csockt}
+ {group, ttest_sgeno_csockf},
+ {group, ttest_sgeno_csocko},
+ {group, ttest_sgeno_csockt}
].
-%% Server: transport = socket(tcp), active = true
-%% Client: transport = socket(tcp), active = false
-ttest_ssockt_csockf_cases() ->
+ttest_sgeno_csockf_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockt_csockf_small_tcp4,
- ttest_ssockt_csockf_small_tcp6,
- ttest_ssockt_csockf_small_tcpL],
+ [ttest_sgeno_csockf_small_tcp4,
+ ttest_sgeno_csockf_small_tcp6],
%% Medium
- [ttest_ssockt_csockf_medium_tcp4,
- ttest_ssockt_csockf_medium_tcp6,
- ttest_ssockt_csockf_medium_tcpL],
+ [ttest_sgeno_csockf_medium_tcp4,
+ ttest_sgeno_csockf_medium_tcp6],
%% Large
- [ttest_ssockt_csockf_large_tcp4,
- ttest_ssockt_csockf_large_tcp6,
- ttest_ssockt_csockf_large_tcpL]).
+ [ttest_sgeno_csockf_large_tcp4,
+ ttest_sgeno_csockf_large_tcp6]).
-%% Server: transport = socket(tcp), active = true
-%% Client: transport = socket(tcp), active = once
-ttest_ssockt_csocko_cases() ->
+ttest_sgeno_csocko_cases() ->
ttest_select_conditional_cases(
%% Small
- [ttest_ssockt_csocko_small_tcp4,
- ttest_ssockt_csocko_small_tcp6,
- ttest_ssockt_csocko_small_tcpL],
+ [ttest_sgeno_csocko_small_tcp4,
+ ttest_sgeno_csocko_small_tcp6],
%% Medium
- [ttest_ssockt_csocko_medium_tcp4,
- ttest_ssockt_csocko_medium_tcp6,
- ttest_ssockt_csocko_medium_tcpL],
+ [ttest_sgeno_csocko_medium_tcp4,
+ ttest_sgeno_csocko_medium_tcp6],
%% Large
- [ttest_ssockt_csocko_large_tcp4,
- ttest_ssockt_csocko_large_tcp6,
- ttest_ssockt_csocko_large_tcpL]).
+ [ttest_sgeno_csocko_large_tcp4,
+ ttest_sgeno_csocko_large_tcp6]).
+
+ttest_sgeno_csockt_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgeno_csockt_small_tcp4,
+ ttest_sgeno_csockt_small_tcp6],
+ %% Medium
+ [ttest_sgeno_csockt_medium_tcp4,
+ ttest_sgeno_csockt_medium_tcp6],
+ %% Large
+ [ttest_sgeno_csockt_large_tcp4,
+ ttest_sgeno_csockt_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+ttest_sgent_cases() ->
+ [
+ {group, ttest_sgent_cgen},
+ {group, ttest_sgent_cgs},
+ {group, ttest_sgent_csock}
+ ].
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp
+ttest_sgent_cgen_cases() ->
+ [
+ {group, ttest_sgent_cgenf},
+ {group, ttest_sgent_cgeno},
+ {group, ttest_sgent_cgent}
+ ].
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp, active = false
+ttest_sgent_cgenf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgenf_small_tcp4,
+ ttest_sgent_cgenf_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgenf_medium_tcp4,
+ ttest_sgent_cgenf_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgenf_large_tcp4,
+ ttest_sgent_cgenf_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp, active = once
+ttest_sgent_cgeno_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgeno_small_tcp4,
+ ttest_sgent_cgeno_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgeno_medium_tcp4,
+ ttest_sgent_cgeno_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgeno_large_tcp4,
+ ttest_sgent_cgeno_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp, active = true
+ttest_sgent_cgent_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgent_small_tcp4,
+ ttest_sgent_cgent_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgent_medium_tcp4,
+ ttest_sgent_cgent_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgent_large_tcp4,
+ ttest_sgent_cgent_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp(socket)
+ttest_sgent_cgs_cases() ->
+ [
+ {group, ttest_sgent_cgsf},
+ {group, ttest_sgent_cgso},
+ {group, ttest_sgent_cgst}
+ ].
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp(socket), active = false
+ttest_sgent_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgsf_small_tcp4,
+ ttest_sgent_cgsf_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgsf_medium_tcp4,
+ ttest_sgent_cgsf_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgsf_large_tcp4,
+ ttest_sgent_cgsf_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp(socket), active = once
+ttest_sgent_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgso_small_tcp4,
+ ttest_sgent_cgso_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgso_medium_tcp4,
+ ttest_sgent_cgso_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgso_large_tcp4,
+ ttest_sgent_cgso_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = gen_tcp(socket), active = true
+ttest_sgent_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_cgst_small_tcp4,
+ ttest_sgent_cgst_small_tcp6],
+ %% Medium
+ [ttest_sgent_cgst_medium_tcp4,
+ ttest_sgent_cgst_medium_tcp6],
+ %% Large
+ [ttest_sgent_cgst_large_tcp4,
+ ttest_sgent_cgst_large_tcp6]).
+
+%% Server: transport = gen_tcp, active = true
+%% Client: transport = socket(tcp)
+ttest_sgent_csock_cases() ->
+ [
+ {group, ttest_sgent_csockf},
+ {group, ttest_sgent_csocko},
+ {group, ttest_sgent_csockt}
+ ].
+
+ttest_sgent_csockf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_csockf_small_tcp4,
+ ttest_sgent_csockf_small_tcp6],
+ %% Medium
+ [ttest_sgent_csockf_medium_tcp4,
+ ttest_sgent_csockf_medium_tcp6],
+ %% Large
+ [ttest_sgent_csockf_large_tcp4,
+ ttest_sgent_csockf_large_tcp6]).
+
+ttest_sgent_csocko_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_csocko_small_tcp4,
+ ttest_sgent_csocko_small_tcp6],
+ %% Medium
+ [ttest_sgent_csocko_medium_tcp4,
+ ttest_sgent_csocko_medium_tcp6],
+ %% Large
+ [ttest_sgent_csocko_large_tcp4,
+ ttest_sgent_csocko_large_tcp6]).
+
+ttest_sgent_csockt_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_sgent_csockt_small_tcp4,
+ ttest_sgent_csockt_small_tcp6],
+ %% Medium
+ [ttest_sgent_csockt_medium_tcp4,
+ ttest_sgent_csockt_medium_tcp6],
+ %% Large
+ [ttest_sgent_csockt_large_tcp4,
+ ttest_sgent_csockt_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+ttest_ssockf_cases() ->
+ [
+ {group, ttest_ssockf_cgen},
+ {group, ttest_ssockf_cgs},
+ {group, ttest_ssockf_csock}
+ ].
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp
+ttest_ssockf_cgen_cases() ->
+ [
+ {group, ttest_ssockf_cgenf},
+ {group, ttest_ssockf_cgeno},
+ {group, ttest_ssockf_cgent}
+ ].
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp, active = false
+ttest_ssockf_cgenf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgenf_small_tcp4,
+ ttest_ssockf_cgenf_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgenf_medium_tcp4,
+ ttest_ssockf_cgenf_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgenf_large_tcp4,
+ ttest_ssockf_cgenf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp, active = once
+ttest_ssockf_cgeno_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgeno_small_tcp4,
+ ttest_ssockf_cgeno_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgeno_medium_tcp4,
+ ttest_ssockf_cgeno_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgeno_large_tcp4,
+ ttest_ssockf_cgeno_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp, active = true
+ttest_ssockf_cgent_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgent_small_tcp4,
+ ttest_ssockf_cgent_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgent_medium_tcp4,
+ ttest_ssockf_cgent_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgent_large_tcp4,
+ ttest_ssockf_cgent_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp(socket)
+ttest_ssockf_cgs_cases() ->
+ [
+ {group, ttest_ssockf_cgsf},
+ {group, ttest_ssockf_cgso},
+ {group, ttest_ssockf_cgst}
+ ].
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp(socket), active = false
+ttest_ssockf_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgsf_small_tcp4,
+ ttest_ssockf_cgsf_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgsf_medium_tcp4,
+ ttest_ssockf_cgsf_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgsf_large_tcp4,
+ ttest_ssockf_cgsf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp(socket), active = once
+ttest_ssockf_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgso_small_tcp4,
+ ttest_ssockf_cgso_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgso_medium_tcp4,
+ ttest_ssockf_cgso_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgso_large_tcp4,
+ ttest_ssockf_cgso_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = gen_tcp(socket), active = true
+ttest_ssockf_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_cgst_small_tcp4,
+ ttest_ssockf_cgst_small_tcp6],
+ %% Medium
+ [ttest_ssockf_cgst_medium_tcp4,
+ ttest_ssockf_cgst_medium_tcp6],
+ %% Large
+ [ttest_ssockf_cgst_large_tcp4,
+ ttest_ssockf_cgst_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = socket(tcp)
+ttest_ssockf_csock_cases() ->
+ [
+ {group, ttest_ssockf_csockf},
+ {group, ttest_ssockf_csocko},
+ {group, ttest_ssockf_csockt}
+ ].
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = socket(tcp), active = false
+ttest_ssockf_csockf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_csockf_small_tcp4,
+ ttest_ssockf_csockf_small_tcp6,
+ ttest_ssockf_csockf_small_tcpL],
+ %% Medium
+ [ttest_ssockf_csockf_medium_tcp4,
+ ttest_ssockf_csockf_medium_tcp6,
+ ttest_ssockf_csockf_medium_tcpL],
+ %% Large
+ [ttest_ssockf_csockf_large_tcp4,
+ ttest_ssockf_csockf_large_tcp6,
+ ttest_ssockf_csockf_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = socket(tcp), active = once
+ttest_ssockf_csocko_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_csocko_small_tcp4,
+ ttest_ssockf_csocko_small_tcp6,
+ ttest_ssockf_csocko_small_tcpL],
+ %% Medium
+ [ttest_ssockf_csocko_medium_tcp4,
+ ttest_ssockf_csocko_medium_tcp6,
+ ttest_ssockf_csocko_medium_tcpL],
+ %% Large
+ [ttest_ssockf_csocko_large_tcp4,
+ ttest_ssockf_csocko_large_tcp6,
+ ttest_ssockf_csocko_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = false
+%% Client: transport = socket(tcp), active = true
+ttest_ssockf_csockt_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockf_csockt_small_tcp4,
+ ttest_ssockf_csockt_small_tcp6,
+ ttest_ssockf_csockt_small_tcpL],
+ %% Medium
+ [ttest_ssockf_csockt_medium_tcp4,
+ ttest_ssockf_csockt_medium_tcp6,
+ ttest_ssockf_csockt_medium_tcpL],
+ %% Large
+ [ttest_ssockf_csockt_large_tcp4,
+ ttest_ssockf_csockt_large_tcp6,
+ ttest_ssockf_csockt_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = once
+ttest_ssocko_cases() ->
+ [
+ {group, ttest_ssocko_cgen},
+ {group, ttest_ssocko_cgs},
+ {group, ttest_ssocko_csock}
+ ].
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp
+ttest_ssocko_cgen_cases() ->
+ [
+ {group, ttest_ssocko_cgenf},
+ {group, ttest_ssocko_cgeno},
+ {group, ttest_ssocko_cgent}
+ ].
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp, active = false
+ttest_ssocko_cgenf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgenf_small_tcp4,
+ ttest_ssocko_cgenf_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgenf_medium_tcp4,
+ ttest_ssocko_cgenf_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgenf_large_tcp4,
+ ttest_ssocko_cgenf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp, active = once
+ttest_ssocko_cgeno_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgeno_small_tcp4,
+ ttest_ssocko_cgeno_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgeno_medium_tcp4,
+ ttest_ssocko_cgeno_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgeno_large_tcp4,
+ ttest_ssocko_cgeno_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp, active = true
+ttest_ssocko_cgent_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgent_small_tcp4,
+ ttest_ssocko_cgent_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgent_medium_tcp4,
+ ttest_ssocko_cgent_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgent_large_tcp4,
+ ttest_ssocko_cgent_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp(socket)
+ttest_ssocko_cgs_cases() ->
+ [
+ {group, ttest_ssocko_cgsf},
+ {group, ttest_ssocko_cgso},
+ {group, ttest_ssocko_cgst}
+ ].
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp(socket), active = false
+ttest_ssocko_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgsf_small_tcp4,
+ ttest_ssocko_cgsf_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgsf_medium_tcp4,
+ ttest_ssocko_cgsf_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgsf_large_tcp4,
+ ttest_ssocko_cgsf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp(socket), active = once
+ttest_ssocko_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgso_small_tcp4,
+ ttest_ssocko_cgso_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgso_medium_tcp4,
+ ttest_ssocko_cgso_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgso_large_tcp4,
+ ttest_ssocko_cgso_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = gen_tcp(socket), active = true
+ttest_ssocko_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_cgst_small_tcp4,
+ ttest_ssocko_cgst_small_tcp6],
+ %% Medium
+ [ttest_ssocko_cgst_medium_tcp4,
+ ttest_ssocko_cgst_medium_tcp6],
+ %% Large
+ [ttest_ssocko_cgst_large_tcp4,
+ ttest_ssocko_cgst_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = socket(tcp)
+ttest_ssocko_csock_cases() ->
+ [
+ {group, ttest_ssocko_csockf},
+ {group, ttest_ssocko_csocko},
+ {group, ttest_ssocko_csockt}
+ ].
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = socket(tcp), active = false
+ttest_ssocko_csockf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_csockf_small_tcp4,
+ ttest_ssocko_csockf_small_tcp6,
+ ttest_ssocko_csockf_small_tcpL],
+ %% Medium
+ [ttest_ssocko_csockf_medium_tcp4,
+ ttest_ssocko_csockf_medium_tcp6,
+ ttest_ssocko_csockf_medium_tcpL],
+ %% Large
+ [ttest_ssocko_csockf_large_tcp4,
+ ttest_ssocko_csockf_large_tcp6,
+ ttest_ssocko_csockf_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = socket(tcp), active = once
+ttest_ssocko_csocko_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_csocko_small_tcp4,
+ ttest_ssocko_csocko_small_tcp6,
+ ttest_ssocko_csocko_small_tcpL],
+ %% Medium
+ [ttest_ssocko_csocko_medium_tcp4,
+ ttest_ssocko_csocko_medium_tcp6,
+ ttest_ssocko_csocko_medium_tcpL],
+ %% Large
+ [ttest_ssocko_csocko_large_tcp4,
+ ttest_ssocko_csocko_large_tcp6,
+ ttest_ssocko_csocko_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = once
+%% Client: transport = socket(tcp), active = true
+ttest_ssocko_csockt_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssocko_csockt_small_tcp4,
+ ttest_ssocko_csockt_small_tcp6,
+ ttest_ssocko_csockt_small_tcpL],
+ %% Medium
+ [ttest_ssocko_csockt_medium_tcp4,
+ ttest_ssocko_csockt_medium_tcp6,
+ ttest_ssocko_csockt_medium_tcpL],
+ %% Large
+ [ttest_ssocko_csockt_large_tcp4,
+ ttest_ssocko_csockt_large_tcp6,
+ ttest_ssocko_csockt_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = true
+ttest_ssockt_cases() ->
+ [
+ {group, ttest_ssockt_cgen},
+ {group, ttest_ssockt_cgs},
+ {group, ttest_ssockt_csock}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp
+ttest_ssockt_cgen_cases() ->
+ [
+ {group, ttest_ssockt_cgenf},
+ {group, ttest_ssockt_cgeno},
+ {group, ttest_ssockt_cgent}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp, active = false
+ttest_ssockt_cgenf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgenf_small_tcp4,
+ ttest_ssockt_cgenf_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgenf_medium_tcp4,
+ ttest_ssockt_cgenf_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgenf_large_tcp4,
+ ttest_ssockt_cgenf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp, active = once
+ttest_ssockt_cgeno_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgeno_small_tcp4,
+ ttest_ssockt_cgeno_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgeno_medium_tcp4,
+ ttest_ssockt_cgeno_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgeno_large_tcp4,
+ ttest_ssockt_cgeno_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp, active = true
+ttest_ssockt_cgent_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgent_small_tcp4,
+ ttest_ssockt_cgent_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgent_medium_tcp4,
+ ttest_ssockt_cgent_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgent_large_tcp4,
+ ttest_ssockt_cgent_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp(socket)
+ttest_ssockt_cgs_cases() ->
+ [
+ {group, ttest_ssockt_cgsf},
+ {group, ttest_ssockt_cgso},
+ {group, ttest_ssockt_cgst}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp(socket), active = false
+ttest_ssockt_cgsf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgsf_small_tcp4,
+ ttest_ssockt_cgsf_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgsf_medium_tcp4,
+ ttest_ssockt_cgsf_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgsf_large_tcp4,
+ ttest_ssockt_cgsf_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp(socket), active = once
+ttest_ssockt_cgso_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgso_small_tcp4,
+ ttest_ssockt_cgso_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgso_medium_tcp4,
+ ttest_ssockt_cgso_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgso_large_tcp4,
+ ttest_ssockt_cgso_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = gen_tcp(socket), active = true
+ttest_ssockt_cgst_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_cgst_small_tcp4,
+ ttest_ssockt_cgst_small_tcp6],
+ %% Medium
+ [ttest_ssockt_cgst_medium_tcp4,
+ ttest_ssockt_cgst_medium_tcp6],
+ %% Large
+ [ttest_ssockt_cgst_large_tcp4,
+ ttest_ssockt_cgst_large_tcp6]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp)
+ttest_ssockt_csock_cases() ->
+ [
+ {group, ttest_ssockt_csockf},
+ {group, ttest_ssockt_csocko},
+ {group, ttest_ssockt_csockt}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp), active = false
+ttest_ssockt_csockf_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_csockf_small_tcp4,
+ ttest_ssockt_csockf_small_tcp6,
+ ttest_ssockt_csockf_small_tcpL],
+ %% Medium
+ [ttest_ssockt_csockf_medium_tcp4,
+ ttest_ssockt_csockf_medium_tcp6,
+ ttest_ssockt_csockf_medium_tcpL],
+ %% Large
+ [ttest_ssockt_csockf_large_tcp4,
+ ttest_ssockt_csockf_large_tcp6,
+ ttest_ssockt_csockf_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp), active = once
+ttest_ssockt_csocko_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_csocko_small_tcp4,
+ ttest_ssockt_csocko_small_tcp6,
+ ttest_ssockt_csocko_small_tcpL],
+ %% Medium
+ [ttest_ssockt_csocko_medium_tcp4,
+ ttest_ssockt_csocko_medium_tcp6,
+ ttest_ssockt_csocko_medium_tcpL],
+ %% Large
+ [ttest_ssockt_csocko_large_tcp4,
+ ttest_ssockt_csocko_large_tcp6,
+ ttest_ssockt_csocko_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp), active = true
+ttest_ssockt_csockt_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_ssockt_csockt_small_tcp4,
+ ttest_ssockt_csockt_small_tcp6,
+ ttest_ssockt_csockt_small_tcpL],
+ %% Medium
+ [ttest_ssockt_csockt_medium_tcp4,
+ ttest_ssockt_csockt_medium_tcp6,
+ ttest_ssockt_csockt_medium_tcpL],
+ %% Large
+ [ttest_ssockt_csockt_large_tcp4,
+ ttest_ssockt_csockt_large_tcp6,
+ ttest_ssockt_csockt_large_tcpL]).
+
+%% Server: transport = socket(tcp), active = true
+ttest_simple_ssockt_cases() ->
+ [
+ {group, ttest_simple_ssockt_csock}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp)
+ttest_simple_ssockt_csock_cases() ->
+ [
+ %% {group, ttest_simple_ssockt_csockf},
+ {group, ttest_simple_ssockt_csocko}%% ,
+ %% {group, ttest_simple_ssockt_csockt}
+ ].
+
+%% Server: transport = socket(tcp), active = true
+%% Client: transport = socket(tcp), active = once
+ttest_simple_ssockt_csocko_cases() ->
+ ttest_select_conditional_cases(
+ %% Small
+ [ttest_simple_ssockt_csocko_small_tcp4,
+ ttest_simple_ssockt_csocko_small_tcp6,
+ ttest_simple_ssockt_csocko_small_tcpL],
+ %% Medium
+ [],
+ %% Large
+ []).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+init_per_suite(Config0) ->
+ ?P("init_per_suite -> entry with"
+ "~n Config: ~p"
+ "~n Nodes: ~p", [Config0, erlang:nodes()]),
+
+ try socket:info() of
+ #{} ->
+ case ?KLIB:init_per_suite(Config0) of
+ {skip, _} = SKIP ->
+ SKIP;
+
+ Config1 when is_list(Config1) ->
+
+ ?P("init_per_suite -> end when "
+ "~n Config: ~p", [Config1]),
+
+ %% We need a monitor on this node also
+ kernel_test_sys_monitor:start(),
+
+ socket:use_registry(false),
+ case quiet_mode(Config1) of
+ default ->
+ case ?LOGGER:start() of
+ ok ->
+ Config1;
+ {error, Reason} ->
+ ?P("init_per_suite -> "
+ "Failed starting logger"
+ "~n Reason: ~p"
+ "~n", [Reason]),
+ {skip, "Failed starting logger"}
+ end;
+ Quiet ->
+ case ?LOGGER:start(Quiet) of
+ ok ->
+ [{esock_test_quiet, Quiet} | Config1];
+ {error, Reason} ->
+ ?P("init_per_suite -> "
+ "Failed starting logger"
+ "~n Reason: ~p"
+ "~n", [Reason]),
+ {skip, "Failed starting logger"}
+ end
+ end
+ end
+ catch
+ error : notsup ->
+ {skip, "esock not supported"};
+ error : undef ->
+ {skip, "esock not configured"}
+ end.
+
+end_per_suite(Config0) ->
+
+ ?P("end_per_suite -> entry with"
+ "~n Config: ~p"
+ "~n Nodes: ~p", [Config0, erlang:nodes()]),
+
+ %% Stop the local monitor
+ kernel_test_sys_monitor:stop(),
+
+ (catch ?LOGGER:stop()),
+
+ Config1 = ?KLIB:end_per_suite(Config0),
+
+ ?P("end_per_suite -> "
+ "~n Nodes: ~p", [erlang:nodes()]),
+
+ Config1.
+
+
+init_per_group(standard = GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [GroupName, Config]),
+ [{category, GroupName} | Config];
+init_per_group(bench = GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [GroupName, Config]),
+ [{category, GroupName} | Config];
+init_per_group(ttest = _GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [_GroupName, Config]),
+ case ttest_condition(Config) of
+ ok ->
+ ttest_manager_start(),
+ case lists:keysearch(esock_test_ttest_runtime, 1, Config) of
+ {value, _} ->
+ Config;
+ false ->
+ [{esock_test_ttest_runtime, which_ttest_runtime_env()} |
+ Config]
+ end;
+ {skip, _} = SKIP ->
+ SKIP
+ end;
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(ttest = _GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [_GroupName, Config]),
+ ttest_manager_stop(),
+ lists:keydelete(esock_test_ttest_runtime, 1, Config);
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+init_per_testcase(_TC, Config) ->
+ io:format("init_per_testcase(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [_TC, Config]),
+ Config.
+
+end_per_testcase(_TC, Config) ->
+ Config.
+
+
+quiet_mode(Config) ->
+ case lists:keysearch(esock_test_quiet, 1, Config) of
+ {value, {esock_test_quiet, Quiet}} ->
+ Quiet;
+ false ->
+ case os:getenv("ESOCK_TEST_QUIET") of
+ "true" -> true;
+ "false" -> false;
+ _ -> default
+ end
+ end.
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% %%
+%% TIME TEST %%
+%% %%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgenf_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgenf_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, once,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, once,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, once,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, once,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgeno_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, once,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgeno_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, once,
+ sock, true).
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgent_medium_tcp4() ->
+ [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=medium"}].
+
+ttest_sgent_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+ttest_sgent_cgent_medium_tcp6() ->
+ [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=medium"}].
+
+ttest_sgent_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgent_large_tcp4() ->
+ [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=large"}].
+
+ttest_sgent_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgent_large_tcp6() ->
+ [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=large"}].
+
+ttest_sgent_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gen, true).
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ gs, true).
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+
+ttest_sgent_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgent_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgent_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgent_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgent_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gen, true,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gs, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gs, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgsf_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgsf_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, false,
+ sock, true).
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgso_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgso_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgso_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gen, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgso_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgso_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgso_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet
+%%
+
+ttest_sgso_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgso_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgso_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gen, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gen, true).
+
+
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet
+%%
-%% Server: transport = socket(tcp), active = true
-%% Client: transport = socket(tcp), active = true
-ttest_ssockt_csockt_cases() ->
- ttest_select_conditional_cases(
- %% Small
- [ttest_ssockt_csockt_small_tcp4,
- ttest_ssockt_csockt_small_tcp6,
- ttest_ssockt_csockt_small_tcpL],
- %% Medium
- [ttest_ssockt_csockt_medium_tcp4,
- ttest_ssockt_csockt_medium_tcp6,
- ttest_ssockt_csockt_medium_tcpL],
- %% Large
- [ttest_ssockt_csockt_large_tcp4,
- ttest_ssockt_csockt_large_tcp6,
- ttest_ssockt_csockt_large_tcpL]).
+ttest_sgso_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gs, false).
-%% Server: transport = socket(tcp), active = true
-ttest_simple_ssockt_cases() ->
- [
- {group, ttest_simple_ssockt_csock}
- ].
-%% Server: transport = socket(tcp), active = true
-%% Client: transport = socket(tcp)
-ttest_simple_ssockt_csock_cases() ->
- [
- %% {group, ttest_simple_ssockt_csockf},
- {group, ttest_simple_ssockt_csocko}%% ,
- %% {group, ttest_simple_ssockt_csockt}
- ].
-%% Server: transport = socket(tcp), active = true
-%% Client: transport = socket(tcp), active = once
-ttest_simple_ssockt_csocko_cases() ->
- ttest_select_conditional_cases(
- %% Small
- [ttest_simple_ssockt_csocko_small_tcp4,
- ttest_simple_ssockt_csocko_small_tcp6,
- ttest_simple_ssockt_csocko_small_tcpL],
- %% Medium
- [],
- %% Large
- []).
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
-init_per_suite(Config0) ->
- ?P("init_per_suite -> entry with"
- "~n Config: ~p"
- "~n Nodes: ~p", [Config0, erlang:nodes()]),
-
- try socket:info() of
- #{} ->
- case ?KLIB:init_per_suite(Config0) of
- {skip, _} = SKIP ->
- SKIP;
+ttest_sgso_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gs, false).
- Config1 when is_list(Config1) ->
- ?P("init_per_suite -> end when "
- "~n Config: ~p", [Config1]),
- %% We need a monitor on this node also
- kernel_test_sys_monitor:start(),
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
- socket:use_registry(false),
- case quiet_mode(Config1) of
- default ->
- case ?LOGGER:start() of
- ok ->
- Config1;
- {error, Reason} ->
- ?P("init_per_suite -> "
- "Failed starting logger"
- "~n Reason: ~p"
- "~n", [Reason]),
- {skip, "Failed starting logger"}
- end;
- Quiet ->
- case ?LOGGER:start(Quiet) of
- ok ->
- [{esock_test_quiet, Quiet} | Config1];
- {error, Reason} ->
- ?P("init_per_suite -> "
- "Failed starting logger"
- "~n Reason: ~p"
- "~n", [Reason]),
- {skip, "Failed starting logger"}
- end
- end
- end
- catch
- error : notsup ->
- {skip, "esock not supported"};
- error : undef ->
- {skip, "esock not configured"}
- end.
+ttest_sgso_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gs, false).
-end_per_suite(Config0) ->
- ?P("end_per_suite -> entry with"
- "~n Config: ~p"
- "~n Nodes: ~p", [Config0, erlang:nodes()]),
- %% Stop the local monitor
- kernel_test_sys_monitor:stop(),
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
- (catch ?LOGGER:stop()),
+ttest_sgso_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gs, false).
- Config1 = ?KLIB:end_per_suite(Config0),
- ?P("end_per_suite -> "
- "~n Nodes: ~p", [erlang:nodes()]),
- Config1.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+ttest_sgso_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gs, false).
-init_per_group(standard = GroupName, Config) ->
- io:format("init_per_group(~w) -> entry with"
- "~n Config: ~p"
- "~n", [GroupName, Config]),
- [{category, GroupName} | Config];
-init_per_group(bench = GroupName, Config) ->
- io:format("init_per_group(~w) -> entry with"
- "~n Config: ~p"
- "~n", [GroupName, Config]),
- [{category, GroupName} | Config];
-init_per_group(ttest = _GroupName, Config) ->
- io:format("init_per_group(~w) -> entry with"
- "~n Config: ~p"
- "~n", [_GroupName, Config]),
- case ttest_condition(Config) of
- ok ->
- ttest_manager_start(),
- case lists:keysearch(esock_test_ttest_runtime, 1, Config) of
- {value, _} ->
- Config;
- false ->
- [{esock_test_ttest_runtime, which_ttest_runtime_env()} |
- Config]
- end;
- {skip, _} = SKIP ->
- SKIP
- end;
-init_per_group(_GroupName, Config) ->
- Config.
-end_per_group(ttest = _GroupName, Config) ->
- io:format("init_per_group(~w) -> entry with"
- "~n Config: ~p"
- "~n", [_GroupName, Config]),
- ttest_manager_stop(),
- lists:keydelete(esock_test_ttest_runtime, 1, Config);
-end_per_group(_GroupName, Config) ->
- Config.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
-init_per_testcase(_TC, Config) ->
- io:format("init_per_testcase(~w) -> entry with"
- "~n Config: ~p"
- "~n", [_TC, Config]),
- Config.
+ttest_sgso_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gs, once).
-end_per_testcase(_TC, Config) ->
- Config.
-quiet_mode(Config) ->
- case lists:keysearch(esock_test_quiet, 1, Config) of
- {value, {esock_test_quiet, Quiet}} ->
- Quiet;
- false ->
- case os:getenv("ESOCK_TEST_QUIET") of
- "true" -> true;
- "false" -> false;
- _ -> default
- end
- end.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_sgso_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gs, once).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% %%
-%% TIME TEST %%
-%% %%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gs, once).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_sgso_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gs, once).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
+%%
+
+ttest_sgso_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gs, once).
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_small_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
-%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% ping-pong like test case.
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_large_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgenf_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ gs, true).
+
+
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_small_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_large_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgent_small_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgent_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgent_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgent_large_tcp4,
- Runtime,
- inet,
- gen, false,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_cgent_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_small_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgso_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgso_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_large_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockf_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgso_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, once,
+ sock, true).
+
+
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgsf_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- gs, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgsf_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- gs, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgsf_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- gs, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgsf_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- gs, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgsf_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- gs, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp(socket), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgsf_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- gs, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_small_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_large_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
-
+ttest_sgst_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gen, once).
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgenf_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockt_small_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgenf_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgenf_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockt_medium_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgenf_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockt_medium_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgenf_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockt_large_tcp4,
- Runtime,
- inet,
- gen, false,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgenf_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgenf_csockt_large_tcp6,
- Runtime,
- inet6,
- gen, false,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gen, true).
+
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_small_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_large_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = false
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgenf_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_small_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_large_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgent_small_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgent_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgent_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgent_large_tcp4,
- Runtime,
- inet,
- gen, once,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = gen_tcp(socket), Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_cgent_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ gs, true).
+
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_small_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_large_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockf_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_small_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_large_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgeno_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockt_small_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ gs, true,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgeno_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_sgst_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ gs, true,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgeno_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockt_medium_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
-
+ttest_sgst_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ gs, true,
+ sock, true).
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgeno_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockt_medium_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_sgst_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ gs, true,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgeno_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockt_large_tcp4,
- Runtime,
- inet,
- gen, once,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ gs, true,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = once
+%% Server: Transport = gen_tcp(socket), Active = true
%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgeno_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgeno_csockt_large_tcp6,
- Runtime,
- inet6,
- gen, once,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_sgst_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ gs, true,
+ sock, true).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgent_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_small_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgent_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_large_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgenf_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgent_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_small_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgent_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_large_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgent_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgent_small_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgeno_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_cgent_medium_tcp4() ->
- [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=medium"}].
-
-ttest_sgent_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgent_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_cgent_medium_tcp6() ->
- [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=medium"}].
-ttest_sgent_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgent_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgent_cgent_large_tcp4() ->
- [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=large"}].
-
-ttest_sgent_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgent_large_tcp4,
- Runtime,
- inet,
- gen, true,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = false
%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_cgent_large_tcp6() ->
- [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=large"}].
-
-ttest_sgent_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_cgent_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-
-ttest_sgent_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_small_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgent_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_large_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockf_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgent_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_small_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet
-%%
-
-ttest_sgent_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_large_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+%%
+
+ttest_ssockf_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_sgent_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockt_small_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_sgent_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csocko_small_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_sgent_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockt_medium_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_sgent_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockt_medium_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_sgent_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockt_large_tcp4,
- Runtime,
- inet,
- gen, true,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = gen_tcp, Active = true
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_sgent_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_sgent_csockt_large_tcp6,
- Runtime,
- inet6,
- gen, true,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ gs, true).
@@ -3893,39 +8859,32 @@ ttest_sgent_csockt_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_small_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
-
+ttest_ssockf_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ sock, false).
@@ -3933,19 +8892,33 @@ ttest_ssockf_cgenf_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: local
+%%
+
+ttest_ssockf_csockf_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockf_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ sock, false).
@@ -3953,19 +8926,16 @@ ttest_ssockf_cgenf_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockf_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ sock, false).
@@ -3973,19 +8943,33 @@ ttest_ssockf_cgenf_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: local
+%%
+
+ttest_ssockf_csockf_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockf_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_large_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ sock, false).
@@ -3993,19 +8977,16 @@ ttest_ssockf_cgenf_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockf_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgenf_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ sock, false).
@@ -4013,19 +8994,33 @@ ttest_ssockf_cgenf_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
+%% Domain: local
+%%
+
+ttest_ssockf_csockf_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, false,
+ sock, false).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_small_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, false,
+ sock, once).
@@ -4033,19 +9028,16 @@ ttest_ssockf_cgeno_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, false,
+ sock, once).
@@ -4053,19 +9045,33 @@ ttest_ssockf_cgeno_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: local
+%%
+
+ttest_ssockf_csocko_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockf_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ sock, once).
@@ -4073,19 +9079,16 @@ ttest_ssockf_cgeno_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockf_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ sock, once).
@@ -4093,19 +9096,33 @@ ttest_ssockf_cgeno_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: local
+%%
+
+ttest_ssockf_csocko_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockf_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_large_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ sock, once).
@@ -4113,19 +9130,16 @@ ttest_ssockf_cgeno_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockf_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ sock, once).
@@ -4133,19 +9147,33 @@ ttest_ssockf_cgeno_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: local
+%%
+
+ttest_ssockf_csocko_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, false,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgent_small_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ sock, true).
@@ -4153,19 +9181,50 @@ ttest_ssockf_cgent_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgeno_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockf_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: small (=1)
+%% Domain: local
+%%
+
+ttest_ssockf_csockt_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, false,
+ sock, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_ssockf_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, false,
+ sock, true).
@@ -4173,19 +9232,16 @@ ttest_ssockf_cgent_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
-%% Domain: inet
-%%
+%% Domain: inet6
+%%
-ttest_ssockf_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgent_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, false,
+ sock, true).
@@ -4193,19 +9249,16 @@ ttest_ssockf_cgent_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
-%% Domain: inet6
+%% Domain: local
%%
-ttest_ssockf_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgent_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockf_csockt_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, false,
+ sock, true).
@@ -4213,19 +9266,16 @@ ttest_ssockf_cgent_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockf_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgent_large_tcp4,
- Runtime,
- inet,
- sock, false,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, false,
+ sock, true).
@@ -4233,19 +9283,16 @@ ttest_ssockf_cgent_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockf_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_cgent_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockf_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, false,
+ sock, true).
@@ -4253,179 +9300,172 @@ ttest_ssockf_cgent_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Client: Transport = socket(tcp), Active = true
+%% Message Size: large (=3)
+%% Domain: local
+%%
+
+ttest_ssockf_csockt_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, false,
+ sock, true).
+
+
+
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_cgsf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- sock, false,
- gs, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_cgsf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- sock, false,
- gs, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockf_cgsf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- sock, false,
- gs, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockf_cgsf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- sock, false,
- gs, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockf_cgsf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet,
- sock, false,
- gs, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp(socket), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockf_cgsf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(?FUNCTION_NAME,
- Runtime,
- inet6,
- sock, false,
- gs, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_small_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: small (=1)
-%% Domain: local
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
-ttest_ssockf_csockf_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_small_tcpL,
- Runtime,
- local,
- sock, false,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gen, once).
@@ -4433,39 +9473,33 @@ ttest_ssockf_csockf_small_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp, Active = once
%% Message Size: medium (=2)
-%% Domain: inet
-%%
+%% Domain: inet6
+%%
-ttest_ssockf_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: medium (=2)
-%% Domain: inet6
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
-ttest_ssockf_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gen, once).
@@ -4473,79 +9507,67 @@ ttest_ssockf_csockf_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: medium (=2)
-%% Domain: local
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
%%
-ttest_ssockf_csockf_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_medium_tcpL,
- Runtime,
- local,
- sock, false,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: large (=3)
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_large_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: large (=3)
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = false
-%% Message Size: large (=3)
-%% Domain: local
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
-ttest_ssockf_csockf_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockf_large_tcpL,
- Runtime,
- local,
- sock, false,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gen, true).
@@ -4553,39 +9575,33 @@ ttest_ssockf_csockf_large_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: small (=1)
-%% Domain: inet
-%%
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
-ttest_ssockf_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_small_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: small (=1)
-%% Domain: inet6
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet
+%%
-ttest_ssockf_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gen, true).
@@ -4593,199 +9609,172 @@ ttest_ssockf_csocko_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: small (=1)
-%% Domain: local
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: large (=3)
+%% Domain: inet6
%%
-ttest_ssockf_csocko_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_small_tcpL,
- Runtime,
- local,
- sock, false,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gen, true).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: medium (=2)
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: medium (=2)
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
-%% Domain: local
-%%
+%% Domain: inet
+%%
-ttest_ssockf_csocko_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_medium_tcpL,
- Runtime,
- local,
- sock, false,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: large (=3)
-%% Domain: inet
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
-ttest_ssockf_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_large_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
-%% Domain: inet6
-%%
+%% Domain: inet
+%%
-ttest_ssockf_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
-%% Domain: local
+%% Domain: inet6
%%
-ttest_ssockf_csocko_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_large_tcpL,
- Runtime,
- local,
- sock, false,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gs, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_small_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: small (=1)
-%% Domain: local
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
-ttest_ssockf_csockt_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csocko_small_tcpL,
- Runtime,
- local,
- sock, false,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gs, once).
@@ -4793,39 +9782,33 @@ ttest_ssockf_csockt_small_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
-%% Domain: inet
-%%
+%% Domain: inet6
+%%
-ttest_ssockf_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_medium_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: medium (=2)
-%% Domain: inet6
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
-ttest_ssockf_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_medium_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gs, once).
@@ -4833,59 +9816,67 @@ ttest_ssockf_csockt_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: medium (=2)
-%% Domain: local
+%% Client: Transport = gen_tcp(socket), Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
%%
-ttest_ssockf_csockt_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_medium_tcpL,
- Runtime,
- local,
- sock, false,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gs, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: large (=3)
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockf_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_large_tcp4,
- Runtime,
- inet,
- sock, false,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: large (=3)
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockf_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_large_tcp6,
- Runtime,
- inet6,
- sock, false,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ gs, true).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
+
+ttest_ssocko_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ gs, true).
@@ -4893,19 +9884,16 @@ ttest_ssockf_csockt_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: large (=3)
-%% Domain: local
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
%%
-ttest_ssockf_csockt_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockf_csockt_large_tcpL,
- Runtime,
- local,
- sock, false,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ gs, true).
@@ -4913,39 +9901,35 @@ ttest_ssockf_csockt_large_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: small (=1)
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssocko_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_small_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ gs, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: small (=1)
+%% Server: Transport = socket(tcp), Active = false
+%% Client: Transport = gen_tcp(socket), Active = true
+%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssocko_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ gs, true).
+
+
@@ -4953,19 +9937,16 @@ ttest_ssocko_cgenf_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: medium (=2)
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssocko_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ sock, false).
@@ -4973,19 +9954,16 @@ ttest_ssocko_cgenf_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: medium (=2)
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssocko_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ sock, false).
@@ -4993,19 +9971,16 @@ ttest_ssocko_cgenf_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: large (=3)
-%% Domain: inet
-%%
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: small (=1)
+%% Domain: local
+%%
-ttest_ssocko_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_large_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csockf_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, once,
+ sock, false).
@@ -5013,19 +9988,16 @@ ttest_ssocko_cgenf_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = false
-%% Message Size: large (=3)
-%% Domain: inet6
-%%
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet
+%%
-ttest_ssocko_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgenf_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csockf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ sock, false).
@@ -5033,19 +10005,16 @@ ttest_ssocko_cgenf_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = once
-%% Message Size: small (=1)
-%% Domain: inet
-%%
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
-ttest_ssocko_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_small_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ sock, false).
@@ -5053,19 +10022,16 @@ ttest_ssocko_cgeno_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = once
-%% Message Size: small (=1)
-%% Domain: inet6
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: medium (=2)
+%% Domain: local
%%
-ttest_ssocko_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockf_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, once,
+ sock, false).
@@ -5073,39 +10039,33 @@ ttest_ssocko_cgeno_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = once
-%% Message Size: medium (=2)
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssocko_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
-%% Message Size: medium (=2)
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = false
+%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssocko_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ sock, false).
@@ -5113,39 +10073,33 @@ ttest_ssocko_cgeno_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = socket(tcp), Active = false
%% Message Size: large (=3)
-%% Domain: inet
-%%
+%% Domain: local
+%%
-ttest_ssocko_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_large_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csockf_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, once,
+ sock, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = once
-%% Message Size: large (=3)
-%% Domain: inet6
-%%
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
-ttest_ssocko_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgeno_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csocko_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ sock, once).
@@ -5153,39 +10107,33 @@ ttest_ssocko_cgeno_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
-%% Domain: inet
-%%
+%% Domain: inet6
+%%
-ttest_ssocko_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_small_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csocko_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: small (=1)
-%% Domain: inet6
+%% Domain: local
%%
-ttest_ssocko_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csocko_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, once,
+ sock, once).
@@ -5193,39 +10141,33 @@ ttest_ssocko_cgent_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssocko_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csocko_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssocko_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csocko_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ sock, once).
@@ -5233,39 +10175,50 @@ ttest_ssocko_cgent_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: medium (=2)
+%% Domain: local
+%%
+
+ttest_ssocko_csocko_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssocko_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_large_tcp4,
- Runtime,
- inet,
- sock, once,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csocko_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ sock, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = false
-%% Client: Transport = gen_tcp, Active = true
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssocko_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_cgent_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csocko_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ sock, once).
@@ -5273,59 +10226,67 @@ ttest_ssocko_cgent_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = once
+%% Message Size: large (=3)
+%% Domain: local
+%%
+
+ttest_ssocko_csocko_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, once,
+ sock, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssocko_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_small_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockt_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssocko_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockt_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, once,
+ sock, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Server: Transport = socket(tcp), Active = once
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: small (=1)
%% Domain: local
%%
-ttest_ssocko_csockf_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_small_tcpL,
- Runtime,
- local,
- sock, once,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockt_small_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, once,
+ sock, true).
@@ -5333,19 +10294,16 @@ ttest_ssocko_csockf_small_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssocko_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockt_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, once,
+ sock, true).
@@ -5353,19 +10311,16 @@ ttest_ssocko_csockf_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssocko_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockt_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, once,
+ sock, true).
@@ -5373,19 +10328,16 @@ ttest_ssocko_csockf_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: medium (=2)
%% Domain: local
%%
-ttest_ssocko_csockf_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_medium_tcpL,
- Runtime,
- local,
- sock, once,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssocko_csockt_medium_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, once,
+ sock, true).
@@ -5393,19 +10345,16 @@ ttest_ssocko_csockf_medium_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssocko_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_large_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csockt_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, once,
+ sock, true).
@@ -5413,19 +10362,16 @@ ttest_ssocko_csockf_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssocko_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssocko_csockt_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, once,
+ sock, true).
@@ -5433,379 +10379,328 @@ ttest_ssocko_csockf_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = false
+%% Client: Transport = socket(tcp), Active = true
%% Message Size: large (=3)
%% Domain: local
%%
-ttest_ssocko_csockf_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockf_large_tcpL,
- Runtime,
- local,
- sock, once,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
-
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% This test case uses the time test (ttest) utility to implement a
-%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: small (=1)
-%% Domain: inet
-%%
-
-ttest_ssocko_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_small_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssocko_csockt_large_tcpL(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, once,
+ sock, true).
+
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
-%% Domain: inet6
-%%
+%% Domain: inet
+%%
-ttest_ssocko_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgenf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: small (=1)
-%% Domain: local
+%% Domain: inet6
%%
-ttest_ssocko_csocko_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_small_tcpL,
- Runtime,
- local,
- sock, once,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgenf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssocko_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgenf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssocko_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgenf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: medium (=2)
-%% Domain: local
-%%
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
+%% Message Size: large (=3)
+%% Domain: inet
+%%
-ttest_ssocko_csocko_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_medium_tcpL,
- Runtime,
- local,
- sock, once,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgenf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = false
%% Message Size: large (=3)
-%% Domain: inet
-%%
+%% Domain: inet6
+%%
-ttest_ssocko_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_large_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgenf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gen, false).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: large (=3)
-%% Domain: inet6
-%%
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet
+%%
-ttest_ssocko_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgeno_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = once
-%% Message Size: large (=3)
-%% Domain: local
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: small (=1)
+%% Domain: inet6
%%
-ttest_ssocko_csocko_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_large_tcpL,
- Runtime,
- local,
- sock, once,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgeno_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: small (=1)
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssocko_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_small_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgeno_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: small (=1)
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssocko_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgeno_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: small (=1)
-%% Domain: local
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet
+%%
+
+ttest_ssockt_cgeno_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gen, once).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This test case uses the time test (ttest) utility to implement a
+%% ping-pong like test case.
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = once
+%% Message Size: large (=3)
+%% Domain: inet6
%%
-ttest_ssocko_csockt_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csocko_small_tcpL,
- Runtime,
- local,
- sock, once,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgeno_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gen, once).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: medium (=2)
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssocko_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_medium_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgent_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: medium (=2)
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssocko_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_medium_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgent_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: medium (=2)
-%% Domain: local
-%%
+%% Domain: inet
+%%
-ttest_ssocko_csockt_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_medium_tcpL,
- Runtime,
- local,
- sock, once,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgent_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
-%% Message Size: large (=3)
-%% Domain: inet
-%%
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
+%% Message Size: medium (=2)
+%% Domain: inet6
+%%
-ttest_ssocko_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_large_tcp4,
- Runtime,
- inet,
- sock, once,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgent_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
-%% Domain: inet6
-%%
+%% Domain: inet
+%%
-ttest_ssocko_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_large_tcp6,
- Runtime,
- inet6,
- sock, once,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgent_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gen, true).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
-%% Server: Transport = socket(tcp), Active = once
-%% Client: Transport = socket(tcp), Active = true
+%% Server: Transport = socket(tcp), Active = true
+%% Client: Transport = gen_tcp, Active = true
%% Message Size: large (=3)
-%% Domain: local
+%% Domain: inet6
%%
-ttest_ssocko_csockt_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssocko_csockt_large_tcpL,
- Runtime,
- local,
- sock, once,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgent_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gen, true).
+
+
+
@@ -5813,19 +10708,16 @@ ttest_ssocko_csockt_large_tcpL(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockt_cgenf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_small_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgsf_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gs, false).
@@ -5833,19 +10725,16 @@ ttest_ssockt_cgenf_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockt_cgenf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, false,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgsf_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gs, false).
@@ -5853,19 +10742,16 @@ ttest_ssockt_cgenf_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockt_cgenf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgsf_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gs, false).
@@ -5873,19 +10759,16 @@ ttest_ssockt_cgenf_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockt_cgenf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, false,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgsf_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gs, false).
@@ -5893,19 +10776,16 @@ ttest_ssockt_cgenf_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockt_cgenf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_large_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgsf_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gs, false).
@@ -5913,19 +10793,16 @@ ttest_ssockt_cgenf_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = false
+%% Client: Transport = gen_tcp(socket), Active = false
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockt_cgenf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgenf_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, false,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgsf_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gs, false).
@@ -5933,19 +10810,16 @@ ttest_ssockt_cgenf_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockt_cgeno_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_small_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgso_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gs, once).
@@ -5953,19 +10827,16 @@ ttest_ssockt_cgeno_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockt_cgeno_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, once,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgso_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gs, once).
@@ -5973,19 +10844,16 @@ ttest_ssockt_cgeno_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockt_cgeno_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgso_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gs, once).
@@ -5993,19 +10861,16 @@ ttest_ssockt_cgeno_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockt_cgeno_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, once,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgso_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gs, once).
@@ -6013,19 +10878,16 @@ ttest_ssockt_cgeno_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockt_cgeno_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_large_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgso_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gs, once).
@@ -6033,19 +10895,16 @@ ttest_ssockt_cgeno_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = once
+%% Client: Transport = gen_tcp(socket), Active = once
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockt_cgeno_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgeno_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, once,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgso_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gs, once).
@@ -6053,19 +10912,16 @@ ttest_ssockt_cgeno_large_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet
%%
-ttest_ssockt_cgent_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_small_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgst_small_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ gs, true).
@@ -6073,19 +10929,16 @@ ttest_ssockt_cgent_small_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: small (=1)
%% Domain: inet6
%%
-ttest_ssockt_cgent_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, true,
- 1, ttest_small_max_outstanding(Config)).
+ttest_ssockt_cgst_small_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ gs, true).
@@ -6093,19 +10946,16 @@ ttest_ssockt_cgent_small_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet
%%
-ttest_ssockt_cgent_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgst_medium_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ gs, true).
@@ -6113,19 +10963,16 @@ ttest_ssockt_cgent_medium_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: medium (=2)
%% Domain: inet6
%%
-ttest_ssockt_cgent_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, true,
- 2, ttest_medium_max_outstanding(Config)).
+ttest_ssockt_cgst_medium_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ gs, true).
@@ -6133,19 +10980,16 @@ ttest_ssockt_cgent_medium_tcp6(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet
%%
-ttest_ssockt_cgent_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_large_tcp4,
- Runtime,
- inet,
- sock, true,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgst_large_tcp4(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ gs, true).
@@ -6153,19 +10997,19 @@ ttest_ssockt_cgent_large_tcp4(Config) when is_list(Config) ->
%% This test case uses the time test (ttest) utility to implement a
%% ping-pong like test case.
%% Server: Transport = socket(tcp), Active = true
-%% Client: Transport = gen_tcp, Active = true
+%% Client: Transport = gen_tcp(socket), Active = true
%% Message Size: large (=3)
%% Domain: inet6
%%
-ttest_ssockt_cgent_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_cgent_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- gen, true,
- 3, ttest_large_max_outstanding(Config)).
+ttest_ssockt_cgst_large_tcp6(Config) when is_list(Config) ->
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ gs, true).
+
+
+
@@ -6179,13 +11023,10 @@ ttest_ssockt_cgent_large_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_small_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ sock, false).
@@ -6199,13 +11040,10 @@ ttest_ssockt_csockf_small_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ sock, false).
@@ -6219,13 +11057,10 @@ ttest_ssockt_csockf_small_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_small_tcpL,
- Runtime,
- local,
- sock, true,
- sock, false,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, true,
+ sock, false).
@@ -6239,13 +11074,10 @@ ttest_ssockt_csockf_small_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ sock, false).
@@ -6259,13 +11091,10 @@ ttest_ssockt_csockf_medium_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ sock, false).
@@ -6279,13 +11108,10 @@ ttest_ssockt_csockf_medium_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_medium_tcpL,
- Runtime,
- local,
- sock, true,
- sock, false,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, true,
+ sock, false).
@@ -6299,13 +11125,10 @@ ttest_ssockt_csockf_medium_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_large_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ sock, false).
@@ -6319,13 +11142,10 @@ ttest_ssockt_csockf_large_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ sock, false).
@@ -6339,13 +11159,10 @@ ttest_ssockt_csockf_large_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockf_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockf_large_tcpL,
- Runtime,
- local,
- sock, true,
- sock, false,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, true,
+ sock, false).
@@ -6359,13 +11176,10 @@ ttest_ssockt_csockf_large_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_small_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ sock, once).
@@ -6379,13 +11193,10 @@ ttest_ssockt_csocko_small_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ sock, once).
@@ -6399,13 +11210,10 @@ ttest_ssockt_csocko_small_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_small_tcpL,
- Runtime,
- local,
- sock, true,
- sock, once,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, true,
+ sock, once).
@@ -6419,13 +11227,10 @@ ttest_ssockt_csocko_small_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ sock, once).
@@ -6439,13 +11244,10 @@ ttest_ssockt_csocko_medium_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ sock, once).
@@ -6459,13 +11261,10 @@ ttest_ssockt_csocko_medium_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_medium_tcpL,
- Runtime,
- local,
- sock, true,
- sock, once,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, true,
+ sock, once).
@@ -6479,13 +11278,10 @@ ttest_ssockt_csocko_medium_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_large_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ sock, once).
@@ -6499,13 +11295,10 @@ ttest_ssockt_csocko_large_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ sock, once).
@@ -6519,13 +11312,10 @@ ttest_ssockt_csocko_large_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csocko_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_large_tcpL,
- Runtime,
- local,
- sock, true,
- sock, once,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, true,
+ sock, once).
@@ -6539,13 +11329,10 @@ ttest_ssockt_csocko_large_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_small_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_small_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet,
+ sock, true,
+ sock, true).
@@ -6559,13 +11346,10 @@ ttest_ssockt_csockt_small_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_small_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_small_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ inet6,
+ sock, true,
+ sock, true).
@@ -6579,13 +11363,10 @@ ttest_ssockt_csockt_small_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_small_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csocko_small_tcpL,
- Runtime,
- local,
- sock, true,
- sock, true,
- 1, ttest_small_max_outstanding(Config)).
+ ?TTEST_TCP_SMALL(Config,
+ local,
+ sock, true,
+ sock, true).
@@ -6599,13 +11380,10 @@ ttest_ssockt_csockt_small_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_medium_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_medium_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet,
+ sock, true,
+ sock, true).
@@ -6619,13 +11397,10 @@ ttest_ssockt_csockt_medium_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_medium_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_medium_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ inet6,
+ sock, true,
+ sock, true).
@@ -6639,13 +11414,10 @@ ttest_ssockt_csockt_medium_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_medium_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_medium_tcpL,
- Runtime,
- local,
- sock, true,
- sock, true,
- 2, ttest_medium_max_outstanding(Config)).
+ ?TTEST_TCP_MEDIUM(Config,
+ local,
+ sock, true,
+ sock, true).
@@ -6659,13 +11431,10 @@ ttest_ssockt_csockt_medium_tcpL(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_large_tcp4(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_large_tcp4,
- Runtime,
- inet,
- sock, true,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet,
+ sock, true,
+ sock, true).
@@ -6679,13 +11448,10 @@ ttest_ssockt_csockt_large_tcp4(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_large_tcp6(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_large_tcp6,
- Runtime,
- inet6,
- sock, true,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ inet6,
+ sock, true,
+ sock, true).
@@ -6699,13 +11465,10 @@ ttest_ssockt_csockt_large_tcp6(Config) when is_list(Config) ->
%%
ttest_ssockt_csockt_large_tcpL(Config) when is_list(Config) ->
- Runtime = which_ttest_runtime(Config),
- ttest_tcp(ttest_ssockt_csockt_large_tcpL,
- Runtime,
- local,
- sock, true,
- sock, true,
- 3, ttest_large_max_outstanding(Config)).
+ ?TTEST_TCP_LARGE(Config,
+ local,
+ sock, true,
+ sock, true).
@@ -6919,8 +11682,7 @@ ttest_tcp(InitState) ->
cmd => fun(#{remote := true} = State) ->
{Peer, Node} = start_node("server"),
?SEV_IPRINT("server node created:"
- "~n Peer: ~p"
- "~n Node: ~p", [Peer, Node]),
+ "~n Node: ~p", [Node]),
{ok, State#{peer => Peer, node => Node}};
(State) ->
?SEV_IPRINT("use local node for server"),
@@ -7014,7 +11776,8 @@ ttest_tcp(InitState) ->
{ok, State1}
end},
#{desc => "(maybe) stop (server) node",
- cmd => fun(#{peer := Peer} = State) when (Peer =/= undefined) ->
+ cmd => fun(#{peer := Peer,
+ node := _Node} = State) when (Peer =/= undefined) ->
{ok,
try peer:stop(Peer) of
ok ->
@@ -7065,8 +11828,7 @@ ttest_tcp(InitState) ->
%% *** Wait for start order part ***
#{desc => "await start",
cmd => fun(#{domain := local} = State) ->
- {Tester, ServerPath} =
- ?SEV_AWAIT_START(),
+ {Tester, ServerPath} = ?SEV_AWAIT_START(),
?SEV_IPRINT("started with server info: "
"~n Path: ~p", [ServerPath]),
{ok, State#{tester => Tester,
@@ -7090,15 +11852,16 @@ ttest_tcp(InitState) ->
%% *** Init part ***
- #{desc => "create node",
- cmd => fun(#{remote := true, host := _Host} = State) ->
- %% Because peer does not accept a host argument,
- %% we can no longer start "remote" nodes...
- %% Not that we actually did that. We always
- %% used local-host.
+ #{desc => "(maybe) create node",
+ cmd => fun(#{remote := true} = State) ->
+ ?SEV_IPRINT("start 'client' node"),
{Peer, Node} = start_node("client"),
+ ?SEV_IPRINT("client node created:"
+ "~n Peer: ~p"
+ "~n Node: ~p", [Peer, Node]),
{ok, State#{peer => Peer, node => Node}};
(State) ->
+ ?SEV_IPRINT("use local node for client"),
{ok, State#{peer => undefined, node => node()}}
end},
#{desc => "(maybe) monitor client node",
@@ -7223,7 +11986,8 @@ ttest_tcp(InitState) ->
end
end},
#{desc => "(maybe) stop (client) node",
- cmd => fun(#{peer := Peer} = State) when (Peer =/= undefined) ->
+ cmd => fun(#{peer := Peer,
+ node := _Node} = State) when (Peer =/= undefined) ->
{ok,
try peer:stop(Peer) of
ok ->
@@ -7461,7 +12225,8 @@ ttest_tcp(InitState) ->
addr => LAddr,
domain => Domain,
mod => maps:get(server_mod, InitState),
- active => maps:get(server_active, InitState)},
+ active => maps:get(server_active, InitState),
+ remote => maps:get(remote, InitState)},
Server = ?SEV_START("server", ServerSeq, ServerInitState),
i("start client evaluator"),
@@ -7472,7 +12237,8 @@ ttest_tcp(InitState) ->
active => maps:get(client_active, InitState),
msg_id => maps:get(msg_id, InitState),
max_outstanding => maps:get(max_outstanding, InitState),
- runtime => maps:get(runtime, InitState)},
+ runtime => maps:get(runtime, InitState),
+ remote => maps:get(remote, InitState)},
Client = ?SEV_START("client", ClientSeq, ClientInitState),
i("start 'tester' evaluator"),
@@ -7484,7 +12250,8 @@ ttest_tcp(InitState) ->
client_active => maps:get(client_active, InitState),
server => Server#ev.pid,
server_mod => maps:get(server_mod, InitState),
- server_active => maps:get(server_active, InitState)},
+ server_active => maps:get(server_active, InitState),
+ remote => maps:get(remote, InitState)},
#ev{pid = TesterPid} = Tester =
?SEV_START("tester", TesterSeq, TesterInitState),
@@ -7886,20 +12653,26 @@ tc_try(Case, TCCondFun, TCFun) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-start_node(Name) ->
+start_node(Name) ->
start_node(Name, 5000).
start_node(Name, Timeout) when is_integer(Timeout) andalso (Timeout > 0) ->
Pa = filename:dirname(code:which(?MODULE)),
Args = ["-pa", Pa,
"-s", atom_to_list(?PROXY), "start", atom_to_list(node()),
+ "-s", atom_to_list(kernel_test_sys_monitor), "start",
"-s", "global", "sync"],
+ ?SEV_IPRINT("try start node ~p", [Name]),
try ?CT_PEER(#{name => Name,
wait_boot => Timeout,
+ %% connection => standard_io,
args => Args}) of
{ok, Peer, Node} ->
- ?SEV_IPRINT("Started node ~p - now (global) sync", [Name]),
- global:sync(), % Again, just in case...
+ ?SEV_IPRINT("Started node: "
+ "~n Peer: ~p"
+ "~n Node: ~p"
+ "~n => await global synced", [Peer, Node]),
+ await_sys_monitor_synced(Node),
?SEV_IPRINT("ping proxy"),
pong = ?PPING(Node),
{Peer, Node};
@@ -7918,6 +12691,18 @@ start_node(Name, Timeout) when is_integer(Timeout) andalso (Timeout > 0) ->
end.
+await_sys_monitor_synced(Node) ->
+ i("check if system monitor on node ~p is running", [Node]),
+ case kernel_test_sys_monitor:ping(Node) of
+ pong ->
+ ok;
+ pang ->
+ i("system monitor on node ~p not yet synced", [Node]),
+ receive after 1000 -> ok end,
+ await_sys_monitor_synced(Node)
+ end.
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
i(F) ->
--
2.43.0