File 4601-ssl-Use-new-map-syntax-for-supervisors.patch of Package erlang

From f2f20b4e4ebc23b1225255b99761cedcfef08207 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 27 Oct 2021 15:26:04 +0200
Subject: [PATCH 1/2] ssl: Use new map syntax for supervisors

---
 lib/ssl/src/dtls_connection_sup.erl           | 28 +++----
 lib/ssl/src/dtls_listener_sup.erl             | 29 ++++---
 lib/ssl/src/dtls_server_session_cache_sup.erl | 27 +++----
 lib/ssl/src/dtls_server_sup.erl               | 47 +++++------
 lib/ssl/src/dtls_sup.erl                      | 47 +++++------
 lib/ssl/src/ssl_admin_sup.erl                 | 57 ++++++-------
 lib/ssl/src/ssl_connection_sup.erl            | 41 +++++-----
 lib/ssl/src/ssl_dist_admin_sup.erl            | 42 +++++-----
 lib/ssl/src/ssl_dist_connection_sup.erl       | 23 +++---
 lib/ssl/src/ssl_dist_sup.erl                  | 40 ++++-----
 lib/ssl/src/ssl_listen_tracker_sup.erl        | 27 +++----
 lib/ssl/src/ssl_server_session_cache_sup.erl  | 29 +++----
 lib/ssl/src/ssl_sup.erl                       | 43 +++++-----
 .../ssl_upgrade_server_session_cache_sup.erl  | 27 +++----
 lib/ssl/src/tls_connection_sup.erl            | 27 +++----
 lib/ssl/src/tls_dist_server_sup.erl           | 63 +++++++--------
 lib/ssl/src/tls_dist_sup.erl                  | 46 ++++++-----
 lib/ssl/src/tls_server_session_ticket_sup.erl | 28 +++----
 lib/ssl/src/tls_server_sup.erl                | 81 ++++++++++---------
 lib/ssl/src/tls_sup.erl                       | 43 +++++-----
 20 files changed, 399 insertions(+), 396 deletions(-)

diff --git a/lib/ssl/src/dtls_connection_sup.erl b/lib/ssl/src/dtls_connection_sup.erl
index 4c5c0a490f..b2b9708209 100644
--- a/lib/ssl/src/dtls_connection_sup.erl
+++ b/lib/ssl/src/dtls_connection_sup.erl
@@ -51,17 +51,17 @@ start_child_dist(Args) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {ssl_gen_statem, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [ssl_gen_statem, dtls_connection],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->    
+    SupFlags = #{strategy  => simple_one_for_one,
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {ssl_gen_statem, start_link, []},
+                    restart  => temporary,
+                    shutdown => 4000,
+                    modules  => [ssl_gen_statem, dtls_connection],
+                    type     => worker
+                   }
+                 ], 
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/dtls_listener_sup.erl b/lib/ssl/src/dtls_listener_sup.erl
index 4f46407290..699f27b95f 100644
--- a/lib/ssl/src/dtls_listener_sup.erl
+++ b/lib/ssl/src/dtls_listener_sup.erl
@@ -76,18 +76,17 @@ register_listener(OwnerAndListner, IP, Port) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    ets:new(dtls_listener_sup, [named_table, public, set]),
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {dtls_packet_demux, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [dtls_packet_demux],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->
+    ets:new(dtls_listener_sup, [named_table, public, set]),    
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {dtls_packet_demux, start_link, []},
+                    restart  => temporary, 
+                    shutdown => 4000,
+                    modules  => [dtls_packet_demux],
+                    type     => worker
+                   }],     
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/dtls_server_session_cache_sup.erl b/lib/ssl/src/dtls_server_session_cache_sup.erl
index 65fbb34918..c0242ab2c0 100644
--- a/lib/ssl/src/dtls_server_session_cache_sup.erl
+++ b/lib/ssl/src/dtls_server_session_cache_sup.erl
@@ -47,17 +47,16 @@ start_child(Listener) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {ssl_server_session_cache, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [ssl_server_session_cache],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {ssl_server_session_cache, start_link, []},
+                    restart  => temporary, 
+                    shutdown => 4000,
+                    modules  => [ssl_server_session_cache],
+                    type     => worker
+                   }], 
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/dtls_server_sup.erl b/lib/ssl/src/dtls_server_sup.erl
index 7ec6db3984..1430627cf2 100644
--- a/lib/ssl/src/dtls_server_sup.erl
+++ b/lib/ssl/src/dtls_server_sup.erl
@@ -43,33 +43,34 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->
-    DTLSListeners = dtls_listeners_spec(),
-    %% Add SessionTracker if we add DTLS-1.3
-    Pre_1_3SessionTracker = ssl_server_session_child_spec(),
-    
-    {ok, {{one_for_all, 10, 3600}, [DTLSListeners,
-                                    Pre_1_3SessionTracker
-				   ]}}.
-
+init([]) ->    
+    SupFlags = #{strategy  => one_for_all,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [dtls_listeners_spec(),
+                  ssl_server_session_child_spec()
+                  %% TODO Add DTLS-1.3 session ticket handling
+                 ], 
+    {ok, {SupFlags, ChildSpecs}}.
 
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 dtls_listeners_spec() ->
-    Name = dtls_listener,  
-    StartFunc = {dtls_listener_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => dtls_listener_sup,
+      start    => {dtls_listener_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [dtls_listener_sup],
+      type     => supervisor
+     }.
 
 ssl_server_session_child_spec() ->
-    Name = dtls_server_session_cache_sup,  
-    StartFunc = {dtls_server_session_cache_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [dtls_server_session_cache_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => dtls_server_session_cache_sup,
+      start    => {dtls_server_session_cache_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [dtls_server_session_cache_sup],
+      type     => supervisor
+     }.
diff --git a/lib/ssl/src/dtls_sup.erl b/lib/ssl/src/dtls_sup.erl
index acc4415a9f..2b73f13e19 100644
--- a/lib/ssl/src/dtls_sup.erl
+++ b/lib/ssl/src/dtls_sup.erl
@@ -44,33 +44,30 @@ start_link() ->
 %%%=========================================================================
 
 init([]) ->    
-    DTLSConnectionManager = dtls_connection_manager_child_spec(),
-    DTLSServers = dtls_server_spec(),
-    
-    {ok, {{one_for_one, 10, 3600}, [DTLSConnectionManager, 
-				    DTLSServers
-				   ]}}.
+    SupFlags = #{strategy  => one_for_one, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    Children = [dtls_connection_child_spec(), server_instance_child_spec()],    
+    {ok, {SupFlags, Children}}.
 
-    
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
-dtls_server_spec() ->
-    Name = dtls_servers,
-    StartFunc = {dtls_server_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [dtls_server_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
-dtls_connection_manager_child_spec() ->
-    Name = dtls_connection,
-    StartFunc = {dtls_connection_sup, start_link, []},
-    Restart = permanent,
-
-    Shutdown = 4000,
-    Modules = [dtls_connection_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+dtls_connection_child_spec() ->
+    #{id       => dtls_connection_sup,
+      start    => {dtls_connection_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [dtls_connection_sup],
+      type     => supervisor
+     }.
 
+server_instance_child_spec() ->
+    #{id       => dtls_server_sup,
+      start    => {dtls_server_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [dtls_server_sup],
+      type     => supervisor
+     }.
diff --git a/lib/ssl/src/ssl_admin_sup.erl b/lib/ssl/src/ssl_admin_sup.erl
index 0cf2ab6332..9c10bf7b41 100644
--- a/lib/ssl/src/ssl_admin_sup.erl
+++ b/lib/ssl/src/ssl_admin_sup.erl
@@ -43,11 +43,15 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->    
-    PEMCache = pem_cache_child_spec(),
-    SessionCertManager = session_and_cert_manager_child_spec(),
-    TicketStore = ticket_store_spec(),
-    {ok, {{rest_for_one, 10, 3600}, [PEMCache, SessionCertManager, TicketStore]}}.
+init([]) ->
+    SupFlags = #{strategy  => rest_for_one, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [pem_cache_child_spec(), 
+                  session_and_cert_manager_child_spec(),
+                  ticket_store_spec()],    
+    {ok, {SupFlags, ChildSpecs}}.
 
 manager_opts() ->
     CbOpts = case application:get_env(ssl, session_cb) of
@@ -69,34 +73,33 @@ manager_opts() ->
 %%--------------------------------------------------------------------
 
 pem_cache_child_spec() ->
-    Name = ssl_pem_cache,  
-    StartFunc = {ssl_pem_cache, start_link, [[]]},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_pem_cache],
-    Type = worker,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => ssl_pem_cache,
+      start    => {ssl_pem_cache, start_link, [[]]},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_pem_cache],
+      type     => worker
+     }.
 session_and_cert_manager_child_spec() ->
     Opts = manager_opts(),
-    Name = ssl_manager,  
-    StartFunc = {ssl_manager, start_link, [Opts]},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_manager],
-    Type = worker,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => ssl_manager,
+      start    => {ssl_manager, start_link, [Opts]},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_manager],
+      type     => worker
+     }.
 
 ticket_store_spec() ->
-    Name = tls_client_ticket_store,
     Size = client_session_ticket_store_size(),
     Lifetime = client_session_ticket_lifetime(),
-    StartFunc = {tls_client_ticket_store, start_link, [Size,Lifetime]},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [tls_client_ticket_store],
-    Type = worker,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_client_ticket_store,
+      start    => {tls_client_ticket_store, start_link, [Size, Lifetime]},
+      restart  => permanent,
+      shutdown => 4000,
+      modules  => [tls_client_ticket_store],
+      type     => worker
+     }.
 
 session_cb_init_args() ->
     case application:get_env(ssl, session_cb_init_args) of
diff --git a/lib/ssl/src/ssl_connection_sup.erl b/lib/ssl/src/ssl_connection_sup.erl
index d930ecf2fa..f5d170934c 100644
--- a/lib/ssl/src/ssl_connection_sup.erl
+++ b/lib/ssl/src/ssl_connection_sup.erl
@@ -44,32 +44,33 @@ start_link() ->
 %%%=========================================================================
 
 init([]) ->    
-  
-    TLSSup = tls_sup_child_spec(),
-    DTLSSup = dtls_sup_child_spec(),
-
-    {ok, {{one_for_one, 10, 3600}, [TLSSup, DTLSSup]}}.
+    ChildSpecs = [tls_sup_child_spec(), dtls_sup_child_spec()],
+    SupFlags = #{strategy  => one_for_one,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    {ok, {SupFlags, ChildSpecs}}.
 
+  
     
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 
 tls_sup_child_spec() ->
-    Name = tls_sup,  
-    StartFunc = {tls_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id => tls_sup,
+      start => {tls_sup, start_link, []},
+      restart => permanent,
+      shutdown => 4000,
+      modules => [tls_sup],
+      type => supervisor
+     }.
 
 dtls_sup_child_spec() ->
