File 1207-Fix-typos-in-lib-ssl.patch of Package erlang

From a8b5f77c777e774d502047d85d76d9618c3c18e4 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Sat, 1 Jan 2022 18:29:11 +0800
Subject: [PATCH] Fix typos in lib/ssl

---
 lib/ssl/doc/src/notes.xml                     | 46 +++++++++----------
 lib/ssl/doc/src/ssl.xml                       |  2 +-
 lib/ssl/doc/src/ssl_crl_cache_api.xml         |  2 +-
 lib/ssl/doc/src/ssl_protocol.xml              |  2 +-
 lib/ssl/doc/src/using_ssl.xml                 |  2 +-
 lib/ssl/src/dtls_connection.hrl               |  2 +-
 lib/ssl/src/dtls_gen_connection.erl           |  4 +-
 lib/ssl/src/dtls_handshake.erl                |  6 +--
 lib/ssl/src/dtls_handshake.hrl                |  2 +-
 lib/ssl/src/dtls_packet_demux.erl             |  4 +-
 lib/ssl/src/dtls_record.hrl                   |  2 +-
 lib/ssl/src/dtls_socket.erl                   | 10 ++--
 lib/ssl/src/inet_tls_dist.erl                 |  6 +--
 lib/ssl/src/ssl.erl                           | 18 ++++----
 lib/ssl/src/ssl_alert.erl                     |  2 +-
 lib/ssl/src/ssl_alert.hrl                     |  2 +-
 lib/ssl/src/ssl_certificate.erl               | 10 ++--
 lib/ssl/src/ssl_cipher.erl                    |  8 ++--
 lib/ssl/src/ssl_cipher.hrl                    |  2 +-
 lib/ssl/src/ssl_cipher_format.erl             |  2 +-
 lib/ssl/src/ssl_connection.hrl                | 10 ++--
 lib/ssl/src/ssl_crl_hash_dir.erl              |  2 +-
 lib/ssl/src/ssl_gen_statem.erl                |  4 +-
 lib/ssl/src/ssl_handshake.erl                 | 12 ++---
 lib/ssl/src/ssl_handshake.hrl                 |  4 +-
 lib/ssl/src/ssl_manager.erl                   |  2 +-
 lib/ssl/src/ssl_pkix_db.erl                   |  4 +-
 lib/ssl/src/ssl_record.hrl                    |  6 +--
 lib/ssl/src/ssl_server_session_cache.erl      | 20 ++++----
 lib/ssl/src/ssl_server_session_cache_db.erl   |  4 +-
 lib/ssl/src/ssl_server_session_cache_sup.erl  |  4 +-
 lib/ssl/src/tls_dtls_connection.erl           | 14 +++---
 lib/ssl/src/tls_gen_connection.erl            | 10 ++--
 lib/ssl/src/tls_handshake.erl                 |  6 +--
 lib/ssl/src/tls_handshake.hrl                 |  2 +-
 lib/ssl/src/tls_handshake_1_3.erl             |  8 ++--
 lib/ssl/src/tls_handshake_1_3.hrl             |  4 +-
 lib/ssl/src/tls_record.hrl                    |  2 +-
 lib/ssl/src/tls_record_1_3.erl                |  2 +-
 lib/ssl/src/tls_record_1_3.hrl                |  2 +-
 lib/ssl/src/tls_sender.erl                    | 10 ++--
 lib/ssl/src/tls_server_session_ticket.erl     |  8 ++--
 lib/ssl/src/tls_socket.erl                    |  2 +-
 lib/ssl/test/dtls_api_SUITE.erl               |  6 +--
 lib/ssl/test/inet_crypto_dist.erl             |  4 +-
 lib/ssl/test/openssl_client_cert_SUITE.erl    |  6 +--
 lib/ssl/test/openssl_server_cert_SUITE.erl    | 10 ++--
 .../test/property_test/ssl_eqc_handshake.erl  |  2 +-
 lib/ssl/test/ssl_ECC.erl                      |  4 +-
 lib/ssl/test/ssl_ECC_SUITE.erl                |  4 +-
 lib/ssl/test/ssl_alert_SUITE.erl              |  4 +-
 lib/ssl/test/ssl_api_SUITE.erl                |  8 ++--
 lib/ssl/test/ssl_basic_SUITE.erl              |  6 +--
 lib/ssl/test/ssl_cert_SUITE.erl               |  2 +-
 lib/ssl/test/ssl_cert_tests.erl               |  6 +--
 lib/ssl/test/ssl_dist_SUITE.erl               |  2 +-
 lib/ssl/test/ssl_engine_SUITE.erl             |  4 +-
 lib/ssl/test/ssl_packet_SUITE.erl             |  2 +-
 lib/ssl/test/ssl_payload_SUITE.erl            |  2 +-
 lib/ssl/test/ssl_pem_cache_SUITE.erl          |  4 +-
 lib/ssl/test/ssl_reject_SUITE.erl             |  2 +-
 lib/ssl/test/ssl_session_SUITE.erl            |  2 +-
 lib/ssl/test/ssl_session_cache_SUITE.erl      |  2 +-
 lib/ssl/test/ssl_socket_SUITE.erl             |  2 +-
 lib/ssl/test/ssl_test_lib.erl                 |  8 ++--
 lib/ssl/test/tls_api_SUITE.erl                |  8 ++--
 66 files changed, 188 insertions(+), 188 deletions(-)

diff --git a/lib/ssl/doc/src/notes.xml b/lib/ssl/doc/src/notes.xml
index f5ac5dcbfc..96d2886995 100644
--- a/lib/ssl/doc/src/notes.xml
+++ b/lib/ssl/doc/src/notes.xml
@@ -1521,14 +1521,14 @@
         <item>
           <p>
 	    Hibernation now works as expected in all cases, was
-	    accidently broken by optimization efforts.</p>
+	    accidentally broken by optimization efforts.</p>
           <p>
 	    Own Id: OTP-15910</p>
         </item>
         <item>
           <p>
 	    Fix interoperability problems with openssl when the TLS
-	    1.3 server is configured wirh the option
+	    1.3 server is configured with the option
 	    signature_algs_cert.</p>
           <p>
 	    Own Id: OTP-15913</p>
@@ -1747,7 +1747,7 @@
         <item>
           <p>
 	    Hibernation now works as expected in all cases, was
-	    accidently broken by optimization efforts.</p>
+	    accidentally broken by optimization efforts.</p>
           <p>
 	    Own Id: OTP-15910</p>
         </item>
@@ -2250,7 +2250,7 @@
           <p>
 	    Correct cipher suite handling for ECDHE_*, the incorrect
 	    handling could cause an incorrrect suite to be selected
-	    and most likly fail the handshake.</p>
+	    and most likely fail the handshake.</p>
           <p>
 	    Own Id: OTP-15203</p>
         </item>
@@ -2292,7 +2292,7 @@
         </item>
         <item>
           <p>
-	    Add suport for ECDHE_PSK cipher suites</p>
+	    Add support for ECDHE_PSK cipher suites</p>
           <p>
 	    Own Id: OTP-14547</p>
         </item>
@@ -2387,7 +2387,7 @@
         <item>
           <p>
 	    Add utility function for converting erlang cipher suites
-	    to a string represenation (ERL-600).</p>
+	    to a string representation (ERL-600).</p>
           <p>
 	    Own Id: OTP-15106</p>
         </item>
@@ -2448,7 +2448,7 @@
           <p>
 	    Correct cipher suite handling for ECDHE_*, the incorrect
 	    handling could cause an incorrrect suite to be selected
-	    and most likly fail the handshake.</p>
+	    and most likely fail the handshake.</p>
           <p>
 	    Own Id: OTP-15203</p>
         </item>
@@ -2764,7 +2764,7 @@
       <list>
         <item>
           <p>
-	    ECDH-ECDSA key exchange supported, was accidently
+	    ECDH-ECDSA key exchange supported, was accidentally
 	    dismissed in earlier versions.</p>
           <p>
 	    Own Id: OTP-14421</p>
@@ -3474,9 +3474,9 @@
       <list>
         <item>
           <p>
-	    Correct cipher suites conversion and gaurd expression.
+	    Correct cipher suites conversion and guard expression.
 	    Caused problems with GCM cipher suites and client side
-	    option to set signature_algorithms extention values.</p>
+	    option to set signature_algorithms extension values.</p>
           <p>
 	    Own Id: OTP-13525</p>
         </item>
@@ -3689,10 +3689,10 @@
           <p>
 	    If upper limit is reached, invalidate the current cache
 	    entries, e.i the session lifetime is the max time a
-	    session will be keept, but it may be invalidated earlier
+	    session will be kept, but it may be invalidated earlier
 	    if the max limit for the table is reached. This will keep
 	    the ssl manager process well behaved, not exhusting
