!51 [sync] PR-49: Fix CVE-2025-30211
From: @openeuler-sync-bot Reviewed-by: @lyn1001 Signed-off-by: @lyn1001
This commit is contained in:
commit
723280a762
145
CVE-2025-30211-1.patch
Normal file
145
CVE-2025-30211-1.patch
Normal file
@ -0,0 +1,145 @@
|
||||
From df3aad2c5570847895562ff96a725190571f028c Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Thu, 13 Mar 2025 13:38:29 +0100
|
||||
Subject: [PATCH] ssh: reduce log processing for plain connections
|
||||
|
||||
- avoid unnecessary data processing
|
||||
|
||||
Origin: https://github.com/erlang/otp/commit/df3aad2c5570847895562ff96a725190571f028c
|
||||
---
|
||||
lib/ssh/src/ssh.hrl | 8 ++-
|
||||
lib/ssh/src/ssh_acceptor.erl | 68 +++++++++++++++++---------
|
||||
lib/ssh/src/ssh_connection_handler.erl | 12 +++--
|
||||
3 files changed, 61 insertions(+), 27 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
|
||||
index aecce6c1efea..6cd615e43a40 100644
|
||||
--- a/lib/ssh/src/ssh.hrl
|
||||
+++ b/lib/ssh/src/ssh.hrl
|
||||
@@ -558,5 +558,11 @@
|
||||
-define(CIRC_BUF_IN_ONCE(VALUE),
|
||||
((fun(V) -> ?CIRC_BUF_IN(V), V end)(VALUE))
|
||||
).
|
||||
-
|
||||
+
|
||||
+-define(SELECT_MSG(__Fun),
|
||||
+ (fun() ->
|
||||
+ #{level := __Level} = logger:get_primary_config(),
|
||||
+ __Fun(__Level)
|
||||
+ end)()).
|
||||
+
|
||||
-endif. % SSH_HRL defined
|
||||
diff --git a/lib/ssh/src/ssh_acceptor.erl b/lib/ssh/src/ssh_acceptor.erl
|
||||
index 00587eecbae1..7f131526bdff 100644
|
||||
--- a/lib/ssh/src/ssh_acceptor.erl
|
||||
+++ b/lib/ssh/src/ssh_acceptor.erl
|
||||
@@ -206,39 +206,63 @@ handle_error(Reason, ToAddress, ToPort, _) ->
|
||||
handle_error(Reason, ToAddress, ToPort, FromAddress, FromPort) ->
|
||||
case Reason of
|
||||
{max_sessions, MaxSessions} ->
|
||||
- error_logger:info_report(
|
||||
- lists:concat(["Ssh login attempt to ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
- " from ",ssh_lib:format_address_port(FromAddress,FromPort),
|
||||
- " denied due to option max_sessions limits to ",
|
||||
- MaxSessions, " sessions."
|
||||
- ])
|
||||
- );
|
||||
-
|
||||
+ MsgFun =
|
||||
+ fun(debug) ->
|
||||
+ lists:concat(["Ssh login attempt to ",
|
||||
+ ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
+ " from ",
|
||||
+ ssh_lib:format_address_port(FromAddress,FromPort),
|
||||
+ " denied due to option max_sessions limits to ",
|
||||
+ MaxSessions, " sessions."]);
|
||||
+ (_) ->
|
||||
+ ["Ssh login attempt denied max_session limits"]
|
||||
+ end,
|
||||
+ error_logger:info_report(?SELECT_MSG(MsgFun));
|
||||
Limit when Limit==enfile ; Limit==emfile ->
|
||||
%% Out of sockets...
|
||||
- error_logger:info_report([atom_to_list(Limit),": out of accept sockets on ",
|
||||
- ssh_lib:format_address_port(ToAddress, ToPort),
|
||||
- " - retrying"]),
|
||||
+ MsgFun =
|
||||
+ fun(debug) ->
|
||||
+ [atom_to_list(Limit),": out of accept sockets on ",
|
||||
+ ssh_lib:format_address_port(ToAddress, ToPort),
|
||||
+ " - retrying"];
|
||||
+ (_) ->
|
||||
+ ["Out of accept sockets on - retrying"]
|
||||
+ end,
|
||||
+ error_logger:info_report(?SELECT_MSG(MsgFun)),
|
||||
timer:sleep(?SLEEP_TIME);
|
||||
-
|
||||
closed ->
|
||||
- error_logger:info_report(["The ssh accept socket on ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
- "was closed by a third party."]
|
||||
- );
|
||||
-
|
||||
+ MsgFun =
|
||||
+ fun(debug) ->
|
||||
+ ["The ssh accept socket on ", ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
+ "was closed by a third party."];
|
||||
+ (_) ->
|
||||
+ ["The ssh accept socket on was closed by a third party"]
|
||||
+ end,
|
||||
+ error_logger:info_report(?SELECT_MSG(MsgFun));
|
||||
timeout ->
|
||||
ok;
|
||||
-
|
||||
Error when is_list(Error) ->
|
||||
ok;
|
||||
Error when FromAddress=/=undefined,
|
||||
FromPort=/=undefined ->
|
||||
- error_logger:info_report(["Accept failed on ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
- " for connect from ",ssh_lib:format_address_port(FromAddress,FromPort),
|
||||
- io_lib:format(": ~p", [Error])]);
|
||||
+ MsgFun =
|
||||
+ fun(debug) ->
|
||||
+ ["Accept failed on ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
+ " for connect from ",ssh_lib:format_address_port(FromAddress,FromPort),
|
||||
+ io_lib:format(": ~p", [Error])];
|
||||
+ (_) ->
|
||||
+ [io_lib:format("Accept failed on for connection: ~p", [Error])]
|
||||
+ end,
|
||||
+ error_logger:info_report(?SELECT_MSG(MsgFun));
|
||||
Error ->
|
||||
- error_logger:info_report(["Accept failed on ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
- io_lib:format(": ~p", [Error])])
|
||||
+ MsgFun =
|
||||
+ fun(debug) ->
|
||||
+ ["Accept failed on ",ssh_lib:format_address_port(ToAddress,ToPort),
|
||||
+ io_lib:format(": ~p", [Error])];
|
||||
+ (_) ->
|
||||
+ [io_lib:format("Accept failed on for connection: ~p", [Error])]
|
||||
+ end,
|
||||
+ error_logger:info_report(?SELECT_MSG(MsgFun))
|
||||
end.
|
||||
|
||||
%%%----------------------------------------------------------------
|
||||
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
|
||||
index 4ef45516ca23..bb62fc9219f5 100644
|
||||
--- a/lib/ssh/src/ssh_connection_handler.erl
|
||||
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
||||
@@ -648,11 +648,15 @@ handle_event(internal, {version_exchange,Version}, {hello,Role}, D0) ->
|
||||
|
||||
%%% timeout after tcp:connect but then nothing arrives
|
||||
handle_event(state_timeout, no_hello_received, {hello,_Role}=StateName, D0 = #data{ssh_params = Ssh0}) ->
|
||||
- Time = ?GET_OPT(hello_timeout, Ssh0#ssh.opts),
|
||||
+ MsgFun =
|
||||
+ fun (debug) ->
|
||||
+ Time = ?GET_OPT(hello_timeout, Ssh0#ssh.opts),
|
||||
+ lists:concat(["No HELLO received within ",ssh_lib:format_time_ms(Time)]);
|
||||
+ (_) ->
|
||||
+ ["No HELLO received within hello_timeout"]
|
||||
+ end,
|
||||
{Shutdown, D} =
|
||||
- ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
|
||||
- lists:concat(["No HELLO received within ",ssh_lib:format_time_ms(Time)]),
|
||||
- StateName, D0),
|
||||
+ ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, ?SELECT_MSG(MsgFun), StateName, D0),
|
||||
{stop, Shutdown, D};
|
||||
|
||||
|
||||
55
CVE-2025-30211-2.patch
Normal file
55
CVE-2025-30211-2.patch
Normal file
@ -0,0 +1,55 @@
|
||||
From 655e20a49ef80431e86ffb6c7f366d01fd4b64c3 Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Fri, 21 Mar 2025 12:17:07 +0100
|
||||
Subject: [PATCH] ssh: ignore too long names
|
||||
|
||||
Origin: https://github.com/erlang/otp/commit/655e20a49ef80431e86ffb6c7f366d01fd4b64c3
|
||||
---
|
||||
lib/ssh/src/ssh_message.erl | 20 ++++++++++++++++++--
|
||||
1 file changed, 18 insertions(+), 2 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/src/ssh_message.erl b/lib/ssh/src/ssh_message.erl
|
||||
index 3c1ea65038df..e22a4e2b8458 100644
|
||||
--- a/lib/ssh/src/ssh_message.erl
|
||||
+++ b/lib/ssh/src/ssh_message.erl
|
||||
@@ -24,6 +24,7 @@
|
||||
-module(ssh_message).
|
||||
|
||||
-include_lib("public_key/include/public_key.hrl").
|
||||
+-include_lib("kernel/include/logger.hrl").
|
||||
|
||||
-include("ssh.hrl").
|
||||
-include("ssh_connect.hrl").
|
||||
@@ -42,6 +43,7 @@
|
||||
|
||||
-behaviour(ssh_dbg).
|
||||
-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1, ssh_dbg_format/2]).
|
||||
+-define(ALG_NAME_LIMIT, 64).
|
||||
|
||||
ucl(B) ->
|
||||
try unicode:characters_to_list(B) of
|
||||
@@ -820,8 +822,22 @@ decode_kex_init(<<?BYTE(Bool)>>, Acc, 0) ->
|
||||
X = 0,
|
||||
list_to_tuple(lists:reverse([X, erl_boolean(Bool) | Acc]));
|
||||
decode_kex_init(<<?DEC_BIN(Data,__0), Rest/binary>>, Acc, N) ->
|
||||
- Names = string:tokens(?unicode_list(Data), ","),
|
||||
- decode_kex_init(Rest, [Names | Acc], N -1).
|
||||
+ BinParts = binary:split(Data, <<$,>>, [global]),
|
||||
+ Process =
|
||||
+ fun(<<>>, PAcc) ->
|
||||
+ PAcc;
|
||||
+ (Part, PAcc) ->
|
||||
+ case byte_size(Part) > ?ALG_NAME_LIMIT of
|
||||
+ true ->
|
||||
+ ?LOG_DEBUG("Ignoring too long name", []),
|
||||
+ PAcc;
|
||||
+ false ->
|
||||
+ Name = binary:bin_to_list(Part),
|
||||
+ [Name | PAcc]
|
||||
+ end
|
||||
+ end,
|
||||
+ Names = lists:foldr(Process, [], BinParts),
|
||||
+ decode_kex_init(Rest, [Names | Acc], N - 1).
|
||||
|
||||
|
||||
%%%================================================================
|
||||
36
CVE-2025-30211-3.patch
Normal file
36
CVE-2025-30211-3.patch
Normal file
@ -0,0 +1,36 @@
|
||||
From d64d9fb0688092356a336e38a8717499113312a0 Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Fri, 21 Mar 2025 17:50:21 +0100
|
||||
Subject: [PATCH] ssh: use chars_limit for bad packets error messages
|
||||
|
||||
Origin: https://github.com/erlang/otp/commit/d64d9fb0688092356a336e38a8717499113312a0
|
||||
---
|
||||
lib/ssh/src/ssh_connection_handler.erl | 8 ++++----
|
||||
1 file changed, 4 insertions(+), 4 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
|
||||
index bb62fc9219f5..a504a2fda722 100644
|
||||
--- a/lib/ssh/src/ssh_connection_handler.erl
|
||||
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
||||
@@ -1148,8 +1148,8 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
|
||||
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
|
||||
{Shutdown, D} =
|
||||
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
|
||||
- io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~P",
|
||||
- [C,E,ST,MaxLogItemLen]),
|
||||
+ io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
|
||||
+ [C,E,ST], [{chars_limit, MaxLogItemLen}]),
|
||||
StateName, D1),
|
||||
{stop, Shutdown, D}
|
||||
end;
|
||||
@@ -1183,8 +1183,8 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
|
||||
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
|
||||
{Shutdown, D} =
|
||||
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
|
||||
- io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~P",
|
||||
- [C,E,ST,MaxLogItemLen]),
|
||||
+ io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",
|
||||
+ [C,E,ST], [{chars_limit, MaxLogItemLen}]),
|
||||
StateName, D0),
|
||||
{stop, Shutdown, D}
|
||||
end;
|
||||
142
CVE-2025-30211-4.patch
Normal file
142
CVE-2025-30211-4.patch
Normal file
@ -0,0 +1,142 @@
|
||||
From 5ee26eb412a76ba1c6afdf4524b62939a48d1bce Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Mon, 24 Mar 2025 11:31:39 +0100
|
||||
Subject: [PATCH] ssh: custom_kexinit test added
|
||||
|
||||
Origin: https://github.com/erlang/otp/commit/5ee26eb412a76ba1c6afdf4524b62939a48d1bce
|
||||
---
|
||||
lib/ssh/test/ssh_protocol_SUITE.erl | 90 ++++++++++++++++++++++++++++-
|
||||
1 file changed, 87 insertions(+), 3 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
index 90f5b54..8bc408b 100644
|
||||
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
@@ -72,6 +72,7 @@
|
||||
modify_rm/1,
|
||||
no_common_alg_client_disconnects/1,
|
||||
no_common_alg_server_disconnects/1,
|
||||
+ custom_kexinit/1,
|
||||
no_ext_info_s1/1,
|
||||
no_ext_info_s2/1,
|
||||
packet_length_too_large/1,
|
||||
@@ -132,7 +133,8 @@ groups() ->
|
||||
{field_size_error, [], [service_name_length_too_large,
|
||||
service_name_length_too_short]},
|
||||
|
||||
- {kex, [], [no_common_alg_server_disconnects,
|
||||
+ {kex, [], [custom_kexinit,
|
||||
+ no_common_alg_server_disconnects,
|
||||
no_common_alg_client_disconnects,
|
||||
gex_client_init_option_groups,
|
||||
gex_server_gex_limit,
|
||||
@@ -173,7 +175,7 @@ init_per_suite(Config) ->
|
||||
end_per_suite(Config) ->
|
||||
stop_apps(Config).
|
||||
|
||||
-init_per_testcase(no_common_alg_server_disconnects, Config) ->
|
||||
+init_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit ->
|
||||
start_std_daemon(Config, [{preferred_algorithms,[{public_key,['ssh-rsa']},
|
||||
{cipher,?DEFAULT_CIPHERS}
|
||||
]}]);
|
||||
@@ -219,7 +221,7 @@ init_per_testcase(TC, Config) when TC == gex_client_init_option_groups ;
|
||||
init_per_testcase(_TestCase, Config) ->
|
||||
check_std_daemon_works(Config, ?LINE).
|
||||
|
||||
-end_per_testcase(no_common_alg_server_disconnects, Config) ->
|
||||
+end_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit ->
|
||||
stop_std_daemon(Config);
|
||||
end_per_testcase(kex_strict_negotiated, Config) ->
|
||||
Config;
|
||||
@@ -380,6 +382,88 @@ no_common_alg_server_disconnects(Config) ->
|
||||
]
|
||||
).
|
||||
|
||||
+custom_kexinit(Config) ->
|
||||
+ %% 16#C0 value causes unicode:characters_to_list to return a big error value
|
||||
+ Trash = lists:duplicate(260_000, 16#C0),
|
||||
+ FunnyAlg = "curve25519-sha256",
|
||||
+ KexInit =
|
||||
+ #ssh_msg_kexinit{cookie = <<"Ã/Ï!9zñKá:ñÀv¿JÜ">>,
|
||||
+ kex_algorithms =
|
||||
+ [FunnyAlg ++ Trash],
|
||||
+ server_host_key_algorithms = ["ssh-rsa"],
|
||||
+ encryption_algorithms_client_to_server =
|
||||
+ ["aes256-ctr","aes192-ctr","aes128-ctr","aes128-cbc","3des-cbc"],
|
||||
+ encryption_algorithms_server_to_client =
|
||||
+ ["aes256-ctr","aes192-ctr","aes128-ctr","aes128-cbc","3des-cbc"],
|
||||
+ mac_algorithms_client_to_server =
|
||||
+ ["hmac-sha2-512-etm@openssh.com","hmac-sha2-256-etm@openssh.com",
|
||||
+ "hmac-sha2-512","hmac-sha2-256","hmac-sha1-etm@openssh.com","hmac-sha1"],
|
||||
+ mac_algorithms_server_to_client =
|
||||
+ ["hmac-sha2-512-etm@openssh.com","hmac-sha2-256-etm@openssh.com",
|
||||
+ "hmac-sha2-512","hmac-sha2-256","hmac-sha1-etm@openssh.com","hmac-sha1"],
|
||||
+ compression_algorithms_client_to_server = ["none","zlib@openssh.com","zlib"],
|
||||
+ compression_algorithms_server_to_client = ["none","zlib@openssh.com","zlib"],
|
||||
+ languages_client_to_server = [],
|
||||
+ languages_server_to_client = [],
|
||||
+ first_kex_packet_follows = false,
|
||||
+ reserved = 0
|
||||
+ },
|
||||
+ PacketFun =
|
||||
+ fun(Msg, Ssh) ->
|
||||
+ BinMsg = custom_encode(Msg),
|
||||
+ ssh_transport:pack(BinMsg, Ssh, 0)
|
||||
+ end,
|
||||
+ {ok,_} =
|
||||
+ ssh_trpt_test_lib:exec(
|
||||
+ [{set_options, [print_ops, {print_messages,detail}]},
|
||||
+ {connect,
|
||||
+ server_host(Config),server_port(Config),
|
||||
+ [{silently_accept_hosts, true},
|
||||
+ {user_dir, user_dir(Config)},
|
||||
+ {user_interaction, false},
|
||||
+ {preferred_algorithms,[{public_key,['ssh-rsa']},
|
||||
+ {cipher,?DEFAULT_CIPHERS}
|
||||
+ ]}
|
||||
+ ]},
|
||||
+ receive_hello,
|
||||
+ {send, hello},
|
||||
+ {match, #ssh_msg_kexinit{_='_'}, receive_msg},
|
||||
+ {send, {special, KexInit, PacketFun}}, % with server unsupported 'ssh-dss' !
|
||||
+ {match, disconnect(), receive_msg}
|
||||
+ ]
|
||||
+ ).
|
||||
+
|
||||
+custom_encode(#ssh_msg_kexinit{
|
||||
+ cookie = Cookie,
|
||||
+ kex_algorithms = KeyAlgs,
|
||||
+ server_host_key_algorithms = HostKeyAlgs,
|
||||
+ encryption_algorithms_client_to_server = EncAlgC2S,
|
||||
+ encryption_algorithms_server_to_client = EncAlgS2C,
|
||||
+ mac_algorithms_client_to_server = MacAlgC2S,
|
||||
+ mac_algorithms_server_to_client = MacAlgS2C,
|
||||
+ compression_algorithms_client_to_server = CompAlgS2C,
|
||||
+ compression_algorithms_server_to_client = CompAlgC2S,
|
||||
+ languages_client_to_server = LangC2S,
|
||||
+ languages_server_to_client = LangS2C,
|
||||
+ first_kex_packet_follows = Bool,
|
||||
+ reserved = Reserved
|
||||
+ }) ->
|
||||
+ KeyAlgsBin0 = <<?Ename_list(KeyAlgs)>>,
|
||||
+ <<?UINT32(Len0), Data:Len0/binary>> = KeyAlgsBin0,
|
||||
+ KeyAlgsBin = <<?UINT32(Len0), Data/binary>>,
|
||||
+ <<?Ebyte(?SSH_MSG_KEXINIT), Cookie/binary,
|
||||
+ KeyAlgsBin/binary,
|
||||
+ ?Ename_list(HostKeyAlgs),
|
||||
+ ?Ename_list(EncAlgC2S),
|
||||
+ ?Ename_list(EncAlgS2C),
|
||||
+ ?Ename_list(MacAlgC2S),
|
||||
+ ?Ename_list(MacAlgS2C),
|
||||
+ ?Ename_list(CompAlgS2C),
|
||||
+ ?Ename_list(CompAlgC2S),
|
||||
+ ?Ename_list(LangC2S),
|
||||
+ ?Ename_list(LangS2C),
|
||||
+ ?Eboolean(Bool), ?Euint32(Reserved)>>.
|
||||
+
|
||||
%%--------------------------------------------------------------------
|
||||
%%% Algo negotiation fail. This should result in a ssh_msg_disconnect
|
||||
%%% being sent from the client.
|
||||
--
|
||||
2.43.0
|
||||
|
||||
@ -10,7 +10,7 @@
|
||||
%global __with_sources 1
|
||||
Name: erlang
|
||||
Version: 25.3.2.6
|
||||
Release: 4
|
||||
Release: 5
|
||||
Summary: General-purpose programming language and runtime environment
|
||||
License: Apache-2.0
|
||||
URL: https://www.erlang.org
|
||||
@ -34,6 +34,10 @@ Patch11: otp-0011-configure.ac-C99-fixes-for-poll_works-check.patch
|
||||
Patch12: otp-0012-Revert-Do-not-install-erlang-sources.patch
|
||||
Patch13: CVE-2023-48795.patch
|
||||
Patch14: CVE-2025-26618.patch
|
||||
Patch15: CVE-2025-30211-1.patch
|
||||
Patch16: CVE-2025-30211-2.patch
|
||||
Patch17: CVE-2025-30211-3.patch
|
||||
Patch18: CVE-2025-30211-4.patch
|
||||
|
||||
BuildRequires: gcc gcc-c++ flex make
|
||||
%if %{with doc}
|
||||
@ -1756,6 +1760,9 @@ useradd -r -g epmd -d /dev/null -s /sbin/nologin \
|
||||
%endif
|
||||
|
||||
%changelog
|
||||
* Tue Apr 01 2025 yaoxin <1024769339@qq.com> - 25.3.2.6-5
|
||||
- Fix CVE-2025-30211
|
||||
|
||||
* Mon Feb 24 2025 yaoxin <1024769339@qq.com> - 25.3.2.6-4
|
||||
- Fix CVE-2025-26618
|
||||
|
||||
|
||||
Loading…
x
Reference in New Issue
Block a user