Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
3831-ssl-Add-debug-logging-on-error-cases.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3831-ssl-Add-debug-logging-on-error-cases.patch of Package erlang
From cbf8825e0d11995bb2c4cbe9100f08e0e8138b90 Mon Sep 17 00:00:00 2001 From: Dan Gudmundsson <dgud@erlang.org> Date: Thu, 3 Nov 2022 16:36:06 +0100 Subject: [PATCH] ssl: Add debug logging on error cases To ease the debugging add info/debug logs whenever an error is caught so that is easy to find out what happened. Also set the default debug level per connection to the application level, or rather the module ssl level since the application level is not stored. --- lib/ssl/src/dtls_connection.erl | 17 +++++---- lib/ssl/src/ssl.erl | 14 +++++-- lib/ssl/src/ssl_cipher.erl | 6 ++- lib/ssl/src/ssl_gen_statem.erl | 19 ++++------ lib/ssl/src/ssl_handshake.erl | 59 ++++++++++++++++------------- lib/ssl/src/ssl_internal.hrl | 21 +++++++++- lib/ssl/src/ssl_logger.erl | 4 +- lib/ssl/src/ssl_pkix_db.erl | 2 +- lib/ssl/src/ssl_record.erl | 7 +++- lib/ssl/src/tls_connection.erl | 20 ++++++---- lib/ssl/src/tls_connection_1_3.erl | 1 + lib/ssl/src/tls_dtls_connection.erl | 25 ++++++------ lib/ssl/src/tls_gen_connection.erl | 6 ++- lib/ssl/src/tls_handshake.erl | 9 +++-- lib/ssl/src/tls_handshake_1_3.erl | 17 +++++---- lib/ssl/src/tls_record_1_3.erl | 7 +++- lib/ssl/test/ssl_cipher_SUITE.erl | 10 ++++- 17 files changed, 152 insertions(+), 92 deletions(-) diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl index 8f2eb7d82b..ff7fee47f0 100644 --- a/lib/ssl/src/dtls_connection.erl +++ b/lib/ssl/src/dtls_connection.erl @@ -163,16 +163,15 @@ %%==================================================================== init([Role, Host, Port, Socket, Options, User, CbInfo]) -> process_flag(trap_exit, true), - State0 = #state{protocol_specific = Map} = - initial_state(Role, Host, Port, Socket, Options, User, CbInfo), + State0 = initial_state(Role, Host, Port, Socket, Options, User, CbInfo), try State = ssl_gen_statem:ssl_config(State0#state.ssl_options, Role, State0), gen_statem:enter_loop(?MODULE, [], initial_hello, State) catch throw:Error -> - EState = State0#state{protocol_specific = - Map#{error => Error}}, + #state{protocol_specific = Map} = State0, + EState = State0#state{protocol_specific = Map#{error => Error}}, gen_statem:enter_loop(?MODULE, [], config_error, EState) end. %%==================================================================== @@ -644,6 +643,7 @@ format_status(Type, Data) -> initial_state(Role, Host, Port, Socket, {#{client_renegotiation := ClientRenegotiation} = SSLOptions, SocketOptions, Trackers}, User, {CbModule, DataTag, CloseTag, ErrorTag, PassiveTag}) -> + put(log_level, maps:get(log_level, SSLOptions)), BeastMitigation = maps:get(beast_mitigation, SSLOptions, disabled), ConnectionStates = dtls_record:init_connection_states(Role, BeastMitigation), #{session_cb := SessionCacheCb} = ssl_config:pre_1_3_session_opts(Role), @@ -754,20 +754,23 @@ gen_handshake(StateName, Type, Event, State) -> catch throw:#alert{}=Alert -> alert_or_reset_connection(Alert, StateName, State); - error:_ -> + error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), Alert = ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data), alert_or_reset_connection(Alert, StateName, State) end. gen_info(Event, connection = StateName, State) -> try dtls_gen_connection:handle_info(Event, StateName, State) - catch error:_ -> + catch error:Reason:ST -> + ?SSL_LOG(info, internal_error, [{error, Reason}, {stacktrace, ST}]), Alert = ?ALERT_REC(?FATAL, ?INTERNAL_ERROR, malformed_data), alert_or_reset_connection(Alert, StateName, State) end; gen_info(Event, StateName, State) -> try dtls_gen_connection:handle_info(Event, StateName, State) - catch error:_ -> + catch error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), Alert = ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,malformed_handshake_data), alert_or_reset_connection(Alert, StateName, State) end. diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl index 8050b354bd..7b42eb84c1 100644 --- a/lib/ssl/src/ssl.erl +++ b/lib/ssl/src/ssl.erl @@ -1726,6 +1726,13 @@ handle_option(key_update_at = Option, Value0, #{versions := Versions} = OptionsM assert_option_dependency(Option, versions, Versions, ['tlsv1.3']), Value = validate_option(Option, Value0), OptionsMap#{Option => Value}; +handle_option(log_level = Option, unbound, OptionsMap, _Env) -> + DefaultLevel = case logger:get_module_level(?MODULE) of + [] -> notice; + [{ssl,Level}] -> Level + end, + Value = validate_option(Option, DefaultLevel), + OptionsMap#{Option => Value}; handle_option(next_protocols_advertised = Option, unbound, OptionsMap, #{rules := Rules}) -> Value = validate_option(Option, default_value(Option, Rules)), @@ -2875,9 +2882,10 @@ add_filter(Filter, Filters) -> maybe_client_warn_no_verify(#{verify := verify_none, warn_verify_none := true, log_level := LogLevel}, client) -> - ssl_logger:log(warning, LogLevel, #{description => "Server authenticity is not verified since certificate path validation is not enabled", - reason => "The option {verify, verify_peer} and one of the options 'cacertfile' or " - "'cacerts' are required to enable this."}, ?LOCATION); + ssl_logger:log(warning, LogLevel, + #{description => "Server authenticity is not verified since certificate path validation is not enabled", + reason => "The option {verify, verify_peer} and one of the options 'cacertfile' or " + "'cacerts' are required to enable this."}, ?LOCATION); maybe_client_warn_no_verify(_,_) -> %% Warning not needed. Note client certificate validation is optional in TLS ok. diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl index f567bd6c53..2c52fc5e8d 100644 --- a/lib/ssl/src/ssl_cipher.erl +++ b/lib/ssl/src/ssl_cipher.erl @@ -260,12 +260,13 @@ decipher(?RC4, HashSz, CipherState = #cipher_state{state = State}, Fragment, _, #generic_stream_cipher{content = Content, mac = Mac} = GSC, {Content, Mac, CipherState} catch - _:_ -> + _:Reason:ST -> %% This is a DECRYPTION_FAILED but %% "differentiating between bad_record_mac and decryption_failed %% alerts may permit certain attacks against CBC mode as used in %% TLS [CBCATT]. It is preferable to uniformly use the %% bad_record_mac alert to hide the specific type of the error." + ?SSL_LOG(debug, decrypt_error, [{reason,Reason}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end; @@ -305,12 +306,13 @@ block_decipher(Fun, #cipher_state{key=Key, iv=IV} = CipherState0, {<<16#F0, Content/binary>>, Mac, CipherState1} end catch - _:_ -> + _:Reason:ST -> %% This is a DECRYPTION_FAILED but %% "differentiating between bad_record_mac and decryption_failed %% alerts may permit certain attacks against CBC mode as used in %% TLS [CBCATT]. It is preferable to uniformly use the %% bad_record_mac alert to hide the specific type of the error." + ?SSL_LOG(debug, decrypt_error, [{reason,Reason}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end. diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl index 2f59b150ca..36768ab6c7 100644 --- a/lib/ssl/src/ssl_gen_statem.erl +++ b/lib/ssl/src/ssl_gen_statem.erl @@ -25,8 +25,6 @@ -module(ssl_gen_statem). --include_lib("kernel/include/logger.hrl"). - -include("ssl_api.hrl"). -include("ssl_internal.hrl"). -include("ssl_connection.hrl"). @@ -853,10 +851,9 @@ handle_info({ErrorTag, Socket, econnaborted}, StateName, handle_info({ErrorTag, Socket, Reason}, StateName, #state{static_env = #static_env{ role = Role, socket = Socket, - error_tag = ErrorTag}, - ssl_options = #{log_level := Level}} = State) -> - ssl_logger:log(info, Level, #{description => "Socket error", - reason => [{error_tag, ErrorTag}, {description, Reason}]}, ?LOCATION), + error_tag = ErrorTag} + } = State) -> + ?SSL_LOG(info, "Socket error", [{error_tag, ErrorTag}, {description, Reason}]), Alert = ?ALERT_REC(?FATAL, ?CLOSE_NOTIFY, {transport_error, Reason}), handle_normal_shutdown(Alert#alert{role = Role}, StateName, State), {stop, {shutdown,normal}, State}; @@ -883,11 +880,9 @@ handle_info({'EXIT', Socket, Reason}, _StateName, #state{static_env = #static_en {stop,{shutdown, Reason}, State}; handle_info(allow_renegotiate, StateName, #state{handshake_env = HsEnv} = State) -> %% PRE TLS-1.3 {next_state, StateName, State#state{handshake_env = HsEnv#handshake_env{allow_renegotiate = true}}}; -handle_info(Msg, StateName, #state{static_env = #static_env{socket = Socket, error_tag = ErrorTag}, - ssl_options = #{log_level := Level}} = State) -> - ssl_logger:log(notice, Level, #{description => "Unexpected INFO message", - reason => [{message, Msg}, {socket, Socket}, - {error_tag, ErrorTag}]}, ?LOCATION), +handle_info(Msg, StateName, #state{static_env = #static_env{socket = Socket, error_tag = ErrorTag}} = State) -> + ?SSL_LOG(notice, "Unexpected INFO message", + [{message, Msg}, {socket, Socket}, {error_tag, ErrorTag}]), {next_state, StateName, State}. %%==================================================================== @@ -1180,7 +1175,7 @@ terminate(Reason, connection, #state{static_env = #static_env{ handle_trusted_certs_db(State), Alert = terminate_alert(Reason), %% Send the termination ALERT if possible - catch (ok = Connection:send_alert_in_connection(Alert, State)), + catch Connection:send_alert_in_connection(Alert, State), Connection:close({timeout, ?DEFAULT_TIMEOUT}, Socket, Transport, ConnectionStates); terminate(Reason, _StateName, #state{static_env = #static_env{transport_cb = Transport, protocol_cb = Connection, diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 3b3e2c50e7..65a47bf912 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -358,7 +358,8 @@ certify(#certificate{asn1_certificates = ASN1Certs}, CertDbHandle, CertDbRef, error:{_,{error, {asn1, Asn1Reason}}} -> %% ASN-1 decode of certificate somehow failed ?ALERT_REC(?FATAL, ?CERTIFICATE_UNKNOWN, {failed_to_decode_certificate, Asn1Reason}); - error:OtherReason -> + error:OtherReason:ST -> + ?SSL_LOG(info, internal_error, [{error, OtherReason}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?INTERNAL_ERROR, {unexpected_error, OtherReason}) end. %%-------------------------------------------------------------------- @@ -427,7 +428,8 @@ master_secret(Version, #session{master_secret = Mastersecret}, try master_secret(Version, Mastersecret, SecParams, ConnectionStates, Role) catch - exit:_ -> + exit:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, key_calculation_failure) end; @@ -443,7 +445,8 @@ master_secret(Version, PremasterSecret, ConnectionStates, Role) -> ClientRandom, ServerRandom), SecParams, ConnectionStates, Role) catch - exit:_ -> + exit:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, master_secret_calculation_failure) end. @@ -1134,26 +1137,27 @@ supported_ecc(_) -> #elliptic_curves{elliptic_curve_list = []}. premaster_secret(OtherPublicDhKey, MyPrivateKey, #'DHParameter'{} = Params) -> - try - public_key:compute_key(OtherPublicDhKey, MyPrivateKey, Params) - catch - error:computation_failed -> + try + public_key:compute_key(OtherPublicDhKey, MyPrivateKey, Params) + catch + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) - end; + end; premaster_secret(PublicDhKey, PrivateDhKey, #server_dh_params{dh_p = Prime, dh_g = Base}) -> - try + try crypto:compute_key(dh, PublicDhKey, PrivateDhKey, [Prime, Base]) - catch - error:computation_failed -> + catch + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) end; premaster_secret(#client_srp_public{srp_a = ClientPublicKey}, ServerKey, #srp_user{prime = Prime, verifier = Verifier}) -> - try crypto:compute_key(srp, ClientPublicKey, ServerKey, {host, [Verifier, Prime, '6a']}) of - PremasterSecret -> - PremasterSecret + try crypto:compute_key(srp, ClientPublicKey, ServerKey, {host, [Verifier, Prime, '6a']}) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) end; premaster_secret(#server_srp_params{srp_n = Prime, srp_g = Generator, srp_s = Salt, srp_b = Public}, @@ -1161,14 +1165,13 @@ premaster_secret(#server_srp_params{srp_n = Prime, srp_g = Generator, srp_s = Sa case ssl_srp_primes:check_srp_params(Generator, Prime) of ok -> DerivedKey = crypto:hash(sha, [Salt, crypto:hash(sha, [Username, <<$:>>, Password])]), - try crypto:compute_key(srp, Public, ClientKeys, {user, [DerivedKey, Prime, Generator, '6a']}) of - PremasterSecret -> - PremasterSecret + try crypto:compute_key(srp, Public, ClientKeys, {user, [DerivedKey, Prime, Generator, '6a']}) catch - error -> + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) end; - _ -> + not_accepted -> throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) end; premaster_secret(#client_rsa_psk_identity{ @@ -1214,14 +1217,16 @@ premaster_secret(EncSecret, #'RSAPrivateKey'{} = RSAPrivateKey) -> try public_key:decrypt_private(EncSecret, RSAPrivateKey, [{rsa_pad, rsa_pkcs1_padding}]) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(debug, decrypt_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?DECRYPT_ERROR)) end; premaster_secret(EncSecret, #{algorithm := rsa} = Engine) -> try crypto:private_decrypt(rsa, EncSecret, maps:remove(algorithm, Engine), [{rsa_pad, rsa_pkcs1_padding}]) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(debug, decrypt_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?DECRYPT_ERROR)) end. %%==================================================================== @@ -2101,11 +2106,10 @@ path_validation_alert(Reason) -> digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) -> - try do_digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) of - Signature -> - Signature + try do_digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(info, sign_error, [{error, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, bad_key(PrivateKey))) end. @@ -2288,7 +2292,8 @@ encrypted_premaster_secret(Secret, RSAPublicKey) -> rsa_pkcs1_padding}]), #encrypted_premaster_secret{premaster_secret = PreMasterSecret} catch - _:_-> + _:Reason:ST-> + ?SSL_LOG(debug, encrypt_error, [{reason, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, premaster_encryption_failed)) end. diff --git a/lib/ssl/src/ssl_internal.hrl b/lib/ssl/src/ssl_internal.hrl index 6b1bd360f8..cdb3154cb6 100644 --- a/lib/ssl/src/ssl_internal.hrl +++ b/lib/ssl/src/ssl_internal.hrl @@ -23,7 +23,8 @@ -ifndef(ssl_internal). -define(ssl_internal, true). --include_lib("public_key/include/public_key.hrl"). +-include_lib("kernel/include/logger.hrl"). +-include_lib("public_key/include/public_key.hrl"). -define(SECRET_PRINTOUT, "***"). @@ -270,6 +271,24 @@ {stop, any(), any()}. -type ssl_options() :: map(). + +-define(SSL_LOG(Level, Descr, Reason), + fun() -> + case get(log_level) of + undefined -> + %% Use debug here, i.e. log everything and let loggers + %% log_level decide if it should be logged + ssl_logger:log(Level, debug, + #{description => Descr, reason => Reason}, + ?LOCATION); + __LogLevel__ -> + ssl_logger:log(Level, __LogLevel__, + #{description => Descr, reason => Reason}, + ?LOCATION) + end + end()). + + %% Internal ticket data record holding pre-processed ticket data. -record(ticket_data, {key, %% key in client ticket store diff --git a/lib/ssl/src/ssl_logger.erl b/lib/ssl/src/ssl_logger.erl index 9e872587e2..8f528b40ce 100644 --- a/lib/ssl/src/ssl_logger.erl +++ b/lib/ssl/src/ssl_logger.erl @@ -57,10 +57,10 @@ log(Level, LogLevel, ReportMap, Meta) -> ok end. -debug(Level, Direction, Protocol, Message) +debug(LogLevel, Direction, Protocol, Message) when (Direction =:= inbound orelse Direction =:= outbound) andalso (Protocol =:= 'record' orelse Protocol =:= 'handshake') -> - case logger:compare_levels(Level, debug) of + case logger:compare_levels(LogLevel, debug) of lt -> ?LOG_DEBUG(#{direction => Direction, protocol => Protocol, diff --git a/lib/ssl/src/ssl_pkix_db.erl b/lib/ssl/src/ssl_pkix_db.erl index 056d772644..eac9e2a8b3 100644 --- a/lib/ssl/src/ssl_pkix_db.erl +++ b/lib/ssl/src/ssl_pkix_db.erl @@ -117,7 +117,7 @@ lookup_trusted_cert(_DbHandle, {extracted,Certs}, SerialNumber, Issuer) -> CertSerial =:= SerialNumber, CertIssuer =:= Issuer], undefined catch - Cert -> + throw:Cert -> {ok, Cert} end. diff --git a/lib/ssl/src/ssl_record.erl b/lib/ssl/src/ssl_record.erl index 03acf70c40..b7b68edd82 100644 --- a/lib/ssl/src/ssl_record.erl +++ b/lib/ssl/src/ssl_record.erl @@ -447,11 +447,14 @@ decipher_aead(Type, #cipher_state{key = Key} = CipherState, AAD0, CipherFragment case ssl_cipher:aead_decrypt(Type, Key, Nonce, CipherText, CipherTag, AAD) of Content when is_binary(Content) -> Content; - _ -> + Reason -> + ?SSL_LOG(debug, decrypt_error, [{reason,Reason}, + {stacktrace, process_info(self(), current_stacktrace)}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end catch - _:_ -> + _:Reason2:ST -> + ?SSL_LOG(debug, decrypt_error, [{reason,Reason2}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end. diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl index 5c5b22d909..6cc9e21cfb 100644 --- a/lib/ssl/src/tls_connection.erl +++ b/lib/ssl/src/tls_connection.erl @@ -140,10 +140,9 @@ %% Internal application API %%==================================================================== init([Role, Sender, Host, Port, Socket, Options, User, CbInfo]) -> - State0 = #state{protocol_specific = Map} = initial_state(Role, Sender, - Host, Port, Socket, Options, User, CbInfo), - try - State1 = #state{static_env = #static_env{session_cache = Cache, + State0 = initial_state(Role, Sender, Host, Port, Socket, Options, User, CbInfo), + try + State1 = #state{static_env = #static_env{session_cache = Cache, session_cache_cb = CacheCb }, connection_env = #connection_env{cert_key_alts = CertKeyAlts}, @@ -160,6 +159,7 @@ init([Role, Sender, Host, Port, Socket, Options, User, CbInfo]) -> tls_gen_connection:initialize_tls_sender(State), gen_statem:enter_loop(?MODULE, [], initial_hello, State) catch throw:Error -> + #state{protocol_specific = Map} = State0, EState = State0#state{protocol_specific = Map#{error => Error}}, gen_statem:enter_loop(?MODULE, [], config_error, EState) end. @@ -386,8 +386,9 @@ connection(internal, #hello_request{}, ConnectionStates#{current_write => Write}, session = Session}), tls_gen_connection:next_event(hello, no_record, State, Actions) - catch - _:_ -> + catch + _:Reason:ST -> + ?SSL_LOG(info, internal_error, [{error, Reason}, {stacktrace, ST}]), {stop, {shutdown, sender_blocked}, State0} end; connection(internal, #hello_request{}, @@ -474,6 +475,7 @@ code_change(_OldVsn, StateName, State, _) -> %%-------------------------------------------------------------------- initial_state(Role, Sender, Host, Port, Socket, {SSLOptions, SocketOptions, Trackers}, User, {CbModule, DataTag, CloseTag, ErrorTag, PassiveTag}) -> + put(log_level, maps:get(log_level, SSLOptions)), #{erl_dist := IsErlDist, %% Use highest supported version for client/server random nonce generation versions := [Version|_], @@ -564,7 +566,8 @@ gen_info(Event, connection = StateName, State) -> try tls_gen_connection:handle_info(Event, StateName, State) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(info, internal_error, [{error, Reason}, {stacktrace, ST}]), ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, malformed_data), StateName, State) @@ -574,7 +577,8 @@ gen_info(Event, StateName, State) -> try tls_gen_connection:handle_info(Event, StateName, State) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data), StateName, State) diff --git a/lib/ssl/src/tls_connection_1_3.erl b/lib/ssl/src/tls_connection_1_3.erl index b1fe0c69f5..0de4ea8bcd 100644 --- a/lib/ssl/src/tls_connection_1_3.erl +++ b/lib/ssl/src/tls_connection_1_3.erl @@ -604,6 +604,7 @@ do_client_start(ServerHello, State0) -> initial_state(Role, Sender, Host, Port, Socket, {SSLOptions, SocketOptions, Trackers}, User, {CbModule, DataTag, CloseTag, ErrorTag, PassiveTag}) -> + put(log_level, maps:get(log_level, SSLOptions)), #{%% Use highest supported version for client/server random nonce generation versions := [Version|_], client_renegotiation := ClientRenegotiation} = SSLOptions, diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl index 1b1c724a1f..6882e8af34 100644 --- a/lib/ssl/src/tls_dtls_connection.erl +++ b/lib/ssl/src/tls_dtls_connection.erl @@ -686,7 +686,8 @@ downgrade(Type, Event, State) -> gen_handshake(StateName, Type, Event, State) -> try tls_dtls_connection:StateName(Type, Event, State) - catch error:_ -> + catch error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)) end. @@ -718,8 +719,12 @@ handle_call({prf, Secret, Label, Seed, WantedLength}, From, _, end, [], Seed)), ssl_handshake:prf(ssl:tls_version(Version), PRFAlgorithm, SecretToUse, Label, SeedToUse, WantedLength) catch - exit:_ -> {error, badarg}; - error:Reason -> {error, Reason} + exit:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), + {error, badarg}; + error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), + {error, Reason} end, {keep_state_and_data, [{reply, From, Reply}]}; handle_call(Msg, From, StateName, State) -> @@ -1484,22 +1489,20 @@ generate_srp_server_keys(_SrpParams, 10) -> generate_srp_server_keys(SrpParams = #srp_user{generator = Generator, prime = Prime, verifier = Verifier}, N) -> - try crypto:generate_key(srp, {host, [Verifier, Generator, Prime, '6a']}) of - Keys -> - Keys + try crypto:generate_key(srp, {host, [Verifier, Generator, Prime, '6a']}) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{error, Reason}, {stacktrace, ST}]), generate_srp_server_keys(SrpParams, N+1) end. generate_srp_client_keys(_Generator, _Prime, 10) -> throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)); generate_srp_client_keys(Generator, Prime, N) -> - try crypto:generate_key(srp, {user, [Generator, Prime, '6a']}) of - Keys -> - Keys + try crypto:generate_key(srp, {user, [Generator, Prime, '6a']}) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{error, Reason}, {stacktrace, ST}]), generate_srp_client_keys(Generator, Prime, N+1) end. diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl index d58489bb55..da7144e413 100644 --- a/lib/ssl/src/tls_gen_connection.erl +++ b/lib/ssl/src/tls_gen_connection.erl @@ -468,7 +468,8 @@ handle_protocol_record(#ssl_tls{type = ?ALERT, fragment = EncAlerts}, StateName, #alert{} = Alert -> ssl_gen_statem:handle_own_alert(Alert, StateName, State) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{error, Reason}, {stacktrace, ST}]), ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, alert_decode_error), StateName, State) @@ -525,7 +526,8 @@ send_sync_alert( Alert, #state{protocol_specific = #{sender := Sender}} = State) -> try tls_sender:send_and_ack_alert(Sender, Alert) catch - _:_ -> + _:Reason:ST -> + ?SSL_LOG(info, "Send failed", [{error, Reason}, {stacktrace, ST}]), throw({stop, {shutdown, own_alert}, State}) end. diff --git a/lib/ssl/src/tls_handshake.erl b/lib/ssl/src/tls_handshake.erl index aba6efcdc9..7704ff7b6b 100644 --- a/lib/ssl/src/tls_handshake.erl +++ b/lib/ssl/src/tls_handshake.erl @@ -245,7 +245,8 @@ hello(#client_hello{client_version = _ClientVersion, SelectedVersion = ssl_handshake:select_supported_version(ClientVersions, Versions), do_hello(SelectedVersion, Versions, CipherSuites, Hello, SslOpts, Info, Renegotiation) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{reason,Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)) end; @@ -260,7 +261,8 @@ hello(#client_hello{client_version = ClientVersion, error:{case_clause,{asn1, Asn1Reason}} -> %% ASN-1 decode of certificate somehow failed throw(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, {failed_to_decode_own_certificate, Asn1Reason})); - error:_ -> + error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{reason,Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)) end. @@ -435,7 +437,8 @@ get_tls_handshakes_aux(Version, <<?BYTE(Type), ?UINT24(Length), ssl_logger:debug(LogLevel, inbound, 'handshake', Handshake), get_tls_handshakes_aux(Version, Rest, Opts, [{Handshake,Raw} | Acc]) catch - error:_ -> + error:Reason:ST -> + ?SSL_LOG(info, handshake_error, [{reason,Reason}, {stacktrace, ST}]), throw(?ALERT_REC(?FATAL, ?DECODE_ERROR, handshake_decode_error)) end; get_tls_handshakes_aux(_Version, Data, _, Acc) -> diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl index dedfb604b0..9caa2a1668 100644 --- a/lib/ssl/src/tls_handshake_1_3.erl +++ b/lib/ssl/src/tls_handshake_1_3.erl @@ -591,21 +591,21 @@ certificate_entry(DER) -> %% 0101010101010101010101010101010101010101010101010101010101010101 sign(THash, Context, HashAlgo, PrivateKey, SignAlgo) -> Content = build_content(Context, THash), - try ssl_handshake:digitally_signed({3,4}, Content, HashAlgo, PrivateKey, SignAlgo) of - Signature -> - {ok, Signature} - catch - error:badarg -> - {error, ?ALERT_REC(?FATAL, ?INTERNAL_ERROR, badarg)} + try + {ok, ssl_handshake:digitally_signed({3,4}, Content, HashAlgo, PrivateKey, SignAlgo)} + catch throw:Alert -> + {error, Alert} end. + verify(THash, Context, HashAlgo, SignAlgo, Signature, PublicKeyInfo) -> Content = build_content(Context, THash), try ssl_handshake:verify_signature({3, 4}, Content, {HashAlgo, SignAlgo}, Signature, PublicKeyInfo) of Result -> {ok, Result} catch - error:badarg -> + error:Reason:ST -> + ?SSL_LOG(debug, handshake_error, [{reason, Reason}, {stacktrace, ST}]), {error, ?ALERT_REC(?FATAL, ?INTERNAL_ERROR, badarg)} end. @@ -907,7 +907,8 @@ do_negotiated({start_handshake, PSK0}, catch {Ref, #alert{} = Alert} -> Alert; - error:badarg -> + error:badarg=Reason:ST -> + ?SSL_LOG(debug, crypto_error, [{reason, Reason}, {stacktrace, ST}]), ?ALERT_REC(?ILLEGAL_PARAMETER, illegal_parameter_to_compute_key) end. diff --git a/lib/ssl/src/tls_record_1_3.erl b/lib/ssl/src/tls_record_1_3.erl index b6439872bd..440d9e0998 100644 --- a/lib/ssl/src/tls_record_1_3.erl +++ b/lib/ssl/src/tls_record_1_3.erl @@ -345,11 +345,14 @@ decipher_aead(CipherFragment, BulkCipherAlgo, Key, Seq, IV, TagLen) -> case ssl_cipher:aead_decrypt(BulkCipherAlgo, Key, Nonce, CipherText, CipherTag, AAD) of Content when is_binary(Content) -> Content; - _ -> + Reason -> + ?SSL_LOG(debug, decrypt_error, [{reason,Reason}, + {stacktrace, process_info(self(), current_stacktrace)}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end catch - _:_ -> + _:Reason2:ST -> + ?SSL_LOG(debug, decrypt_error, [{reason,Reason2}, {stacktrace, ST}]), ?ALERT_REC(?FATAL, ?BAD_RECORD_MAC, decryption_failed) end. diff --git a/lib/ssl/test/ssl_cipher_SUITE.erl b/lib/ssl/test/ssl_cipher_SUITE.erl index 40592870a1..9d7eb20c7a 100644 --- a/lib/ssl/test/ssl_cipher_SUITE.erl +++ b/lib/ssl/test/ssl_cipher_SUITE.erl @@ -74,9 +74,17 @@ end_per_group(_GroupName, Config) -> init_per_testcase(_TestCase, Config) -> ct:timetrap({seconds, 5}), - Config. + _ = application:load(ssl), + Previous = case logger:get_module_level(ssl) of + [] -> notice; + [{ssl,P}] -> P + end, + ok = logger:set_application_level(ssl, debug), + [{app_log_level, Previous}|Config]. end_per_testcase(_TestCase, Config) -> + Previous = proplists:get_value(app_log_level, Config), + logger:set_application_level(ssl, Previous), Config. %%-------------------------------------------------------------------- -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor