File 0602-ssl-Enhance-session-max-table-testing.patch of Package erlang

From 5d4fdbe6c5933199718e48d3b5dd743aeef2a28e Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Tue, 24 Aug 2021 13:51:05 +0200
Subject: [PATCH] ssl: Enhance session max table testing

---
 lib/ssl/test/ssl_session_SUITE.erl       | 33 +++++++++++++++++++++---
 lib/ssl/test/ssl_session_cache_SUITE.erl | 24 ++++++++---------
 2 files changed, 40 insertions(+), 17 deletions(-)

diff --git a/lib/ssl/test/ssl_session_SUITE.erl b/lib/ssl/test/ssl_session_SUITE.erl
index 57e8944fe2..33a455bf77 100644
--- a/lib/ssl/test/ssl_session_SUITE.erl
+++ b/lib/ssl/test/ssl_session_SUITE.erl
@@ -63,6 +63,7 @@
 
 -define(SLEEP, 500).
 -define(EXPIRE, 10).
+-define(CLIENT_CB, ssl_client_session_cache_db).
 
 %%--------------------------------------------------------------------
 %% Common Test interface functions -----------------------------------
@@ -453,22 +454,36 @@ no_reuses_session_server_restart_new_cert_file(Config) when is_list(Config) ->
 
 
 client_max_session_table() ->
-      [{doc, "Check that max session table limit handling set max to 1 in init_per_testcase"}].
+      [{doc, "Check that max session table limit is not exceeded, set max to 2 in init_per_testcase"}].
 
 client_max_session_table(Config) when is_list(Config)->
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
     {ClientNode, ServerNode, HostName} = ssl_test_lib:run_where(Config),
-    test_max_session_limit(ClientOpts,ServerOpts,ClientNode, ServerNode, HostName).
+    test_max_session_limit(ClientOpts,ServerOpts,ClientNode, ServerNode, HostName),    
+    %% Explicit check table size
+    {status, _, _, StatusInfo} = sys:get_status(whereis(ssl_manager)),
+    [_, _,_, _, Prop] = StatusInfo,
+    State = ssl_test_lib:state(Prop),
+    ClientCache = element(2, State),	
+    2 = ?CLIENT_CB:size(ClientCache).
     
 server_max_session_table() ->
-      [{doc, "Check that max session table limit handling set max to 1 in init_per_testcase"}].
+      [{doc, "Check that max session table limit exceeded, set max to 2 in init_per_testcase"}].
 
 server_max_session_table(Config) when is_list(Config)->
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
     {ClientNode, ServerNode, HostName} = ssl_test_lib:run_where(Config),
-    test_max_session_limit(ClientOpts,ServerOpts,ClientNode, ServerNode, HostName).
+    test_max_session_limit(ClientOpts,ServerOpts,ClientNode, ServerNode, HostName),
+    %% Explicit check table size
+    SupName = sup_name(ServerOpts),
+    Sup = whereis(SupName),
+    %% Will only be one process, that is one server, in our test senario
+    [{_, SessionCachePid, worker,[ssl_server_session_cache]}] = supervisor:which_children(Sup),
+    {SessionCacheCb, SessionCacheDb} = session_cachce_info(SessionCachePid),
+    N = SessionCacheCb:size(SessionCacheDb),
+    true = N == 2.
 
 session_table_stable_size_on_tcp_close() ->
       [{doc, "Check that new sessions are cleanup when connection is closed abruptly during first handshake"}].
@@ -702,3 +717,13 @@ test_max_session_limit(ClientOpts, ServerOpts, ClientNode, ServerNode, HostName)
         Other  ->
             ct:fail({{expected, SID2}, {got,Other}})
     end.
+
+
+sup_name(Opts) ->
+   case proplists:get_value(protocol, Opts, tls) of
+       tls ->
+           ssl_server_session_cache_sup;
+       dtls ->
+           dtls_server_session_cache_sup
+   end.
+
diff --git a/lib/ssl/test/ssl_session_cache_SUITE.erl b/lib/ssl/test/ssl_session_cache_SUITE.erl
index 8f67908ad7..8b73bac1c6 100644
--- a/lib/ssl/test/ssl_session_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_session_cache_SUITE.erl
@@ -216,7 +216,7 @@ client_unique_session(Config) when is_list(Config) ->
 				   {tcp_options, [{active, false}]},
 				   {options, ServerOpts}]),
     Port = ssl_test_lib:inet_port(Server),
-    LastClient = clients_start(Server, ClientNode, Hostname, Port, ClientOpts, 20),
+    LastClient = clients_start(Server, ClientNode, Hostname, Port, ClientOpts, 20, []),
     receive 
 	{LastClient, {ok, _}} ->
 	    ok
@@ -370,18 +370,17 @@ max_table_size(Config) when is_list(Config) ->
 				   {options, ServerOpts}]),
     Port = ssl_test_lib:inet_port(Server),
     LastClient = clients_start(Server, 
-			    ClientNode, Hostname, Port, ClientOpts, 20),
+                               ClientNode, Hostname, Port, ClientOpts, 20, [{reuse_sessions, save}]),
     receive 
-	{LastClient, {ok, _}} ->
-	    ok
+        {LastClient, {ok, _}} ->
+            ok
     end,
-    ct:sleep(1000),
     {status, _, _, StatusInfo} = sys:get_status(whereis(ssl_manager)),
     [_, _,_, _, Prop] = StatusInfo,
     State = ssl_test_lib:state(Prop),
     ClientCache = element(2, State),	
     M = ?CLIENT_CB:size(ClientCache),
-    ct:pal("~p",[M]),
+    ct:pal("Cache size ~p",[M]),
     ssl_test_lib:close(Server, 500),
     ssl_test_lib:close(LastClient),
     true = M =< ?MAX_TABLE_SIZE.
@@ -551,22 +550,21 @@ session_cache_process(_Type,Config) when is_list(Config) ->
     ssl_test_lib:reuse_session(ClientOpts, ServerOpts, Config).
 
 
-clients_start(_Server, ClientNode, Hostname, Port, ClientOpts, 0) ->
-    %% Make sure session is registered
-    ct:sleep(?SLEEP * 2),
+clients_start(_Server, ClientNode, Hostname, Port, ClientOpts, 0, Opts) ->
     ssl_test_lib:start_client([{node, ClientNode},
 			       {port, Port}, {host, Hostname},
 			       {mfa, {?MODULE, connection_info_result, []}},
-			       {from, self()},  {options, ClientOpts}]);
-clients_start(Server, ClientNode, Hostname, Port, ClientOpts, N) ->
+                               %% Make sure session is registered    
+			       {from, self()},  {options, Opts ++ ClientOpts}]);
+clients_start(Server, ClientNode, Hostname, Port, ClientOpts, N, Opts) ->
     spawn_link(ssl_test_lib, start_client, 
 	       [[{node, ClientNode},
 		 {port, Port}, {host, Hostname},
 		 {mfa, {ssl_test_lib, no_result, []}},
-		 {from, self()},  {options, ClientOpts}]]),
+		 {from, self()},  {options, Opts ++ ClientOpts}]]),
     Server ! listen,
     wait_for_server(),
-    clients_start(Server, ClientNode, Hostname, Port, ClientOpts, N-1).
+    clients_start(Server, ClientNode, Hostname, Port, ClientOpts, N-1, Opts).
 	
 
 check_timer(Timer) ->
-- 
2.31.1

openSUSE Build Service is sponsored by