File 1531-ssl-Fix-encode-decode-test.patch of Package erlang

From f31f3e0a7ed2fc2f04dcf939117190a22f54e765 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Tue, 28 Oct 2025 13:13:39 +0100
Subject: [PATCH] ssl: Fix encode/decode test

---
 lib/ssl/src/ssl_handshake.erl                 |  34 ++++--
 .../test/property_test/ssl_eqc_handshake.erl  | 107 +++++++++++++-----
 2 files changed, 104 insertions(+), 37 deletions(-)

diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index 84992b81b7..8a975a909b 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -3911,9 +3911,10 @@ empty_extensions() ->
 
 empty_extensions(?TLS_1_3, client_hello) ->
     #{
+      %% Commented are not currently implemented
       sni => undefined,
-      %% max_frag_enum => undefined,
-      %% status_request => undefined,
+      max_frag_enum => undefined,
+      status_request => undefined,
       elliptic_curves => undefined,
       signature_algs => undefined,
       use_srtp => undefined,
@@ -3926,10 +3927,11 @@ empty_extensions(?TLS_1_3, client_hello) ->
       key_share => undefined,
       pre_shared_key => undefined,
       psk_key_exchange_modes => undefined,
-      %% early_data => undefined,
+      early_data => undefined,
       cookie => undefined,
       client_hello_versions => undefined,
       certificate_authorities => undefined,
+      %% oid_filters => undefined
       %% post_handshake_auth => undefined,
       signature_algs_cert => undefined
      };
@@ -3945,21 +3947,33 @@ empty_extensions(_, client_hello) ->
       elliptic_curves => undefined,
       sni => undefined};
 empty_extensions(?TLS_1_3, server_hello) ->
-    #{server_hello_selected_version => undefined,
+    #{
       key_share => undefined,
-      pre_shared_key => undefined
+      pre_shared_key => undefined,
+      server_hello_selected_version => undefined
      };
 empty_extensions(?TLS_1_3, hello_retry_request) ->
-    #{server_hello_selected_version => undefined,
-      key_share => undefined,
-      pre_shared_key => undefined, %% TODO remove!
-      cookie => undefined
+    #{key_share => undefined,
+      cookie => undefined,
+      server_hello_selected_version => undefined
      };
 empty_extensions(_, server_hello) ->
     #{renegotiation_info => undefined,
       alpn => undefined,
       next_protocol_negotiation => undefined,
-      ec_point_formats => undefined}.
+      ec_point_formats => undefined};
+empty_extensions(?TLS_1_3, encrypted_extensions) ->
+    #{
+      sni => undefined,
+      max_frag_enum => undefined,
+      elliptic_curves => undefined,
+      use_srtp => undefined,
+      %% heartbeat => undefined,
+      alpn => undefined,
+      %% client_cert_type => undefined,
+      %% server_cert_type => undefined,
+      early_data => undefined
+     }.
 
 handle_log(Level, {LogLevel, ReportMap, Meta}) ->
     ssl_logger:log(Level, LogLevel, ReportMap, Meta).
diff --git a/lib/ssl/test/property_test/ssl_eqc_handshake.erl b/lib/ssl/test/property_test/ssl_eqc_handshake.erl
index f68d649205..84ee5ced1d 100644
--- a/lib/ssl/test/property_test/ssl_eqc_handshake.erl
+++ b/lib/ssl/test/property_test/ssl_eqc_handshake.erl
@@ -42,13 +42,52 @@ prop_tls_hs_encode_decode() ->
     ?FORALL({Handshake, TLSVersion}, ?LET(Version, tls_version(), {tls_msg(Version), Version}),
             try 
                 [Type, _Length, Data] = tls_handshake:encode_handshake(Handshake, TLSVersion),
-                tls_handshake:decode_handshake(TLSVersion, Type, Data) == Handshake
+                DecHandshake = tls_handshake:decode_handshake(TLSVersion, Type, Data),
+                RawHandshke = raw_handshake(DecHandshake),
+                RawHandshke == Handshake
             catch
                 throw:#alert{} ->
                     true
             end
 	   ).
 