-    Name = dtls_sup,
-    StartFunc = {dtls_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [dtls_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id => dtls_sup,
+      start => {dtls_sup, start_link, []},
+      restart => permanent,
+      shutdown => 4000,
+      modules => [dtls_sup],
+      type => supervisor
+     }.
diff --git a/lib/ssl/src/ssl_dist_admin_sup.erl b/lib/ssl/src/ssl_dist_admin_sup.erl
index f60806c4cb..3e10643dcd 100644
--- a/lib/ssl/src/ssl_dist_admin_sup.erl
+++ b/lib/ssl/src/ssl_dist_admin_sup.erl
@@ -44,31 +44,31 @@ start_link() ->
 %%%=========================================================================
 
 init([]) ->    
-    PEMCache = pem_cache_child_spec(),
-    SessionCertManager = session_and_cert_manager_child_spec(),
-    {ok, {{rest_for_one, 10, 3600}, [PEMCache, SessionCertManager]}}.
-
-
+    ChildSpecs = [pem_cache_child_spec(), 
+                  session_and_cert_manager_child_spec()], 
+    SupFlags = #{strategy  => rest_for_one, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    {ok, {SupFlags, ChildSpecs}}.
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 
 pem_cache_child_spec() ->
-    Name = ssl_pem_cache_dist,  
-    StartFunc = {ssl_pem_cache, start_link_dist, [[]]},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_pem_cache],
-    Type = worker,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id        => ssl_pem_cache_dist,
+      start     => {ssl_pem_cache, start_link_dist, [[]]},
+      restart   => permanent, 
+      shutdown  => 4000,
+      modules   => [ssl_pem_cache],
+      type      => worker
+     }.
 session_and_cert_manager_child_spec() ->
     Opts = ssl_admin_sup:manager_opts(),
-    Name = ssl_dist_manager,  
-    StartFunc = {ssl_manager, start_link_dist, [Opts]},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_manager],
-    Type = worker,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => ssl_dist_manager,
+      start    => {ssl_manager, start_link_dist, [Opts]},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_manager],
+      type     => worker
+     }.
diff --git a/lib/ssl/src/ssl_dist_connection_sup.erl b/lib/ssl/src/ssl_dist_connection_sup.erl
index 441a7577be..47c467b358 100644
--- a/lib/ssl/src/ssl_dist_connection_sup.erl
+++ b/lib/ssl/src/ssl_dist_connection_sup.erl
@@ -43,19 +43,22 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 init([]) ->    
-    TLSSup = tls_sup_child_spec(),
-    {ok, {{one_for_one, 10, 3600}, [TLSSup]}}.
+    SupFlags = #{strategy  => one_for_one, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [tls_sup_child_spec()], 
+    {ok, {SupFlags, ChildSpecs}}.
 
-    
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 
 tls_sup_child_spec() ->
-    Name = dist_tls_sup,  
-    StartFunc = {tls_dist_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_dist_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_dist_sup,
+      start    => {tls_dist_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_dist_sup],
+      type     => supervisor
+     }.
diff --git a/lib/ssl/src/ssl_dist_sup.erl b/lib/ssl/src/ssl_dist_sup.erl
index ae0887c3d9..74e4775413 100644
--- a/lib/ssl/src/ssl_dist_sup.erl
+++ b/lib/ssl/src/ssl_dist_sup.erl
@@ -58,30 +58,34 @@ start_link() ->
 %%%=========================================================================
 
 init([]) ->    
-    AdminSup = ssl_admin_child_spec(),
-    ConnectionSup = ssl_connection_sup(),
-    {ok, {{one_for_all, 10, 3600}, [AdminSup, ConnectionSup]}}.
+    SupFlags = #{strategy  => one_for_all, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [ssl_admin_child_spec(),
+                  ssl_connection_sup()], 
+    {ok, {SupFlags, ChildSpecs}}.
 
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 ssl_admin_child_spec() ->
-    Name = ssl_dist_admin_sup,  
-    StartFunc = {ssl_dist_admin_sup, start_link , []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_dist_admin_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => ssl_dist_admin_sup,
+      start    =>  {ssl_dist_admin_sup, start_link , []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_dist_admin_sup],
+      type     => supervisor
+     }.
+    
 ssl_connection_sup() ->
