File 0858-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
@@ -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/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/ssl.erl b/lib/ssl/src/ssl.erl
index 017ca03117..d1ca621e22 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -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_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
%%----------------------------------------------------------------------
@@ -1965,7 +1965,7 @@ decode_extensions(<<?UINT16(?EC_POINT_FORMATS_EXT), ?UINT16(Len),
ECPointFormats}});
dec_hello_extensions(<<?UINT16(?SNI_EXT), ?UINT16(Len), Rest/binary>>, Acc) when Len == 0 ->
- dec_hello_extensions(Rest, Acc#hello_extensions{sni = #sni{hostname = ""}}); %% Server may send an empy SNI
+ dec_hello_extensions(Rest, Acc#hello_extensions{sni = #sni{hostname = ""}}); %% Server may send an empty SNI
dec_hello_extensions(<<?UINT16(?SNI_EXT), ?UINT16(Len),
ExtData:Len/binary, Rest/binary>>, Acc) ->
@@ -2204,7 +2204,7 @@ maybe_check_crl(OtpCert, #{crl_check := Check,
dps_and_crls(OtpCert, Callback, CRLDbHandle, same_issuer),
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, dps_and_crls(OtpCert, Callback,
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, 16#FFFFFFFFFFFFFFFFC90FDAA22168C234C4C6628B80DC1CD129024E088A67CC74020BBEA63B139B22514A08798E3404DDEF9519B3CD3A431B302B0A6DF25F14374FE1356D6D51C245E485B576625E7EC6F44C42E9A637ED6B0BFF5CB6F406B7EDEE386BFB5A899FA5AE9F24117C4B1FE649286651ECE65381FFFFFFFFFFFFFFFF).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% 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, PemCache | _]} = State) ->
case ssl_pkix_db:lookup(Ref, RefDb) of
- undefined -> %% Alredy cleaned
+ undefined -> %% Already cleaned
ok;
_ ->
clean_cert_db(Ref, CertDb, RefDb, PemCache, 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
%%----------------------------------------------------------------------
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
%%----------------------------------------------------------------------
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_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/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
@@ -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).
shutdown_both_result(Socket, server) ->
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_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_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} ->
--
2.31.1