-	    memeory. Invalidating the entries will incrementally
+	    memory. Invalidating the entries will incrementally
 	    empty the cache to make room for fresh sessions entries.</p>
           <p>
 	    Own Id: OTP-12392</p>
@@ -3871,7 +3871,7 @@
       <list>
         <item>
           <p>
-	    Terminate gracefully when receving bad input to premaster
+	    Terminate gracefully when receiving bad input to premaster
 	    secret calculation</p>
           <p>
 	    Own Id: OTP-12783</p>
@@ -4219,7 +4219,7 @@
 	    Added option honor_cipher_order. This instructs the
 	    server to prefer its own cipher ordering rather than the
 	    client's and can help protect against things like BEAST
-	    while maintaining compatability with clients which only
+	    while maintaining compatibility with clients which only
 	    support older ciphers. </p>
           <p>
 	    Thanks to Andrew Thompson for the implementation, and
@@ -4247,8 +4247,8 @@
         <item>
           <p>
 	    Correct clean up of certificate database when certs are
-	    inputed in pure DER format.The incorrect code could cause
-	    a memory leek when certs where inputed in DER. Thanks to
+	    inputted in pure DER format.The incorrect code could cause
+	    a memory leek when certs where inputted in DER. Thanks to
 	    Bernard Duggan for reporting this.</p>
           <p>
 	    Own Id: OTP-11733</p>
@@ -4709,9 +4709,9 @@
         <item>
           <p>
 	    ssl:recv/3 could "loose" data when the timeout occurs. If
-	    the timout in ssl:connect or ssl:ssl_accept expired the
+	    the timeout in ssl:connect or ssl:ssl_accept expired the
 	    ssl connection process was not terminated as it should,
-	    this due to gen_fsm:send_all_state_event timout is a
+	    this due to gen_fsm:send_all_state_event timeout is a
 	    client side time out. These timouts are now handled by
 	    the gen_fsm-procss instead.</p>
           <p>
@@ -4807,7 +4807,7 @@
           <p>
 	    Fix a bug where ssl_tls_dist_proxy would crash at caller
 	    timeout. Fix a bug where a timeout from the SSL layer
-	    would block the distribution indefinately. Run the proxy
+	    would block the distribution indefinitely. Run the proxy
 	    exclusively on the loopback interface. (Thanks to Paul
 	    Guyot)</p>
           <p>
@@ -4817,7 +4817,7 @@
           <p>
 	    Fix setup loop of SSL TLS dist proxy</p>
           <p>
-	    Fix potential leak of processes waiting indefinately for
+	    Fix potential leak of processes waiting indefinitely for
 	    data from closed sockets during socket setup phase.
 	    (Thanks to Paul Guyot)</p>
           <p>
@@ -4997,7 +4997,7 @@
       <item>
 	<p>Calling gen_tcp:connect with option {ip, {127,0,0,1}} results in 
 	an exit with reason badarg. Neither SSL nor INETS This was not 
-	catched, resulting in crashes with incomprehensible reasons.</p>
+	caught, resulting in crashes with incomprehensible reasons.</p>
 	<p>Own Id: OTP-9289 Aux Id: seq11845</p>
       </item>
     </list>
diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml
index 175ebb1b86..f75005e1ac 100644
--- a/lib/ssl/doc/src/ssl.xml
+++ b/lib/ssl/doc/src/ssl.xml
@@ -961,7 +961,7 @@ fun(srp, Username :: binary(), UserState :: term()) ->
       and saved for later reuse. The session ID can be fetched with 
       <seealso marker="#connection_information-2">connection_information/2</seealso>
       and used with the client option <seealso marker="#type-client_reuse_session">reuse_session</seealso>
-      The boolean value true specifies that if possible, automatized session reuse will
+      The boolean value true specifies that if possible, automated session reuse will
       be performed. If a new session is created, and is unique in regard 
       to previous stored sessions, it will be saved for possible later reuse. Since OTP-21.3</p>
       </desc>
diff --git a/lib/ssl/doc/src/ssl_crl_cache_api.xml b/lib/ssl/doc/src/ssl_crl_cache_api.xml
index cdbcd9ddcd..ca661b9207 100644
--- a/lib/ssl/doc/src/ssl_crl_cache_api.xml
+++ b/lib/ssl/doc/src/ssl_crl_cache_api.xml
@@ -152,7 +152,7 @@
 	  marker="public_key:public_key_records"> X509 certificates records</seealso>,
 	  originating form <c>#'DistributionPoint'.cRLissuer</c> and  
 	  representing different mechanism to obtain the CRLs. The cache
-	  callback needs to use the appropriate entry to retrive the CRLs or
+	  callback needs to use the appropriate entry to retrieve the CRLs or
 	  return an empty list if it does not exist.
 	  </p>
 
diff --git a/lib/ssl/doc/src/ssl_protocol.xml b/lib/ssl/doc/src/ssl_protocol.xml
index fc148cdee6..4f6186a641 100644
--- a/lib/ssl/doc/src/ssl_protocol.xml
+++ b/lib/ssl/doc/src/ssl_protocol.xml
@@ -42,7 +42,7 @@
   though you can plug in any other reliable transport protocol
   with the same Application Programming Interface (API) as the
   <c>gen_tcp</c> module in Kernel. DTLS is by default run over UDP/IP,
-  which means that application data has no delivery guarentees. Other 
+  which means that application data has no delivery guarantees. Other 
   transports, such as SCTP, may be supported in future releases.</p>
   
   <p>If a client and a server wants to use an upgrade mechanism, such as
diff --git a/lib/ssl/src/dtls_connection.hrl b/lib/ssl/src/dtls_connection.hrl
index 3dd78235d0..42581fca21 100644
--- a/lib/ssl/src/dtls_connection.hrl
+++ b/lib/ssl/src/dtls_connection.hrl
@@ -33,7 +33,7 @@
 	  dtls_handshake_next_seq = 0,
 	  dtls_flight_last,
 	  dtls_handshake_next_fragments = [], %% Fragments of the next handshake message
-	  dtls_handshake_later_fragments = [], %% Fragments of handsake messages come after the one in next buffer
+	  dtls_handshake_later_fragments = [], %% Fragments of handshake messages come after the one in next buffer
 	  dtls_cipher_texts = []         %%:: [binary()],
 	 }).
 
diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl
index 2d0f37e0fe..46ee95db87 100644
--- a/lib/ssl/src/dtls_handshake.erl
+++ b/lib/ssl/src/dtls_handshake.erl
@@ -18,7 +18,7 @@
 %% %CopyrightEnd%
 
 %%----------------------------------------------------------------------
-%% Purpose: Help funtions for handling the DTLS (specific parts of)
+%% Purpose: Help functions for handling the DTLS (specific parts of)
 %%% SSL/TLS/DTLS handshake protocol
 %%----------------------------------------------------------------------
 -module(dtls_handshake).
@@ -36,7 +36,7 @@
 %% Handshake encoding
 -export([fragment_handshake/2, encode_handshake/3]).
 
-%% Handshake decodeing
+%% Handshake decoding
 -export([get_dtls_handshake/4]).
 
 -type dtls_handshake() :: #client_hello{} | #hello_verify_request{} | 
@@ -150,7 +150,7 @@ encode_handshake(Handshake, Version, Seq) ->
     [MsgType, ?uint24(Len), ?uint16(Seq), ?uint24(0), ?uint24(Len), Bin].
   
 %%--------------------------------------------------------------------
-%%% Handshake decodeing
+%%% Handshake decoding
 %%--------------------------------------------------------------------
 
 %%--------------------------------------------------------------------
diff --git a/lib/ssl/src/dtls_handshake.hrl b/lib/ssl/src/dtls_handshake.hrl
index 3a8159df0a..7835c46f48 100644
--- a/lib/ssl/src/dtls_handshake.hrl
+++ b/lib/ssl/src/dtls_handshake.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the DTLS-handshake protocol
+%% Purpose: Record and constant definitions for the DTLS-handshake protocol
 %% that differs from TLS see RFC 6347 
 %%----------------------------------------------------------------------
 -ifndef(dtls_handshake).
diff --git a/lib/ssl/src/dtls_record.hrl b/lib/ssl/src/dtls_record.hrl
index 373481c3f8..893f01a559 100644
--- a/lib/ssl/src/dtls_record.hrl
+++ b/lib/ssl/src/dtls_record.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the DTLS-record protocol
+%% Purpose: Record and constant definitions for the DTLS-record protocol
 %% see RFC 6347
 %%----------------------------------------------------------------------
 
diff --git a/lib/ssl/src/dtls_socket.erl b/lib/ssl/src/dtls_socket.erl
index f1569f5069..a0aa3c5f4e 100644
--- a/lib/ssl/src/dtls_socket.erl
+++ b/lib/ssl/src/dtls_socket.erl
@@ -70,10 +70,10 @@ listen(Port, #config{inet_ssl = SockOpts,
 
 accept(dtls, #config{transport_info = {Transport,_,_,_,_},
                      connection_cb = ConnectionCb,
-                     dtls_handler = {Listner, _}}, _Timeout) -> 
-    case dtls_packet_demux:accept(Listner, self()) of
+                     dtls_handler = {Listener, _}}, _Timeout) -> 
+    case dtls_packet_demux:accept(Listener, self()) of
 	{ok, Pid, Socket} ->