-    Name = tls_dist_sup,
-    StartFunc = {tls_dist_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [tls_dist_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_dist_sup,
+      start    => {tls_dist_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_dist_sup],
+      type     => supervisor
+     }.
 
 consult(File) ->
     case erl_prim_loader:get_file(File) of
diff --git a/lib/ssl/src/ssl_listen_tracker_sup.erl b/lib/ssl/src/ssl_listen_tracker_sup.erl
index 6afd1c0009..998ec5fbc3 100644
--- a/lib/ssl/src/ssl_listen_tracker_sup.erl
+++ b/lib/ssl/src/ssl_listen_tracker_sup.erl
@@ -51,20 +51,19 @@ start_child_dist(Args) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {tls_socket, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [tls_socket],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {tls_socket, start_link, []},
+                    restart  => temporary, 
+                    shutdown => 4000,
+                    modules  => [tls_socket],
+                    type     => worker
+                   }],    
+    {ok, {SupFlags, ChildSpecs}}.
 
 tracker_name(normal) ->
     ?MODULE;
diff --git a/lib/ssl/src/ssl_server_session_cache_sup.erl b/lib/ssl/src/ssl_server_session_cache_sup.erl
index 88f068a319..80868215d8 100644
--- a/lib/ssl/src/ssl_server_session_cache_sup.erl
+++ b/lib/ssl/src/ssl_server_session_cache_sup.erl
@@ -44,22 +44,19 @@ start_link() ->
 start_child(Listener) ->
     supervisor:start_child(?MODULE, [Listener | [ssl_config:pre_1_3_session_opts(server)]]).
 
-
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 3,
-    MaxT = 3600,
-
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {ssl_server_session_cache, start_link, []},
-    Restart = transient, % Should be restarted only on abnormal termination
-    Shutdown = 4000,
-    Modules = [ssl_server_session_cache],
-    Type = worker,
-
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
-
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   3,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {ssl_server_session_cache, start_link, []},
+                    restart  => transient, 
+                    shutdown => 4000,
+                    modules  => [ssl_server_session_cache],
+                    type     => worker
+                   }],   
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/ssl_sup.erl b/lib/ssl/src/ssl_sup.erl
index 05a7aaaa82..1c38eae433 100644
--- a/lib/ssl/src/ssl_sup.erl
+++ b/lib/ssl/src/ssl_sup.erl
@@ -43,29 +43,32 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->    
-    {ok, {{rest_for_one, 10, 3600}, [ssl_admin_child_spec(),
-				     ssl_connection_sup()
-				    ]}}.
+init([]) ->  
+    SupFlags = #{strategy  => rest_for_one,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [ssl_admin_child_spec(),
+                  ssl_connection_sup()],    
+    {ok, {SupFlags, ChildSpecs}}.
 
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 ssl_admin_child_spec() ->
-    Name = ssl_admin_sup,  
-    StartFunc = {ssl_admin_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_admin_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => ssl_admin_sup,
+      start    =>  {ssl_admin_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_admin_sup],
+      type     => supervisor
+      }.
+  
 ssl_connection_sup() ->
-    Name = ssl_connection_sup,
-    StartFunc = {ssl_connection_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [ssl_connection_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id        => ssl_connection_sup,
+      start     =>  {ssl_connection_sup, start_link, []},
+      restart   => permanent, 
+      shutdown  => 4000,
+      modules   => [ssl_connection_sup],
+      type      => supervisor
+     }.
diff --git a/lib/ssl/src/ssl_upgrade_server_session_cache_sup.erl b/lib/ssl/src/ssl_upgrade_server_session_cache_sup.erl
index 69169cca0d..62f1e8e4f1 100644
--- a/lib/ssl/src/ssl_upgrade_server_session_cache_sup.erl
+++ b/lib/ssl/src/ssl_upgrade_server_session_cache_sup.erl
@@ -69,20 +69,19 @@ start_child(Type) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 3,
-    MaxT = 3600,
-
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {ssl_server_session_cache, start_link, []},
-    Restart = transient, % Should be restarted only on abnormal termination
-    Shutdown = 4000,
-    Modules = [ssl_server_session_cache],
-    Type = worker,
-
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   3,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    =>  {ssl_server_session_cache, start_link, []},
+                    restart  => transient, 
+                    shutdown => 4000,
+                    modules  => [ssl_server_session_cache],
+                    type     => worker
+                   }],     
+    {ok, {SupFlags, ChildSpecs}}.
 
 sup_name(normal) ->
     ?MODULE;
diff --git a/lib/ssl/src/tls_connection_sup.erl b/lib/ssl/src/tls_connection_sup.erl
index b7f80ad524..e08e682534 100644
--- a/lib/ssl/src/tls_connection_sup.erl
+++ b/lib/ssl/src/tls_connection_sup.erl
@@ -51,17 +51,16 @@ start_child_dist(Args) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {ssl_gen_statem, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [ssl_gen_statem, tls_connection, tls_connection_1_3],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {ssl_gen_statem, start_link, []},
+                    restart  => temporary, 
+                    shutdown => 4000,
+                    modules  => [ssl_gen_statem, tls_connection, tls_connection_1_3],
+                    type     => worker
+                   }],    
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/tls_dist_server_sup.erl b/lib/ssl/src/tls_dist_server_sup.erl
index 96603a7495..9560d05158 100644
--- a/lib/ssl/src/tls_dist_server_sup.erl
+++ b/lib/ssl/src/tls_dist_server_sup.erl
@@ -43,16 +43,16 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->    
-    ListenTracker = listen_options_tracker_child_spec(),
-    SessionTracker = tls_server_session_child_spec(),
-    Pre_1_3SessionTracker = ssl_server_session_child_spec(),
-    
-    {ok, {{one_for_all, 10, 3600}, [ListenTracker, 
-				    SessionTracker,
-                                    Pre_1_3SessionTracker
-				   ]}}.
-
+init([]) ->  
+    SupFlags = #{strategy  => one_for_all,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [listen_options_tracker_child_spec(), 
+                  tls_server_session_child_spec(),
+                  ssl_server_session_child_spec()],
+    {ok, {SupFlags, ChildSpecs}}.
+ 
 
 %%--------------------------------------------------------------------
 %%% Internal functions
@@ -61,29 +61,28 @@ init([]) ->
 %% Handles emulated options so that they inherited by the accept
 %% socket, even when setopts is performed on the listen socket
 listen_options_tracker_child_spec() ->
-    Name = dist_tls_socket,  
-    StartFunc = {ssl_listen_tracker_sup, start_link_dist, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_listen_tracker_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => dist_ssl_listen_tracker_sup,
+      start    => {ssl_listen_tracker_sup, start_link_dist, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_listen_tracker_sup],
+      type     => supervisor
+     }.
 
 tls_server_session_child_spec() ->
-    Name = dist_tls_server_session_ticket,  
-    StartFunc = {tls_server_session_ticket_sup, start_link_dist, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_server_session_ticket_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => dist_tls_server_session_ticket,
+      start    => {tls_server_session_ticket_sup, start_link_dist, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_server_session_ticket_sup],
+      type     => supervisor
+     }.
 
 ssl_server_session_child_spec() ->
-    Name = dist_ssl_server_session_cache_sup,
-    StartFunc = {ssl_upgrade_server_session_cache_sup, start_link_dist, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [ssl_server_session_cache_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => dist_ssl_upgrade_server_session_cache_sup,
+      start    => {ssl_upgrade_server_session_cache_sup, start_link_dist, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_upgrade_server_session_cache_sup],
+      type     => supervisor
+     }.
diff --git a/lib/ssl/src/tls_dist_sup.erl b/lib/ssl/src/tls_dist_sup.erl
index 54e0a6a514..ebff741f9b 100644
--- a/lib/ssl/src/tls_dist_sup.erl
+++ b/lib/ssl/src/tls_dist_sup.erl
@@ -44,32 +44,34 @@ start_link() ->
 %%%=========================================================================
 
 init([]) ->    
-  
-    TLSConnetionSup = tls_connection_child_spec(),
-    ServerInstanceSup = server_instance_child_spec(), 
-
-    {ok, {{one_for_one, 10, 3600}, [TLSConnetionSup, 
-				    ServerInstanceSup
-				   ]}}.
+    SupFlags = #{strategy  => one_for_one,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    ChildSpecs = [tls_connection_child_spec(),
+                  server_instance_child_spec()
+                 ],     
+    {ok, {SupFlags, ChildSpecs}}.
 
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
 
 tls_connection_child_spec() ->
-    Name = dist_tls_connection,  
-    StartFunc = {tls_connection_sup, start_link_dist, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_connection_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
-
+    #{id       => dist_tls_connection_sup,
+      start    => {tls_connection_sup, start_link_dist, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_connection_sup],
+      type     => supervisor
+     }.
+ 
 server_instance_child_spec() ->
-    Name = dist_tls_server_sup,  
-    StartFunc = {tls_dist_server_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_dist_server_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_dist_server_sup,
+      start    => {tls_dist_server_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_dist_server_sup],
+      type     => supervisor
+     }.
+
diff --git a/lib/ssl/src/tls_server_session_ticket_sup.erl b/lib/ssl/src/tls_server_session_ticket_sup.erl
index bdde94ecea..a515e8bbe0 100644
--- a/lib/ssl/src/tls_server_session_ticket_sup.erl
+++ b/lib/ssl/src/tls_server_session_ticket_sup.erl
@@ -59,18 +59,16 @@ sup_name(dist) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init(_O) ->
-    RestartStrategy = simple_one_for_one,
-    MaxR = 0,
-    MaxT = 3600,
-   
-    Name = undefined, % As simple_one_for_one is used.
-    StartFunc = {tls_server_session_ticket, start_link, []},
-    Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
-    Modules = [tls_server_session_ticket],
-    Type = worker,
-    
-    ChildSpec = {Name, StartFunc, Restart, Shutdown, Type, Modules},
-    {ok, {{RestartStrategy, MaxR, MaxT}, [ChildSpec]}}.
-
+init(_) ->
+    SupFlags = #{strategy  => simple_one_for_one, 
+                 intensity =>   0,
+                 period    => 3600
+                },
+    ChildSpecs = [#{id       => undefined,
+                    start    => {tls_server_session_ticket, start_link, []},
+                    restart  => transient, 
+                    shutdown => 4000,
+                    modules  => [tls_server_session_ticket],
+                    type     => worker
+                   }], 
+    {ok, {SupFlags, ChildSpecs}}.
diff --git a/lib/ssl/src/tls_server_sup.erl b/lib/ssl/src/tls_server_sup.erl
index b2f011f221..7f739ed015 100644
--- a/lib/ssl/src/tls_server_sup.erl
+++ b/lib/ssl/src/tls_server_sup.erl
@@ -43,18 +43,19 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->    
-    ListenTracker = listen_options_tracker_child_spec(),
-    SessionTracker = tls_server_session_child_spec(),
-    Pre_1_3SessionTracker = ssl_server_session_child_spec(),
-    Pre_1_3UpgradeSessionTracker = ssl_upgrade_server_session_child_spec(),
-
-    {ok, {{one_for_all, 10, 3600}, [ListenTracker, 
-				    SessionTracker,
-                                    Pre_1_3SessionTracker,
-                                    Pre_1_3UpgradeSessionTracker
-				   ]}}.
-
+init([]) ->  
+    ChildSpecs = [listen_options_tracker_child_spec(),
+                tls_server_session_child_spec(), %% TLS-1.3 Session ticket handling
+                ssl_server_session_child_spec(), %% PRE TLS-1.3 session handling
+                ssl_upgrade_server_session_child_spec() %% PRE TLS-1.3 session handling for upgrade servers
+               ], 
+    SupFlags = #{strategy  => one_for_all,
+                 intensity =>   10,
+                 period    => 3600
+                },
+    {ok, {SupFlags, ChildSpecs}}.
+
+   
 
 %%--------------------------------------------------------------------
 %%% Internal functions