+raw_handshake(#client_hello{extensions = Ext} = Hello) ->
+    NewExt = raw_ext(Ext),
+    Hello#client_hello{extensions = NewExt};
+raw_handshake(Handshake) ->
+    Handshake.
+
+%% binder_length is saved in decode because we need it later to
+%% truncates client hello in handshake history, but it is not defined
+%% as part of the handshake record but calculated at TLS record
+%% layer. So we want to "unset" it for being able to have a simple
+%% property for encoding/decoding testing. Same goes for hybrid
+%% key_exchange where the decode functions splits the key-share into
+%% the two individual key-share values to use.
+raw_ext(Exts0) ->
+    Exts =  case maps:get(pre_shared_key, Exts0, undefined) of
+                #pre_shared_key_client_hello{} = PSKCH ->
+                    NewPSKCH = PSKCH#pre_shared_key_client_hello{binder_length = undefined},
+                    Exts0#{pre_shared_key => NewPSKCH};
+                _  ->
+                    Exts0
+            end,
+    case maps:get(key_share, Exts, undefined) of
+        #key_share_client_hello{client_shares = CShares} ->
+            NewCShares = [#key_share_entry{group = G, key_exchange = raw_kex(G, Kex)}
+                          || #key_share_entry{group = G, key_exchange = Kex} <- CShares],
+            Exts#{key_share => #key_share_client_hello{client_shares = NewCShares}};
+        _ ->
+            Exts
+    end.
+
+raw_kex(Group, {Bin1, Bin2}) when Group == x25519mlkem768;
+                                  Group == secp256r1mlkem768;
+                                  Group == secp384r1mlkem1024 ->
+    <<Bin1/binary, Bin2/binary>>;
+raw_kex(_, Kex) ->
+    Kex.
+
 %%--------------------------------------------------------------------
 %% Message Generators  -----------------------------------------------
 %%--------------------------------------------------------------------
@@ -249,8 +288,8 @@ pre_shared_keyextension() ->
 extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
      ?LET({
            ServerName,
-           %% MaxFragmentLength,
-           %% StatusRequest,
+           MaxFragmentLength,
+           StatusRequest,
            SupportedGroups,
            SignatureAlgorithms,
            UseSrtp,
@@ -263,8 +302,8 @@ extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
            KeyShare,
            PreSharedKey,
            PSKKeyExchangeModes,
-           %% EarlyData,
-           %% Cookie,
+           EarlyData,
+           Cookie,
            SupportedVersions,
            CertAuthorities,
            %% PostHandshakeAuth,
@@ -272,10 +311,10 @@ extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
           },
           {
            oneof([server_name(), undefined]),
-           %% oneof([max_fragment_length(), undefined]),
-           %% oneof([status_request(), undefined]),
+           oneof([max_fragment_length(), undefined]),
+           oneof([status_request(), undefined]),
            oneof([supported_groups(Version), undefined]),
-           oneof([signature_algs(Version), undefined]),
+           oneof([signature_algs(Version)]),
            oneof([use_srtp(), undefined]),
            %% oneof([heartbeat(), undefined]),
            oneof([alpn(), undefined]),
@@ -286,8 +325,8 @@ extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
            oneof([key_share(MsgType), undefined]),
            oneof([pre_shared_key(MsgType), undefined]),
            oneof([psk_key_exchange_modes(), undefined]),
-           %% oneof([early_data(), undefined]),
-           %% oneof([cookie(), undefined]),
+           oneof([early_data_indication(), undefined]),
+           oneof([cookie(), undefined]),
            oneof([client_hello_versions(Version)]),
            oneof([cert_auths(), undefined]),
            %% oneof([post_handshake_auth(), undefined]),
@@ -300,8 +339,8 @@ extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
                       end,
                       #{
                         sni => ServerName,
-                        %% max_fragment_length => MaxFragmentLength,
-                        %% status_request => StatusRequest,
+                        max_frag_enum => MaxFragmentLength,
+                        status_request => StatusRequest,
                         elliptic_curves => SupportedGroups,
                         signature_algs => SignatureAlgorithms,
                         use_srtp => UseSrtp,
@@ -314,8 +353,8 @@ extensions(?TLS_1_3 = Version, MsgType = client_hello) ->
                         key_share => KeyShare,
                         pre_shared_key => PreSharedKey,
                         psk_key_exchange_modes => PSKKeyExchangeModes,
-                        %% early_data => EarlyData,
-                        %% cookie => Cookie,
+                        early_data => EarlyData,
+                        cookie => Cookie,
                         client_hello_versions => SupportedVersions,
                         certificate_authorities => CertAuthorities,
                         %% post_handshake_auth => PostHandshakeAuth,
@@ -402,25 +441,25 @@ extensions(Version, server_hello) ->
 extensions(?TLS_1_3 = Version, encrypted_extensions) ->
      ?LET({
            ServerName,
-           %% MaxFragmentLength,
+           MaxFragmentLength,
            SupportedGroups,
-           %% UseSrtp,
+           UseSrtp,
            %% Heartbeat,
-           ALPN
+           ALPN,
            %% ClientCertiticateType,
            %% ServerCertificateType,
-           %% EarlyData
+           EarlyData
           },
           {
            oneof([server_name(), undefined]),
-           %% oneof([max_fragment_length(), undefined]),
+           oneof([max_fragment_length(), undefined]),
            oneof([supported_groups(Version), undefined]),
-           %% oneof([use_srtp(), undefined]),
+           oneof([use_srtp(), undefined]),
            %% oneof([heartbeat(), undefined]),
-           oneof([alpn(), undefined])
+           oneof([alpn(), undefined]),
            %% oneof([client_cert_type(), undefined]),
            %% oneof([server_cert_type(), undefined]),
-           %% oneof([early_data(), undefined])
+           oneof([early_data_indication(), undefined])
           },
           maps:filter(fun(_, undefined) ->
                               false;
@@ -429,14 +468,14 @@ extensions(?TLS_1_3 = Version, encrypted_extensions) ->
                       end,
                       #{
                         sni => ServerName,
-                        %% max_fragment_length => MaxFragmentLength,
+                        max_frag_enum => MaxFragmentLength,
                         elliptic_curves => SupportedGroups,
-                        %% use_srtp => UseSrtp,
+                        use_srtp => UseSrtp,
                         %% heartbeat => Heartbeat,
-                        alpn => ALPN
+                        alpn => ALPN,
                         %% client_cert_type => ClientCertificateType,
                         %% server_cert_type => ServerCertificateType,
-                        %% early_data => EarlyData
+                        early_data => EarlyData
                        })).
 
 server_name() ->
@@ -444,6 +483,20 @@ server_name() ->
        ServerName).
     %% sni().
 
+max_fragment_length() ->
+    ?LET(Enum, elements([1,2,3,4]), #max_frag_enum{enum = Enum}).
+
+status_request() ->
+    %% TODO real impl
+    undefined.
+
+early_data_indication() ->
+    elements([#early_data_indication{}, #early_data_indication_nst{indication = 500}]).
+
+cookie() ->
+    %% TODO real impl
+    undefined.
+
 signature_algs_cert() ->
     ?LET(List,  sig_scheme_list(),
          #signature_algorithms_cert{signature_scheme_list = List}).
@@ -471,7 +524,7 @@ sig_scheme_list() ->
                rsa_pss_pss_sha256,
                rsa_pss_pss_sha384,
                rsa_pss_pss_sha512,
-            rsa_pkcs1_sha1,
+               rsa_pkcs1_sha1,
                ecdsa_sha1]
              ]).
 
-- 
2.51.0

openSUSE Build Service is sponsored by