-	    {ok, socket([Pid], Transport, {Listner, Socket}, ConnectionCb)};
+	    {ok, socket([Pid], Transport, {Listener, Socket}, ConnectionCb)};
 	{error, Reason} ->
 	    {error, Reason}
     end.
@@ -110,11 +110,11 @@ close(Transport, {_Client, Socket}) ->
 socket(Pids, gen_udp = Transport,
        PeerAndSock = {{_Host, _Port}, _Socket}, ConnectionCb) ->
     #sslsocket{pid = Pids, 
-	       %% "The name "fd" is keept for backwards compatibility
+	       %% "The name "fd" is kept for backwards compatibility
 	       fd = {Transport, PeerAndSock, ConnectionCb}};
 socket(Pids, Transport, Socket, ConnectionCb) ->
     #sslsocket{pid = Pids, 
-	       %% "The name "fd" is keept for backwards compatibility
+	       %% "The name "fd" is kept for backwards compatibility
 	       fd = {Transport, Socket, ConnectionCb}}.
 setopts(_, Socket = #sslsocket{pid = {dtls, #config{dtls_handler = {ListenPid, _}}}}, Options) ->
     SplitOpts = {_, EmOpts} = tls_socket:split_options(Options),
diff --git a/lib/ssl/src/inet_tls_dist.erl b/lib/ssl/src/inet_tls_dist.erl
index ca4383f730..63e599661f 100644
--- a/lib/ssl/src/inet_tls_dist.erl
+++ b/lib/ssl/src/inet_tls_dist.erl
@@ -315,10 +315,10 @@ accept_one(Driver, Kernel, Socket) ->
 %% {verify_fun,{fun ?MODULE:verify_client/3,_}} is used
 %% as a configuration marker that verify_client/3 shall be used.
 %%
-%% Replace the State in the first occurence of
+%% Replace the State in the first occurrence of
 %% {verify_fun,{fun ?MODULE:verify_client/3,State}}
 %% and remove the rest.
-%% The inserted state is not accesible from a configuration file
+%% The inserted state is not accessible from a configuration file
 %% since it is dynamic and connection dependent.
 %%
 setup_verify_client(Socket, Opts) ->
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 017ca03117..d1ca621e22 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -762,7 +762,7 @@ handshake(Socket, SslOptions, Timeout) when (is_integer(Timeout) andalso Timeout
       Reason :: closed | timeout | error_alert().
 %%
 %%
-%% Description: Continues the handshke possible with newly supplied options.
+%% Description: Continues the handshake possible with newly supplied options.
 %%--------------------------------------------------------------------
 handshake_continue(Socket, SSLOptions) ->
     handshake_continue(Socket, SSLOptions, infinity).
@@ -776,7 +776,7 @@ handshake_continue(Socket, SSLOptions) ->
       Reason :: closed | timeout | error_alert().
 %%
 %%
-%% Description: Continues the handshke possible with newly supplied options.
+%% Description: Continues the handshake possible with newly supplied options.
 %%--------------------------------------------------------------------
 handshake_continue(Socket, SSLOptions, Timeout) ->
     ssl_connection:handshake_continue(Socket, SSLOptions, Timeout).
@@ -817,7 +817,7 @@ close(#sslsocket{pid = [TLSPid|_]},
 				       (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
     case ssl_connection:close(TLSPid, {close, DownGrade}) of
         ok -> %% In normal close {error, closed} is regarded as ok, as it is not interesting which side
-            %% that got to do the actual close. But in the downgrade case only {ok, Port} is a sucess.
+            %% that got to do the actual close. But in the downgrade case only {ok, Port} is a success.
             {error, closed};
         Other ->
             Other
@@ -1056,7 +1056,7 @@ filter_cipher_suites(Suites, Filters0) ->
       Preferred :: ciphers() | cipher_filters(),
       Suites :: ciphers().
 
-%% Description: Make <Preferred> suites become the most prefered
+%% Description: Make <Preferred> suites become the most preferred
 %%      suites that is put them at the head of the cipher suite list
 %%      and remove them from <Suites> if present. <Preferred> may be a
 %%      list of cipher suites or a list of filters in which case the
@@ -1075,7 +1075,7 @@ prepend_cipher_suites(Filters, Suites) ->
       Suites :: ciphers().
 
 %% Description: Make <Deferred> suites suites become the 
-%% least prefered suites that is put them at the end of the cipher suite list
+%% least preferred suites that is put them at the end of the cipher suite list
 %% and removed them from <Suites> if present.
 %%
 %%--------------------------------------------------------------------
@@ -1246,9 +1246,9 @@ getstat(Socket) ->
 %% Description: Get one or more statistic options for a socket.
 %%--------------------------------------------------------------------
 getstat(#sslsocket{pid = {dtls, #config{transport_info = {Transport, _, _, _, _},
-                                        dtls_handler = {Listner, _}}}},
+                                        dtls_handler = {Listener, _}}}},
         Options) when is_list(Options) ->
-    dtls_socket:getstat(Transport, Listner, Options);
+    dtls_socket:getstat(Transport, Listener, Options);
 getstat(#sslsocket{pid = {Listen,  #config{transport_info = {Transport, _, _, _, _}}}},
         Options) when is_port(Listen), is_list(Options) ->
     tls_socket:getstat(Transport, Listen, Options);
@@ -1954,7 +1954,7 @@ expand_options(Opts0, Rules) ->
                       {list, [{mode, list}]}], Opts0),
     Opts2 = handle_option_format(Opts1, []),
 
-    %% Remove depricated ssl_imp option
+    %% Remove deprecated ssl_imp option
     Opts = proplists:delete(ssl_imp, Opts2),
     AllOpts = maps:keys(Rules),
     SockOpts = lists:foldl(fun(Key, PropList) -> proplists:delete(Key, PropList) end,
@@ -2070,7 +2070,7 @@ validate_option(beast_mitigation, Value, _)
 validate_option(cacerts, Value) when Value == undefined;
 				     is_list(Value) ->
     Value;
-%% certfile must be present in some cases otherwhise it can be set
+%% certfile must be present in some cases otherwise it can be set
 %% to the empty string.
 validate_option(cacertfile, undefined) ->
    <<>>;
diff --git a/lib/ssl/src/ssl_alert.erl b/lib/ssl/src/ssl_alert.erl
index aa21c8213e..9e3cf364fb 100644
--- a/lib/ssl/src/ssl_alert.erl
+++ b/lib/ssl/src/ssl_alert.erl
@@ -44,7 +44,7 @@
 %%--------------------------------------------------------------------
 -spec decode(binary()) -> [#alert{}] | #alert{}.
 %%
-%% Description: Decode alert(s), will return a singel own alert if peer
+%% Description: Decode alert(s), will return a single own alert if peer
 %% sends garbage or too many warning alerts.
 %%--------------------------------------------------------------------
 decode(Bin) ->
diff --git a/lib/ssl/src/ssl_alert.hrl b/lib/ssl/src/ssl_alert.hrl
index fe9e17c8f5..d05b08b950 100644
--- a/lib/ssl/src/ssl_alert.hrl
+++ b/lib/ssl/src/ssl_alert.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the SSL-alert protocol
+%% Purpose: Record and constant definitions for the SSL-alert protocol
 %% see RFC 2246
 %%----------------------------------------------------------------------
 
diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl
index 69a98567e8..d171b676aa 100644
--- a/lib/ssl/src/ssl_certificate.erl
+++ b/lib/ssl/src/ssl_certificate.erl
@@ -19,7 +19,7 @@
 %%
 
 %%----------------------------------------------------------------------
-%% Purpose: Help funtions for handling certificat verification.
+%% Purpose: Help functions for handling certificate verification.
 %% The path validation defined in ssl_handshake.erl that mainly
 %% calls functions in this module is described in RFC 3280. 
 %%----------------------------------------------------------------------
diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl
index 037da3439c..dff9c25412 100644
--- a/lib/ssl/src/ssl_cipher.erl
+++ b/lib/ssl/src/ssl_cipher.erl
@@ -970,7 +970,7 @@ is_correct_padding(#generic_block_cipher{padding_length = Len,
     Len == byte_size(Padding); %% Only length check is done in SSL 3.0 spec
 %% For interoperability reasons it is possible to disable
 %% the padding check when using TLS 1.0, as it is not strictly required 
-%% in the spec (only recommended), howerver this makes TLS 1.0 vunrable to the Poodle attack 
+%% in the spec (only recommended), however this makes TLS 1.0 vunrable to the Poodle attack 
 %% so by default this clause will not match
 is_correct_padding(GenBlockCipher, {3, 1}, false) ->
     is_correct_padding(GenBlockCipher, {3, 0}, false);
diff --git a/lib/ssl/src/ssl_cipher.hrl b/lib/ssl/src/ssl_cipher.hrl
index 9f2141b6f8..62f59dfd82 100644
--- a/lib/ssl/src/ssl_cipher.hrl
+++ b/lib/ssl/src/ssl_cipher.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the SSL ciphers and
+%% Purpose: Record and constant definitions for the SSL ciphers and
 %% the SSL-cipher protocol see RFC 4346, RFC 3268
 %%----------------------------------------------------------------------
 
diff --git a/lib/ssl/src/ssl_cipher_format.erl b/lib/ssl/src/ssl_cipher_format.erl
index 589b0facf8..b780048ec3 100644
--- a/lib/ssl/src/ssl_cipher_format.erl
+++ b/lib/ssl/src/ssl_cipher_format.erl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Convert between diffrent cipher suite representations
+%% Purpose: Convert between different cipher suite representations
 %% 
 %%----------------------------------------------------------------------
 -module(ssl_cipher_format).
diff --git a/lib/ssl/src/ssl_connection.hrl b/lib/ssl/src/ssl_connection.hrl
index 5b90dc4105..a08545cafc 100644
--- a/lib/ssl/src/ssl_connection.hrl
+++ b/lib/ssl/src/ssl_connection.hrl
@@ -106,13 +106,13 @@
                 ssl_options           :: ssl_options(),
                 socket_options        :: #socket_options{},
 
-                %% Hanshake %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+                %% Handshake %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
                 handshake_env         :: #handshake_env{} | secret_printout(),
                 %% Buffer of TLS/DTLS records, used during the TLS
                 %% handshake to when possible pack more than one TLS
-                %% record into the underlaying packet
+                %% record into the underlying packet
                 %% format. Introduced by DTLS - RFC 4347.  The
-                %% mecahnism is also usefull in TLS although we do not
+                %% mechanism is also useful in TLS although we do not
                 %% need to worry about packet loss in TLS. In DTLS we
                 %% need to track DTLS handshake seqnr
                 flight_buffer = []   :: list() | map(),  
@@ -159,9 +159,9 @@
 %%   renegotiation                - TLS 1.3 forbids renegotiation
 %%   hello                        - used in user_hello, handshake continue
 %%   allow_renegotiate            - TLS 1.3 forbids renegotiation
-%%   expecting_next_protocol_negotiation - ALPN replaced NPN, depricated in TLS 1.3
+%%   expecting_next_protocol_negotiation - ALPN replaced NPN, deprecated in TLS 1.3
 %%   expecting_finished           - not implemented, used by abbreviated
-%%   next_protocol                - ALPN replaced NPN, depricated in TLS 1.3
+%%   next_protocol                - ALPN replaced NPN, deprecated in TLS 1.3
 %%
 %% connection_state :: map()
 %%
diff --git a/lib/ssl/src/ssl_crl_hash_dir.erl b/lib/ssl/src/ssl_crl_hash_dir.erl
index 3a13d9dbe4..65404db72d 100644
--- a/lib/ssl/src/ssl_crl_hash_dir.erl
+++ b/lib/ssl/src/ssl_crl_hash_dir.erl
@@ -53,7 +53,7 @@ select([{directoryName, Issuer} | _], {_DbHandle, [{dir, Dir}]}) ->
         {#{reason := [_|_]} = Report, DERs} ->
             {logger, {notice, Report, ?LOCATION}, DERs};
         {error, Error} ->
-            {logger, {error, #{description => "CRL retrival",
+            {logger, {error, #{description => "CRL retrieval",
                                reason => [{cannot_find_crl, Error},
                                           {dir, Dir}]}, ?LOCATION}, []}
     end;
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index 6ee0aa8f7b..2dce5f35d6 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -18,7 +18,7 @@
 %% %CopyrightEnd%
 
 %----------------------------------------------------------------------
-%% Purpose: Help funtions for handling the SSL-handshake protocol (common
+%% Purpose: Help functions for handling the SSL-handshake protocol (common
 %% to SSL/TLS and DTLS
 %%----------------------------------------------------------------------
 
@@ -2141,7 +2141,7 @@ maybe_check_crl(OtpCert, #{crl_check := Check,
 				  dps_and_crls(OtpCert, Callback, CRLDbHandle, same_issuer, LogLevel),
 				  Options);
 	DpsAndCRLs ->  %% This DP list may be empty if relevant CRLs existed 
-	    %% but could not be retrived, will result in {bad_cert, revocation_status_undetermined}
+	    %% but could not be retrieved, will result in {bad_cert, revocation_status_undetermined}
 	    case public_key:pkix_crls_validate(OtpCert, DpsAndCRLs, Options) of
 		{bad_cert, {revocation_status_undetermined, _}} ->
 		    crl_check_same_issuer(OtpCert, Check, 
@@ -2889,7 +2889,7 @@ decode_extensions(<<?UINT16(?EC_POINT_FORMATS_EXT), ?UINT16(Len),
 decode_extensions(<<?UINT16(?SNI_EXT), ?UINT16(Len),
                     Rest/binary>>, Version, MessageType, Acc) when Len == 0 ->
     decode_extensions(Rest, Version, MessageType,
-                      Acc#{sni => #sni{hostname = ""}}); %% Server may send an empy SNI
+                      Acc#{sni => #sni{hostname = ""}}); %% Server may send an empty SNI
 
 decode_extensions(<<?UINT16(?SNI_EXT), ?UINT16(Len),
                 ExtData:Len/binary, Rest/binary>>, Version, MessageType, Acc) ->
@@ -3286,7 +3286,7 @@ filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], Has
       KeyExchange == dhe_dss;
       KeyExchange == srp_dss ->							       
     do_filter_hashsigns(dsa, Suite, Suites, Algos, HashSigns, Version, Acc);
-filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], HashSigns, Verion,
+filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], HashSigns, Version,
                  Acc) when 
       KeyExchange == dh_dss; 
       KeyExchange == dh_rsa; 
@@ -3296,7 +3296,7 @@ filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], Has
       %%  Fixed DH certificates MAY be signed with any hash/signature
       %%  algorithm pair appearing in the hash_sign extension.  The names
     %%  DH_DSS, DH_RSA, ECDH_ECDSA, and ECDH_RSA are historical.
-    filter_hashsigns(Suites, Algos, HashSigns, Verion, [Suite| Acc]);
+    filter_hashsigns(Suites, Algos, HashSigns, Version, [Suite| Acc]);
 filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], HashSigns, Version,
                  Acc) when 
       KeyExchange == dh_anon;
diff --git a/lib/ssl/src/ssl_handshake.hrl b/lib/ssl/src/ssl_handshake.hrl
index 4968b83a8a..c56ee31fdd 100644
--- a/lib/ssl/src/ssl_handshake.hrl
+++ b/lib/ssl/src/ssl_handshake.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the SSL-handshake protocol
+%% Purpose: Record and constant definitions for the SSL-handshake protocol
 %% see RFC 5246. Also includes supported hello extensions.
 %%----------------------------------------------------------------------
 
@@ -59,7 +59,7 @@
 -define(DEFAULT_DIFFIE_HELLMAN_PRIME, ssl_dh_groups:modp2048_prime()).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% Handsake protocol - RFC 4346 section 7.4
+%%% Handshake protocol - RFC 4346 section 7.4
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% enum {
diff --git a/lib/ssl/src/ssl_manager.erl b/lib/ssl/src/ssl_manager.erl
index 1194141c6a..1cb42898be 100644
--- a/lib/ssl/src/ssl_manager.erl
+++ b/lib/ssl/src/ssl_manager.erl
@@ -369,7 +369,7 @@ handle_info({clean_cert_db, Ref, File},
 	    #state{certificate_db = [CertDb, {RefDb, FileMapDb} | _]} = State) ->
     
     case ssl_pkix_db:lookup(Ref, RefDb) of
-	undefined -> %% Alredy cleaned
+	undefined -> %% Already cleaned
 	    ok;
 	_ ->
 	    clean_cert_db(Ref, CertDb, RefDb, FileMapDb, File)
diff --git a/lib/ssl/src/ssl_pkix_db.erl b/lib/ssl/src/ssl_pkix_db.erl
index 13ce07b1cd..0778a90aaf 100644
--- a/lib/ssl/src/ssl_pkix_db.erl
+++ b/lib/ssl/src/ssl_pkix_db.erl
@@ -99,7 +99,7 @@ remove(Dbs) ->
 				 undefined | {ok, {der_cert(), #'OTPCertificate'{}}}.
 
 %%
-%% Description: Retrives the trusted certificate identified by 
+%% Description: Retrieves the trusted certificate identified by 
 %% <SerialNumber, Issuer>. Ref is used as it is specified  
 %% for each connection which certificates are trusted.
 %%--------------------------------------------------------------------
@@ -193,7 +193,7 @@ decode_pem_file(File) ->
 %%--------------------------------------------------------------------
 -spec remove_trusted_certs(reference(), db_handle()) -> ok.
 %%
-%% Description: Removes all trusted certificates refernced by <Ref>.
+%% Description: Removes all trusted certificates referenced by <Ref>.
 %%--------------------------------------------------------------------
 remove_trusted_certs(Ref, CertsDb) ->
     remove_certs(Ref, CertsDb).
diff --git a/lib/ssl/src/ssl_record.hrl b/lib/ssl/src/ssl_record.hrl
index 6eea059351..93721e228c 100644
--- a/lib/ssl/src/ssl_record.hrl
+++ b/lib/ssl/src/ssl_record.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the SSL-record protocol
+%% Purpose: Record and constant definitions for the SSL-record protocol
 % see RFC 2246
 %%----------------------------------------------------------------------
 
@@ -100,8 +100,8 @@
 -define(AES_GCM, 8).
 -define(CHACHA20_POLY1305, 9).
 %% Following two are not defined in any RFC but we want to have the
-%% same type of handling internaly, all of these "bulk_cipher_algorithm"
-%% enums are only used internaly anyway.
+%% same type of handling internally, all of these "bulk_cipher_algorithm"
+%% enums are only used internally anyway.
 -define(AES_CCM, 10). 
 -define(AES_CCM_8, 11). 
 
diff --git a/lib/ssl/src/tls_handshake.erl b/lib/ssl/src/tls_handshake.erl
index a6375d28e3..8b81e1dcc5 100644
--- a/lib/ssl/src/tls_handshake.erl
+++ b/lib/ssl/src/tls_handshake.erl
@@ -19,7 +19,7 @@
 %%
 
 %%----------------------------------------------------------------------
-%% Purpose: Help funtions for handling the TLS (specific parts of)
+%% Purpose: Help functions for handling the TLS (specific parts of)
 %%% SSL/TLS/DTLS handshake protocol
 %%----------------------------------------------------------------------
 
@@ -41,7 +41,7 @@
 %% Handshake encoding
 -export([encode_handshake/2]).
 
-%% Handshake decodeing
+%% Handshake decoding
 -export([get_tls_handshake/4, decode_handshake/3]).
 
 -type tls_handshake() :: #client_hello{} | ssl_handshake:ssl_handshake().
@@ -281,7 +281,7 @@ encode_handshake(Package, Version) ->
 
 
 %%--------------------------------------------------------------------
-%%% Handshake decodeing
+%%% Handshake decoding
 %%--------------------------------------------------------------------
 
 %%--------------------------------------------------------------------
diff --git a/lib/ssl/src/tls_handshake.hrl b/lib/ssl/src/tls_handshake.hrl
index d1ec80691e..ea57516a47 100644
--- a/lib/ssl/src/tls_handshake.hrl
+++ b/lib/ssl/src/tls_handshake.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the TLS-handshake protocol
+%% Purpose: Record and constant definitions for the TLS-handshake protocol
 %% see RFC 5246. 
 %%----------------------------------------------------------------------
 -ifndef(tls_handshake).
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index 12811459b1..8bc2a35d18 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -19,7 +19,7 @@
 %%
 
 %%----------------------------------------------------------------------
-%% Purpose: Help funtions for handling the TLS 1.3 (specific parts of)
+%% Purpose: Help functions for handling the TLS 1.3 (specific parts of)
 %%% TLS handshake protocol
 %%----------------------------------------------------------------------
 
@@ -2138,7 +2138,7 @@ context_string(client) ->
     <<"TLS 1.3, client CertificateVerify">>.
 
 
-%% Return context string for verifing peer signature
+%% Return context string for verifying peer signature
 peer_context_string(server) ->
     <<"TLS 1.3, client CertificateVerify">>;
 peer_context_string(client) ->
@@ -2620,7 +2620,7 @@ truncate_client_hello(HelloBin0) ->
     %% the input can result in a different handshake binary.
     %% The original length of the binders can still be determined by
     %% re-encoding the original ClientHello and using its size as reference
-    %% when we substract the size of the truncated binary.
+    %% when we subtract the size of the truncated binary.
     TruncatedSize = iolist_size(tls_handshake:encode_handshake(CH, {3,4})),
     RefSize = iolist_size(tls_handshake:encode_handshake(CH0, {3,4})),
     BindersSize = RefSize - TruncatedSize,
diff --git a/lib/ssl/src/tls_handshake_1_3.hrl b/lib/ssl/src/tls_handshake_1_3.hrl
index d506821f6c..6cad172d1d 100644
--- a/lib/ssl/src/tls_handshake_1_3.hrl
+++ b/lib/ssl/src/tls_handshake_1_3.hrl
@@ -19,7 +19,7 @@
 %%
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the TLS-handshake protocol
+%% Purpose: Record and constant definitions for the TLS-handshake protocol
 %% see RFC 8446. Also includes supported hello extensions.
 %%----------------------------------------------------------------------
 
@@ -27,7 +27,7 @@
 -define(tls_handshake_1_3, true).
 
 %% Common to TLS-1.3 and previous TLS versions 
-%% Some defenitions may not exist in TLS-1.3 this is 
+%% Some definitions may not exist in TLS-1.3 this is 
 %% handled elsewhere
 -include("tls_handshake.hrl"). 
 
diff --git a/lib/ssl/src/tls_record.hrl b/lib/ssl/src/tls_record.hrl
index e296f23673..98ee3f7bf1 100644
--- a/lib/ssl/src/tls_record.hrl
+++ b/lib/ssl/src/tls_record.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the TLS-record protocol
+%% Purpose: Record and constant definitions for the TLS-record protocol
 %% see RFC 5246
 %%----------------------------------------------------------------------
 
diff --git a/lib/ssl/src/tls_record_1_3.erl b/lib/ssl/src/tls_record_1_3.erl
index 4411209aee..93bf88788d 100644
--- a/lib/ssl/src/tls_record_1_3.erl
+++ b/lib/ssl/src/tls_record_1_3.erl
@@ -111,7 +111,7 @@ encode_iolist(Type, Data, ConnectionStates0) ->
 				{#ssl_tls{}, ssl_record:connection_states()}| #alert{}.
 %%
 %% Description: Decode cipher text, use legacy type ssl_tls instead of tls_cipher_text
-%% in decoding context so that we can reuse the code from erlier versions. 
+%% in decoding context so that we can reuse the code from earlier versions. 
 %%--------------------------------------------------------------------
 decode_cipher_text(#ssl_tls{type = ?OPAQUE_TYPE,
                             version = ?LEGACY_VERSION,
diff --git a/lib/ssl/src/tls_record_1_3.hrl b/lib/ssl/src/tls_record_1_3.hrl
index 273427a34e..dcfa1b28a5 100644
--- a/lib/ssl/src/tls_record_1_3.hrl
+++ b/lib/ssl/src/tls_record_1_3.hrl
@@ -20,7 +20,7 @@
 
 %%
 %%----------------------------------------------------------------------
-%% Purpose: Record and constant defenitions for the TLS-1.3-record protocol
+%% Purpose: Record and constant definitions for the TLS-1.3-record protocol
 %% see RFC 8446 not present in earlier versions
 %%----------------------------------------------------------------------
 
diff --git a/lib/ssl/src/tls_sender.erl b/lib/ssl/src/tls_sender.erl
index 34ec00a96f..9fb6d9f554 100644
--- a/lib/ssl/src/tls_sender.erl
+++ b/lib/ssl/src/tls_sender.erl
@@ -129,7 +129,7 @@ send_alert(Pid, Alert) ->
 %%--------------------------------------------------------------------
 -spec send_and_ack_alert(pid(), #alert{}) -> _.
 %% Description: TLS connection process wants to send an Alert
-%% in the connection state and recive an ack.
+%% in the connection state and receive an ack.
 %%--------------------------------------------------------------------
 send_and_ack_alert(Pid, Alert) ->
     gen_statem:call(Pid, {ack_alert, Alert}, ?DEFAULT_TIMEOUT).
@@ -247,7 +247,7 @@ init({call, From}, {Pid, #{current_write := WriteState,
                                                 log_level = LogLevel}},
     {next_state, handshake, StateData, [{reply, From, ok}]};
 init(_, _, _) ->
-    %% Just in case anything else sneeks through
+    %% Just in case anything else sneaks through
     {keep_state_and_data, [postpone]}.
 
 %%--------------------------------------------------------------------
@@ -425,11 +425,11 @@ handle_common(info, {'EXIT', _Sup, shutdown},
   #data{static = #static{connection_monitor = Monitor}} = StateData) ->
     {stop, normal, StateData};
 handle_common(info, Msg, #data{static = #static{log_level = Level}}) ->
-    ssl_logger:log(info, Level, #{event => "TLS sender recived unexpected info", 
+    ssl_logger:log(info, Level, #{event => "TLS sender received unexpected info", 
                                   reason => [{message, Msg}]}, ?LOCATION),
     keep_state_and_data;
 handle_common(Type, Msg, #data{static = #static{log_level = Level}}) ->
-    ssl_logger:log(error, Level, #{event => "TLS sender recived unexpected event", 
+    ssl_logger:log(error, Level, #{event => "TLS sender received unexpected event", 
                                    reason => [{type, Type}, {message, Msg}]}, ?LOCATION),
     keep_state_and_data.
 
diff --git a/lib/ssl/src/tls_server_session_ticket.erl b/lib/ssl/src/tls_server_session_ticket.erl
index c1334cddfb..20be9933ed 100644
--- a/lib/ssl/src/tls_server_session_ticket.erl
+++ b/lib/ssl/src/tls_server_session_ticket.erl
@@ -239,7 +239,7 @@ stateful_ticket_store(Ref, NewSessionTicket, Hash, Psk,
     StatefulTicket = {NewSessionTicket, Hash, Psk},
     case gb_trees:size(Tree0) of
         Max ->
-            %% Trow away oldes ticket
+            %% Trow away oldest ticket
             {_, {#new_session_ticket{ticket = OldRef},_,_}, Tree1} 
                 = gb_trees:take_smallest(Tree0),
             Tree = gb_trees:insert(Id, StatefulTicket, Tree1),
@@ -311,7 +311,7 @@ stateful_living_ticket({TimeStamp,_},
 
 stateful_psk_ticket_id(Key) ->
     Unique = erlang:unique_integer(),
-    %% Obfuscate to avoid DoS attack possiblities
+    %% Obfuscate to avoid DoS attack possibilities
     %% that could invalidate tickets and render them
     %% unusable. This id should be unpredictable
     %% and unique but have no other cryptographic requirements.
diff --git a/lib/ssl/src/tls_socket.erl b/lib/ssl/src/tls_socket.erl
index 2b4df16643..1e80c767d3 100644
--- a/lib/ssl/src/tls_socket.erl
+++ b/lib/ssl/src/tls_socket.erl
@@ -148,7 +148,7 @@ connect(Address, Port,
 
 socket(Pids, Transport, Socket, ConnectionCb, Trackers) ->
     #sslsocket{pid = Pids, 
-	       %% "The name "fd" is keept for backwards compatibility
+	       %% "The name "fd" is kept for backwards compatibility
 	       fd = {Transport, Socket, ConnectionCb, Trackers}}.
 setopts(gen_tcp, Socket = #sslsocket{pid = {ListenSocket, #config{trackers = Trackers}}}, Options) ->
     Tracker = proplists:get_value(option_tracker, Trackers),
diff --git a/lib/ssl/test/inet_crypto_dist.erl b/lib/ssl/test/inet_crypto_dist.erl
index 6bf285ba42..d4a1053561 100644
--- a/lib/ssl/test/inet_crypto_dist.erl
+++ b/lib/ssl/test/inet_crypto_dist.erl
@@ -261,7 +261,7 @@ compute_shared_secret(
 %%
 %% For an connection net_kernel calls setup/5 which spawns the
 %% Controller process as linked to net_kernel.  This Controller process
-%% connects to the other node's listen socket and when that is succesful
+%% connects to the other node's listen socket and when that is successful
 %% spawns the DistCtrl process as linked to the controller and transfers
 %% socket ownership to it.
 %%
@@ -905,7 +905,7 @@ reply({Ref, Pid}, Msg) ->
 %% While the sender generates a new key pair at every rekey,
 %% which changes the shared secret at every rekey.
 %%
-%% The only reaction to errors is to crash noisily (?) wich will bring
+%% The only reaction to errors is to crash noisily (?) which will bring
 %% down the connection and hopefully produce something useful
 %% in the local log, but all the other end sees is a closed connection.
 %% -------------------------------------------------------------------------
diff --git a/lib/ssl/test/openssl_client_cert_SUITE.erl b/lib/ssl/test/openssl_client_cert_SUITE.erl
index 7ccbac33d6..3135ee5840 100644
--- a/lib/ssl/test/openssl_client_cert_SUITE.erl
+++ b/lib/ssl/test/openssl_client_cert_SUITE.erl
@@ -179,7 +179,7 @@ init_per_group(Group, Config0) when Group == rsa;
     Config = ssl_test_lib:make_rsa_cert(Config0),
     COpts = proplists:get_value(client_rsa_opts, Config),
     SOpts = proplists:get_value(server_rsa_opts, Config),
-    %% Make sure _rsa* suite is choosen by ssl_test_lib:start_server
+    %% Make sure _rsa* suite is chosen by ssl_test_lib:start_server
     Version = ssl_test_lib:protocol_version(Config),
     Ciphers = ssl_cert_tests:test_ciphers(fun(dhe_rsa) -> 
                                                   true;
@@ -235,7 +235,7 @@ init_per_group(Group, Config0) when Group == ecdsa;
             Config = ssl_test_lib:make_ecdsa_cert(Config0),
             COpts = proplists:get_value(client_ecdsa_opts, Config),
             SOpts = proplists:get_value(server_ecdsa_opts, Config),
-            %% Make sure ecdh* suite is choosen by ssl_test_lib:start_server
+            %% Make sure ecdh* suite is chosen by ssl_test_lib:start_server
             Version = ssl_test_lib:protocol_version(Config),
             Ciphers =  ssl_cert_tests:test_ciphers(fun(ecdh_ecdsa) -> 
                                                            true;
@@ -296,7 +296,7 @@ init_per_group(Group, Config0) when Group == dsa ->
             Config = ssl_test_lib:make_dsa_cert(Config0),    
             COpts = proplists:get_value(client_dsa_opts, Config),
             SOpts = proplists:get_value(server_dsa_opts, Config),
-            %% Make sure dhe_dss* suite is choosen by ssl_test_lib:start_server
+            %% Make sure dhe_dss* suite is chosen by ssl_test_lib:start_server
             Version = ssl_test_lib:protocol_version(Config),
             Ciphers =  ssl_cert_tests:test_ciphers(fun(dh_dss) -> 
                                                            true;
diff --git a/lib/ssl/test/openssl_server_cert_SUITE.erl b/lib/ssl/test/openssl_server_cert_SUITE.erl
index 54079644cf..1b001aa79f 100644
--- a/lib/ssl/test/openssl_server_cert_SUITE.erl
+++ b/lib/ssl/test/openssl_server_cert_SUITE.erl
@@ -170,7 +170,7 @@ init_per_group(rsa = Group, Config0) ->
     Config = ssl_test_lib:make_rsa_cert(Config0),
     COpts = proplists:get_value(client_rsa_opts, Config),
     SOpts = proplists:get_value(server_rsa_opts, Config),
-    %% Make sure _rsa* suite is choosen by ssl_test_lib:start_server
+    %% Make sure _rsa* suite is chosen by ssl_test_lib:start_server
     Version = ssl_test_lib:protocol_version(Config),
     Ciphers = ssl_cert_tests:test_ciphers(fun(dhe_rsa) -> 
                                                   true;
@@ -194,7 +194,7 @@ init_per_group(rsa_1_3 = Group, Config0) ->
     Config = ssl_test_lib:make_rsa_cert(Config0),
     COpts = proplists:get_value(client_rsa_opts, Config),
     SOpts = proplists:get_value(server_rsa_opts, Config),
-    %% Make sure _rsa* suite is choosen by ssl_test_lib:start_server
+    %% Make sure _rsa* suite is chosen by ssl_test_lib:start_server
     Version = ssl_test_lib:protocol_version(Config),
     Ciphers = ssl_cert_tests:test_ciphers(undefined, Version),
     case Ciphers of
@@ -240,7 +240,7 @@ init_per_group(ecdsa = Group, Config0) ->
             Config = ssl_test_lib:make_ecdsa_cert(Config0),
             COpts = proplists:get_value(client_ecdsa_opts, Config),
             SOpts = proplists:get_value(server_ecdsa_opts, Config),
-            %% Make sure ecdh* suite is choosen by ssl_test_lib:start_server
+            %% Make sure ecdh* suite is chosen by ssl_test_lib:start_server
             Version = ssl_test_lib:protocol_version(Config),
             Ciphers =  ssl_cert_tests:test_ciphers(fun(ecdh_ecdsa) -> 
                                                            true;
@@ -274,7 +274,7 @@ init_per_group(ecdsa_1_3 = Group, Config0) ->
             Config = ssl_test_lib:make_ecdsa_cert(Config0),
             COpts = proplists:get_value(client_ecdsa_opts, Config),
             SOpts = proplists:get_value(server_ecdsa_opts, Config),
-            %% Make sure ecdh* suite is choosen by ssl_test_lib:start_server
+            %% Make sure ecdh* suite is chosen by ssl_test_lib:start_server
             Version = proplists:get_value(version,Config),            
             Ciphers =  ssl_cert_tests:test_ciphers(undefined, Version),
             case Ciphers of
@@ -326,7 +326,7 @@ init_per_group(dsa = Group, Config0) ->
             Config = ssl_test_lib:make_dsa_cert(Config0),    
             COpts = proplists:get_value(client_dsa_opts, Config),
             SOpts = proplists:get_value(server_dsa_opts, Config),
-            %% Make sure dhe_dss* suite is choosen by ssl_test_lib:start_server
+            %% Make sure dhe_dss* suite is chosen by ssl_test_lib:start_server
             Version = proplists:get_value(version,Config),
             Ciphers =  ssl_cert_tests:test_ciphers(fun(dh_dss) -> 
                                                            true;
diff --git a/lib/ssl/test/property_test/ssl_eqc_handshake.erl b/lib/ssl/test/property_test/ssl_eqc_handshake.erl
index 72ee2af2b7..09e62adb6e 100644
--- a/lib/ssl/test/property_test/ssl_eqc_handshake.erl
+++ b/lib/ssl/test/property_test/ssl_eqc_handshake.erl
@@ -193,7 +193,7 @@ key_update() ->
 
 
 %%--------------------------------------------------------------------
-%% Messge Data Generators  -------------------------------------------
+%% Message Data Generators  -------------------------------------------
 %%--------------------------------------------------------------------
 
 tls_version() ->
diff --git a/lib/ssl/test/ssl_ECC.erl b/lib/ssl/test/ssl_ECC.erl
index 0930be46c8..4a87fa9fce 100644
--- a/lib/ssl/test/ssl_ECC.erl
+++ b/lib/ssl/test/ssl_ECC.erl
@@ -40,8 +40,8 @@
 -include_lib("common_test/include/ct.hrl").
 -include_lib("public_key/include/public_key.hrl").
 
-%% Test diffrent certificate chain types, note that it is the servers
-%% chain that affect what cipher suite that will be choosen
+%% Test different certificate chain types, note that it is the servers
+%% chain that affect what cipher suite that will be chosen
 
 %% ECDH_RSA 
 client_ecdh_rsa_server_ecdh_rsa(Config) when is_list(Config) ->
diff --git a/lib/ssl/test/ssl_ECC_SUITE.erl b/lib/ssl/test/ssl_ECC_SUITE.erl
index 9165f6bbe4..b8a0e8184e 100644
--- a/lib/ssl/test/ssl_ECC_SUITE.erl
+++ b/lib/ssl/test/ssl_ECC_SUITE.erl
@@ -156,8 +156,8 @@ end_per_testcase(_TestCase, Config) ->
 %%--------------------------------------------------------------------
 %% Test Cases --------------------------------------------------------
 %%--------------------------------------------------------------------
-%% Test diffrent certificate chain types, note that it is the servers
-%% chain that affect what cipher suite that will be choosen
+%% Test different certificate chain types, note that it is the servers
+%% chain that affect what cipher suite that will be chosen
 
 client_ecdsa_server_ecdsa_with_raw_key(Config)  when is_list(Config) ->
      Default = ssl_test_lib:default_cert_chain_conf(),
diff --git a/lib/ssl/test/ssl_alert_SUITE.erl b/lib/ssl/test/ssl_alert_SUITE.erl
index 3b32d3ece1..d604a99677 100644
--- a/lib/ssl/test/ssl_alert_SUITE.erl
+++ b/lib/ssl/test/ssl_alert_SUITE.erl
@@ -63,7 +63,7 @@ end_per_testcase(_TestCase, Config) ->
 %% Test Cases --------------------------------------------------------
 %%--------------------------------------------------------------------
 alerts() ->
-    [{doc, "Test ssl_alert formating code"}].
+    [{doc, "Test ssl_alert formatting code"}].
 alerts(Config) when is_list(Config) ->
     Descriptions = [?CLOSE_NOTIFY, ?UNEXPECTED_MESSAGE, ?BAD_RECORD_MAC,
 		    ?DECRYPTION_FAILED_RESERVED, ?RECORD_OVERFLOW, ?DECOMPRESSION_FAILURE,
@@ -75,7 +75,7 @@ alerts(Config) when is_list(Config) ->
 		    ?NO_RENEGOTIATION, ?UNSUPPORTED_EXTENSION, ?CERTIFICATE_UNOBTAINABLE,
 		    ?UNRECOGNIZED_NAME, ?BAD_CERTIFICATE_STATUS_RESPONSE,
 		    ?BAD_CERTIFICATE_HASH_VALUE, ?UNKNOWN_PSK_IDENTITY, 
-		    255 %% Unsupported/unknow alert will result in a description too
+		    255 %% Unsupported/unknown alert will result in a description too
 		   ],
     Alerts = [?ALERT_REC(?WARNING, ?CLOSE_NOTIFY) | 
 	      [?ALERT_REC(?FATAL, Desc) || Desc <- Descriptions]],
diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl
index 325edf9047..a4c7f24a00 100644
--- a/lib/ssl/test/ssl_api_SUITE.erl
+++ b/lib/ssl/test/ssl_api_SUITE.erl
@@ -1519,7 +1519,7 @@ controller_dies(Config) when is_list(Config) ->
 	    Client3 ! die_nice 
     end,
 
-    ct:log("Wating on exit ~p~n",[Client3]),
+    ct:log("Waiting on exit ~p~n",[Client3]),
     receive {'EXIT', Client3, normal} -> ok end,
     
     receive   %% Client3 is dead but that doesn't matter, socket should not be closed.
@@ -2681,7 +2681,7 @@ connection_information_result(Socket) ->
     {ok, Info = [_ | _]} = ssl:connection_information(Socket),
     case  length(Info) > 3 of
 	true -> 
-	    %% Atleast one ssl_option() is set
+	    %% At least one ssl_option() is set
 	    ct:log("Info ~p", [Info]),
 	    ok;
 	false ->
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index 746390b5af..bdd250458d 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -270,7 +270,7 @@ fallback(Config) when is_list(Config) ->
    
 %%--------------------------------------------------------------------
 cipher_format() ->
-    [{doc, "Test that cipher conversion from maps | tuples | stings to binarys works"}].
+    [{doc, "Test that cipher conversion from maps | tuples | strings to binarys works"}].
 cipher_format(Config) when is_list(Config) ->
     {ok, Socket0} = ssl:listen(0, [{ciphers, ssl:cipher_suites(default, 'tlsv1.2')}]),
     ssl:close(Socket0),
@@ -787,7 +787,7 @@ connect_dist_c(S) ->
 
 dummy(_Socket) ->
     %% Should not happen as the ssl connection will not be established
-    %% due to fatal handshake failiure
+    %% due to fatal handshake failure
     exit(kill).
 
 version_option_test(Config, Version) ->
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index e58f791af6..61fa3e1989 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -512,7 +512,7 @@ missing_root_cert_auth(Config) when is_list(Config) ->
     
 %%--------------------------------------------------------------------
 missing_root_cert_auth_user_verify_fun_accept() ->
-    [{doc, "Test that the client succeds if the ROOT CA is unknown in verify_peer mode"
+    [{doc, "Test that the client succeeds if the ROOT CA is unknown in verify_peer mode"
      " with a verify_fun that accepts the unknown CA error"}].
 
 missing_root_cert_auth_user_verify_fun_accept(Config) ->
diff --git a/lib/ssl/test/ssl_cert_tests.erl b/lib/ssl/test/ssl_cert_tests.erl
index 90c1b9a5cd..506d3b8fc7 100644
--- a/lib/ssl/test/ssl_cert_tests.erl
+++ b/lib/ssl/test/ssl_cert_tests.erl
@@ -125,7 +125,7 @@ client_auth_empty_cert_rejected(Config) ->
     end.
 %%--------------------------------------------------------------------
 client_auth_partial_chain() ->
-    [{doc, "Client sends an incompleate chain, by default not acceptable."}].
+    [{doc, "Client sends an incomplete chain, by default not acceptable."}].
 
 client_auth_partial_chain(Config) when is_list(Config) ->
     ServerOpts = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
@@ -164,7 +164,7 @@ client_auth_allow_partial_chain(Config) when is_list(Config) ->
 
  %%--------------------------------------------------------------------
 client_auth_do_not_allow_partial_chain() ->
-    [{doc, "Server does not accept the chain sent by the client as ROOT CA is unkown, "
+    [{doc, "Server does not accept the chain sent by the client as ROOT CA is unknown, "
       "and we do not choose to trust the intermediate CA. (partial_chain option)"}].
 
 client_auth_do_not_allow_partial_chain(Config) when is_list(Config) ->
@@ -250,7 +250,7 @@ client_auth_seelfsigned_peer(Config) when is_list(Config) ->
 
 %%--------------------------------------------------------------------
 missing_root_cert_no_auth() ->
-     [{doc,"Test that the client succeds if the ROOT CA is unknown in verify_none mode"}].
+     [{doc,"Test that the client succeeds if the ROOT CA is unknown in verify_none mode"}].
 
 missing_root_cert_no_auth(Config) ->
     ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
diff --git a/lib/ssl/test/ssl_dist_SUITE.erl b/lib/ssl/test/ssl_dist_SUITE.erl
index 0a9fe2c725..493a19b4fa 100644
--- a/lib/ssl/test/ssl_dist_SUITE.erl
+++ b/lib/ssl/test/ssl_dist_SUITE.erl
@@ -118,7 +118,7 @@ init_per_suite(Config0) ->
 init_per_suite(Config0) ->
     try crypto:start() of
 	ok ->
-	    %% Currently no ct function avilable for is_cover!
+	    %% Currently no ct function available for is_cover!
 	    case test_server:is_cover() of
 		false ->
 		    Config = add_ssl_opts_config(Config0),
diff --git a/lib/ssl/test/ssl_engine_SUITE.erl b/lib/ssl/test/ssl_engine_SUITE.erl
index 296211d751..076399c5dd 100644
--- a/lib/ssl/test/ssl_engine_SUITE.erl
+++ b/lib/ssl/test/ssl_engine_SUITE.erl
@@ -159,10 +159,10 @@ private_key(Config) when is_list(Config) ->
     test_tls_connection([{ciphers, RSASuites}, {versions, ['tlsv1.2']} | EngineServerConf], 
                         [{ciphers, RSASuites}, {versions, ['tlsv1.2']} | EngineClientConf], Config),
     
-    %% Test with engine and present file arugments
+    %% Test with engine and present file arguments
     test_tls_connection(EngineFileServerConf, EngineFileClientConf, Config),
     
-    %% Test that sofware fallback is available
+    %% Test that software fallback is available
     test_tls_connection(ServerConf, [{reuse_sessions, false} |ClientConf], Config).
     
 engine_key(Conf) ->
diff --git a/lib/ssl/test/ssl_packet_SUITE.erl b/lib/ssl/test/ssl_packet_SUITE.erl
index 97237c018c..9e5d8ebdf3 100644
--- a/lib/ssl/test/ssl_packet_SUITE.erl
+++ b/lib/ssl/test/ssl_packet_SUITE.erl
@@ -875,7 +875,7 @@ packet_size_passive(Config) when is_list(Config) ->
 
 %%--------------------------------------------------------------------
 packet_switch() ->
-    [{doc,"Test packet option {packet, 2} followd by {packet, 4}"}].
+    [{doc,"Test packet option {packet, 2} followed by {packet, 4}"}].
 
 packet_switch(Config) when is_list(Config) ->
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
diff --git a/lib/ssl/test/ssl_payload_SUITE.erl b/lib/ssl/test/ssl_payload_SUITE.erl
index 1eb02fe30d..f4b29798ec 100644
--- a/lib/ssl/test/ssl_payload_SUITE.erl
+++ b/lib/ssl/test/ssl_payload_SUITE.erl
@@ -556,7 +556,7 @@ client_echos_active_huge(Config) when is_list(Config) ->
 %%--------------------------------------------------------------------
 client_active_once_server_close() ->
     [{doc, "Server sends 500000 bytes and immediately after closes the connection"
-     "Make sure client recives all data if possible"}].
+     "Make sure client receives all data if possible"}].
 
 client_active_once_server_close(Config) when is_list(Config) -> 
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
diff --git a/lib/ssl/test/ssl_pem_cache_SUITE.erl b/lib/ssl/test/ssl_pem_cache_SUITE.erl
index 86c8ac7412..fed1a93007 100644
--- a/lib/ssl/test/ssl_pem_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_pem_cache_SUITE.erl
@@ -139,7 +139,7 @@ pem_cleanup(Config)when is_list(Config) ->
     false = Size == Size1.
 
 clear_pem_cache() ->
-    [{doc,"Test that internal reference tabel is cleaned properly even when "
+    [{doc,"Test that internal reference table is cleaned properly even when "
      " the PEM cache is cleared" }].
 clear_pem_cache(Config) when is_list(Config) -> 
     {status, _, _, StatusInfo} = sys:get_status(whereis(ssl_manager)),
diff --git a/lib/ssl/test/ssl_session_cache_SUITE.erl b/lib/ssl/test/ssl_session_cache_SUITE.erl
index eab51e8555..d48bcd8d56 100644
--- a/lib/ssl/test/ssl_session_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_session_cache_SUITE.erl
@@ -232,7 +232,7 @@ client_unique_session(Config) when is_list(Config) ->
     ssl_test_lib:close(LastClient).
 		
 session_cleanup() ->
-    [{doc, "Test that sessions are cleand up eventually, so that the session table "
+    [{doc, "Test that sessions are cleaned up eventually, so that the session table "
      "does not grow and grow ..."}].
 session_cleanup(Config) when is_list(Config) ->
     process_flag(trap_exit, true),
diff --git a/lib/ssl/test/ssl_socket_SUITE.erl b/lib/ssl/test/ssl_socket_SUITE.erl
index e10ec5afaf..5f0ea76626 100644
--- a/lib/ssl/test/ssl_socket_SUITE.erl
+++ b/lib/ssl/test/ssl_socket_SUITE.erl
@@ -403,7 +403,7 @@ invalid_inet_set_option_not_list(Config) when is_list(Config) ->
 
 %%--------------------------------------------------------------------
 invalid_inet_set_option_improper_list() ->
-    [{doc,"Test handling of invalid tye in setopts"}].
+    [{doc,"Test handling of invalid type in setopts"}].
 
 invalid_inet_set_option_improper_list(Config) when is_list(Config) ->
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_opts, Config),
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index 1ed050c6bb..beabdcb8de 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -984,7 +984,7 @@ client_loop(_Node, Host, Port, Pid, Transport, Options, Opts) ->
 		    ct:sleep(?SLEEP),
 		    run_client(Opts);
 	       _ ->
-		    ct:log("~p:~p~nClient faild several times: connection failed: ~p ~n", [?MODULE,?LINE, Reason]),
+		    ct:log("~p:~p~nClient failed several times: connection failed: ~p ~n", [?MODULE,?LINE, Reason]),
 		    Pid ! {self(), {error, Reason}}
 	    end;
 	{error, econnreset = Reason} ->
@@ -996,7 +996,7 @@ client_loop(_Node, Host, Port, Pid, Transport, Options, Opts) ->
 		    ct:sleep(?SLEEP),
 		    run_client(Opts);
 	       _ ->
-		    ct:log("~p:~p~nClient faild several times: connection failed: ~p ~n", [?MODULE,?LINE, Reason]),
+		    ct:log("~p:~p~nClient failed several times: connection failed: ~p ~n", [?MODULE,?LINE, Reason]),
 		    Pid ! {self(), {error, Reason}}
 	    end;
 	{error, Reason} ->
@@ -3088,7 +3088,7 @@ is_fips(crypto) ->
             true
     end.
 
-%% Acctual support is tested elsewhere, this is to exclude some LibreSSL and OpenSSL versions
+%% Actual support is tested elsewhere, this is to exclude some LibreSSL and OpenSSL versions
 openssl_sane_dtls() -> 
     case portable_cmd("openssl", ["version"]) of
         "OpenSSL 0." ++ _ ->
diff --git a/lib/ssl/test/tls_api_SUITE.erl b/lib/ssl/test/tls_api_SUITE.erl
index f41222a2a3..e2e1629336 100644
--- a/lib/ssl/test/tls_api_SUITE.erl
+++ b/lib/ssl/test/tls_api_SUITE.erl
@@ -401,7 +401,7 @@ tls_shutdown_error(Config) when is_list(Config) ->
     {error, closed} = ssl:shutdown(Listen, read_write).
 %%--------------------------------------------------------------------
 tls_client_closes_socket() ->
-    [{doc,"Test what happens when client closes socket before handshake is compleated"}].
+    [{doc,"Test what happens when client closes socket before handshake is completed"}].
 
 tls_client_closes_socket(Config) when is_list(Config) -> 
     ServerOpts = ssl_test_lib:ssl_options(server_opts, Config),
@@ -642,7 +642,7 @@ tls_dont_crash_on_handshake_garbage(Config) ->
 
 %%--------------------------------------------------------------------
 tls_tcp_error_propagation_in_active_mode() ->
-    [{doc,"Test that process recives {ssl_error, Socket, closed} when tcp error ocurres"}].
+    [{doc,"Test that process receives {ssl_error, Socket, closed} when tcp error ocurres"}].
 tls_tcp_error_propagation_in_active_mode(Config) when is_list(Config) ->
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_opts, Config),
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
-- 
2.31.1

openSUSE Build Service is sponsored by