@@ -63,37 +64,37 @@ init([]) ->
 %% Handles emulated options so that they inherited by the accept
 %% socket, even when setopts is performed on the listen socket
 listen_options_tracker_child_spec() ->
-    Name = tls_socket,  
-    StartFunc = {ssl_listen_tracker_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [ssl_listen_tracker_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => ssl_listen_tracker_sup,
+      start    => {ssl_listen_tracker_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_listen_tracker_sup],
+      type     => supervisor
+     }.
 
 tls_server_session_child_spec() ->
-    Name = tls_server_session_ticket,  
-    StartFunc = {tls_server_session_ticket_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_server_session_ticket_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_server_session_ticket,
+      start    => {tls_server_session_ticket_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_server_session_ticket_sup],
+      type     => supervisor
+     }.
 
 ssl_server_session_child_spec() ->
-    Name = ssl_server_session_cache_sup,
-    StartFunc = {ssl_server_session_cache_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [ssl_server_session_cache_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => ssl_server_session_cache_sup,
+      start    => {ssl_server_session_cache_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_server_session_cache_sup],
+      type     => supervisor
+     }.
 
 ssl_upgrade_server_session_child_spec() ->
-    Name = ssl_upgrade_server_session_cache_sup,
-    StartFunc = {ssl_upgrade_server_session_cache_sup, start_link, []},
-    Restart = permanent,
-    Shutdown = 4000,
-    Modules = [ssl_upgrade_server_session_cache_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => ssl_upgrade_server_session_cache_sup,
+      start    => {ssl_upgrade_server_session_cache_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [ssl_upgrade_server_session_cache_sup],
+      type     => supervisor
+     }.
diff --git a/lib/ssl/src/tls_sup.erl b/lib/ssl/src/tls_sup.erl
index a425ae31e2..cafc563943 100644
--- a/lib/ssl/src/tls_sup.erl
+++ b/lib/ssl/src/tls_sup.erl
@@ -43,14 +43,13 @@ start_link() ->
 %%%  Supervisor callback
 %%%=========================================================================
 
-init([]) ->    
-  
-    TLSConnetionSup = tls_connection_child_spec(),
-    ServerInstanceSup = server_instance_child_spec(), 
-
-    {ok, {{one_for_one, 10, 3600}, [TLSConnetionSup, 
-				    ServerInstanceSup
-				   ]}}.
+init([]) ->      
+    ChildSpecs = [tls_connection_child_spec(), server_instance_child_spec()], 
+    SupFlags = #{strategy  => one_for_one, 
+                 intensity =>   10,
+                 period    => 3600
+                },
+    {ok, {SupFlags, ChildSpecs}}.
 
 
 %%--------------------------------------------------------------------
@@ -58,19 +57,19 @@ init([]) ->
 %%--------------------------------------------------------------------
 
 tls_connection_child_spec() ->
-    Name = tls_connection,  
-    StartFunc = {tls_connection_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_connection_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_connection_sup,
+      start    => {tls_connection_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_connection_sup],
+      type     => supervisor
+     }.
 
 server_instance_child_spec() ->
-    Name = tls_server_sup,  
-    StartFunc = {tls_server_sup, start_link, []},
-    Restart = permanent, 
-    Shutdown = 4000,
-    Modules = [tls_server_sup],
-    Type = supervisor,
-    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
+    #{id       => tls_server_sup,
+      start    => {tls_server_sup, start_link, []},
+      restart  => permanent, 
+      shutdown => 4000,
+      modules  => [tls_server_sup],
+      type     => supervisor
+     }.
-- 
2.31.1

openSUSE Build Service is sponsored by