commit 59e9b7996dc14e0a0fa4206907801a5df520f54b Author: Jiayi Yin Date: Sun May 18 21:00:42 2025 +0000 转换LFS仓库为普通仓库 diff --git a/CVE-2023-48795.patch b/CVE-2023-48795.patch new file mode 100644 index 0000000..23db700 --- /dev/null +++ b/CVE-2023-48795.patch @@ -0,0 +1,826 @@ +From ee67d46285394db95133709cef74b0c462d665aa Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Fri, 15 Dec 2023 09:12:33 +0100 +Subject: [PATCH] ssh: KEX strict + +Origin: https://github.com/erlang/otp/commit/ee67d46285394db95133709cef74b0c462d665aa + +- negotiate "strict KEX" OpenSSH feature +- when negotiated between peers apply strict KEX +- related tests +- print_seqnums fix in ssh_trtp test code +--- + lib/ssh/src/ssh.hrl | 5 +- + lib/ssh/src/ssh_connection_handler.erl | 10 +++ + lib/ssh/src/ssh_fsm_kexinit.erl | 2 +- + lib/ssh/src/ssh_transport.erl | 104 ++++++++++++++++++++----- + lib/ssh/src/ssh_transport.hrl | 4 +- + lib/ssh/test/ssh_protocol_SUITE.erl | 100 +++++++++++++++++++++--- + lib/ssh/test/ssh_test_lib.erl | 52 ++++++++++++- + lib/ssh/test/ssh_to_openssh_SUITE.erl | 90 ++++++++++++++++----- + lib/ssh/test/ssh_trpt_test_lib.erl | 34 ++++---- + 9 files changed, 335 insertions(+), 66 deletions(-) + +diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl +index 2f6e9614577d..d667bfbcd270 100644 +--- a/lib/ssh/src/ssh.hrl ++++ b/lib/ssh/src/ssh.hrl +@@ -437,6 +437,8 @@ + send_ext_info, %% May send ext-info to peer + recv_ext_info, %% Expect ext-info from peer + ++ kex_strict_negotiated = false, ++ + algorithms, %% #alg{} + + send_mac = none, %% send MAC algorithm +@@ -508,7 +510,8 @@ + c_lng, + s_lng, + send_ext_info, +- recv_ext_info ++ recv_ext_info, ++ kex_strict_negotiated = false + }). + + -record(ssh_pty, {c_version = "", % client version string, e.g "SSH-2.0-Erlang/4.10.5" +diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl +index b2545c4db40b..7d20b94e873b 100644 +--- a/lib/ssh/src/ssh_connection_handler.erl ++++ b/lib/ssh/src/ssh_connection_handler.erl +@@ -701,6 +701,16 @@ handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D + disconnect_fun("Received disconnect: "++Desc, D), + {stop_and_reply, {shutdown,Desc}, Actions, D}; + ++handle_event(internal, #ssh_msg_ignore{}, {_StateName, _Role, init}, ++ #data{ssh_params = #ssh{kex_strict_negotiated = true, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("strict KEX violation: unexpected SSH_MSG_IGNORE " ++ "send_sequence = ~p recv_sequence = ~p", ++ [SendSeq, RecvSeq]) ++ ); ++ + handle_event(internal, #ssh_msg_ignore{}, _StateName, _) -> + keep_state_and_data; + +diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl +index 6ac4ec798f21..b5ae0158158a 100644 +--- a/lib/ssh/src/ssh_fsm_kexinit.erl ++++ b/lib/ssh/src/ssh_fsm_kexinit.erl +@@ -58,7 +58,7 @@ callback_mode() -> + handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg}, + D = #data{key_exchange_init_msg = OwnKex}) -> + Ssh1 = ssh_transport:key_init(peer_role(Role), D#data.ssh_params, Payload), +- Ssh = case ssh_transport:handle_kexinit_msg(Kex, OwnKex, Ssh1) of ++ Ssh = case ssh_transport:handle_kexinit_msg(Kex, OwnKex, Ssh1, ReNeg) of + {ok, NextKexMsg, Ssh2} when Role==client -> + ssh_connection_handler:send_bytes(NextKexMsg, D), + Ssh2; +diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl +index e43c345130b1..12575df8aa3c 100644 +--- a/lib/ssh/src/ssh_transport.erl ++++ b/lib/ssh/src/ssh_transport.erl +@@ -42,7 +42,7 @@ + key_exchange_init_msg/1, + key_init/3, new_keys_message/1, + ext_info_message/1, +- handle_kexinit_msg/3, handle_kexdh_init/2, ++ handle_kexinit_msg/4, handle_kexdh_init/2, + handle_kex_dh_gex_group/2, handle_kex_dh_gex_init/2, handle_kex_dh_gex_reply/2, + handle_new_keys/2, handle_kex_dh_gex_request/2, + handle_kexdh_reply/2, +@@ -235,7 +235,6 @@ supported_algorithms(cipher) -> + same( + select_crypto_supported( + [ +- {'chacha20-poly1305@openssh.com', [{ciphers,chacha20}, {macs,poly1305}]}, + {'aes256-gcm@openssh.com', [{ciphers,aes_256_gcm}]}, + {'aes256-ctr', [{ciphers,aes_256_ctr}]}, + {'aes192-ctr', [{ciphers,aes_192_ctr}]}, +@@ -243,6 +242,7 @@ supported_algorithms(cipher) -> + {'aes128-ctr', [{ciphers,aes_128_ctr}]}, + {'AEAD_AES_256_GCM', [{ciphers,aes_256_gcm}]}, + {'AEAD_AES_128_GCM', [{ciphers,aes_128_gcm}]}, ++ {'chacha20-poly1305@openssh.com', [{ciphers,chacha20}, {macs,poly1305}]}, + {'aes256-cbc', [{ciphers,aes_256_cbc}]}, + {'aes192-cbc', [{ciphers,aes_192_cbc}]}, + {'aes128-cbc', [{ciphers,aes_128_cbc}]}, +@@ -358,7 +358,8 @@ kexinit_message(Role, Random, Algs, HostKeyAlgs, Opts) -> + #ssh_msg_kexinit{ + cookie = Random, + kex_algorithms = to_strings( get_algs(kex,Algs) ) +- ++ kex_ext_info(Role,Opts), ++ ++ kex_ext_info(Role,Opts) ++ ++ kex_strict_alg(Role), + server_host_key_algorithms = HostKeyAlgs, + encryption_algorithms_client_to_server = c2s(cipher,Algs), + encryption_algorithms_server_to_client = s2c(cipher,Algs), +@@ -387,10 +388,12 @@ new_keys_message(Ssh0) -> + + + handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, +- #ssh{role = client} = Ssh) -> ++ #ssh{role = client} = Ssh, ReNeg) -> + try +- {ok, Algorithms} = select_algorithm(client, Own, CounterPart, Ssh#ssh.opts), ++ {ok, Algorithms} = ++ select_algorithm(client, Own, CounterPart, Ssh, ReNeg), + true = verify_algorithm(Algorithms), ++ true = verify_kexinit_is_first_msg(Algorithms, Ssh, ReNeg), + Algorithms + of + Algos -> +@@ -403,10 +406,12 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, + end; + + handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, +- #ssh{role = server} = Ssh) -> ++ #ssh{role = server} = Ssh, ReNeg) -> + try +- {ok, Algorithms} = select_algorithm(server, CounterPart, Own, Ssh#ssh.opts), ++ {ok, Algorithms} = ++ select_algorithm(server, CounterPart, Own, Ssh, ReNeg), + true = verify_algorithm(Algorithms), ++ true = verify_kexinit_is_first_msg(Algorithms, Ssh, ReNeg), + Algorithms + of + Algos -> +@@ -482,6 +487,21 @@ verify_algorithm(#alg{kex = Kex}) -> + false -> {false, "kex"} + end. + ++verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = false}, _, _) -> ++ true; ++verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true}, _, renegotiate) -> ++ true; ++verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true}, ++ #ssh{send_sequence = 1, recv_sequence = 1}, ++ init) -> ++ true; ++verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true}, ++ #ssh{send_sequence = SendSequence, ++ recv_sequence = RecvSequence}, init) -> ++ error_logger:warning_report( ++ lists:concat(["KEX strict violation (", SendSequence, ", ", RecvSequence, ")."])), ++ {false, "kex_strict"}. ++ + %%%---------------------------------------------------------------- + %%% + %%% Key exchange initialization +@@ -861,6 +881,9 @@ handle_new_keys(#ssh_msg_newkeys{}, Ssh0) -> + ) + end. + ++%%%---------------------------------------------------------------- ++kex_strict_alg(client) -> [?kex_strict_c]; ++kex_strict_alg(server) -> [?kex_strict_s]. + + %%%---------------------------------------------------------------- + kex_ext_info(Role, Opts) -> +@@ -1082,7 +1105,35 @@ known_host_key(#ssh{opts = Opts, peer = {PeerName,{IP,Port}}} = Ssh, + %% + %% The first algorithm in each list MUST be the preferred (guessed) + %% algorithm. Each string MUST contain at least one algorithm name. +-select_algorithm(Role, Client, Server, Opts) -> ++select_algorithm(Role, Client, Server, ++ #ssh{opts = Opts, ++ kex_strict_negotiated = KexStrictNegotiated0}, ++ ReNeg) -> ++ KexStrictNegotiated = ++ case ReNeg of ++ %% KEX strict negotiated once per connection ++ init -> ++ Result = ++ case Role of ++ server -> ++ lists:member(?kex_strict_c, ++ Client#ssh_msg_kexinit.kex_algorithms); ++ client -> ++ lists:member(?kex_strict_s, ++ Server#ssh_msg_kexinit.kex_algorithms) ++ end, ++ case Result of ++ true -> ++ error_logger:info_report( ++ lists:concat([Role, " will use strict KEX ordering"])); ++ _ -> ++ ok ++ end, ++ Result; ++ _ -> ++ KexStrictNegotiated0 ++ end, ++ + {Encrypt0, Decrypt0} = select_encrypt_decrypt(Role, Client, Server), + {SendMac0, RecvMac0} = select_send_recv_mac(Role, Client, Server), + +@@ -1133,7 +1184,8 @@ select_algorithm(Role, Client, Server, Opts) -> + c_lng = C_Lng, + s_lng = S_Lng, + send_ext_info = SendExtInfo, +- recv_ext_info = RecvExtInfo ++ recv_ext_info = RecvExtInfo, ++ kex_strict_negotiated = KexStrictNegotiated + }}. + + +@@ -1231,7 +1283,8 @@ alg_setup(snd, SSH) -> + c_lng = ALG#alg.c_lng, + s_lng = ALG#alg.s_lng, + send_ext_info = ALG#alg.send_ext_info, +- recv_ext_info = ALG#alg.recv_ext_info ++ recv_ext_info = ALG#alg.recv_ext_info, ++ kex_strict_negotiated = ALG#alg.kex_strict_negotiated + }; + + alg_setup(rcv, SSH) -> +@@ -1243,22 +1296,23 @@ alg_setup(rcv, SSH) -> + c_lng = ALG#alg.c_lng, + s_lng = ALG#alg.s_lng, + send_ext_info = ALG#alg.send_ext_info, +- recv_ext_info = ALG#alg.recv_ext_info ++ recv_ext_info = ALG#alg.recv_ext_info, ++ kex_strict_negotiated = ALG#alg.kex_strict_negotiated + }. + +- +-alg_init(snd, SSH0) -> ++alg_init(Dir = snd, SSH0) -> + {ok,SSH1} = send_mac_init(SSH0), + {ok,SSH2} = encrypt_init(SSH1), + {ok,SSH3} = compress_init(SSH2), +- SSH3; ++ {ok,SSH4} = maybe_reset_sequence(Dir, SSH3), ++ SSH4; + +-alg_init(rcv, SSH0) -> ++alg_init(Dir = rcv, SSH0) -> + {ok,SSH1} = recv_mac_init(SSH0), + {ok,SSH2} = decrypt_init(SSH1), + {ok,SSH3} = decompress_init(SSH2), +- SSH3. +- ++ {ok,SSH4} = maybe_reset_sequence(Dir, SSH3), ++ SSH4. + + alg_final(snd, SSH0) -> + {ok,SSH1} = send_mac_final(SSH0), +@@ -2236,6 +2290,14 @@ crypto_name_supported(Tag, CryptoName, Supported) -> + + same(Algs) -> [{client2server,Algs}, {server2client,Algs}]. + ++maybe_reset_sequence(snd, Ssh = #ssh{kex_strict_negotiated = true}) -> ++ {ok, Ssh#ssh{send_sequence = 0}}; ++maybe_reset_sequence(rcv, Ssh = #ssh{kex_strict_negotiated = true}) -> ++ {ok, Ssh#ssh{recv_sequence = 0}}; ++maybe_reset_sequence(_Dir, Ssh) -> ++ {ok, Ssh}. ++ ++ + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + %% + %% Other utils +@@ -2262,14 +2324,14 @@ ssh_dbg_flags(raw_messages) -> ssh_dbg_flags(hello); + ssh_dbg_flags(ssh_messages) -> ssh_dbg_flags(hello). + + +-ssh_dbg_on(alg) -> dbg:tpl(?MODULE,select_algorithm,4,x); ++ssh_dbg_on(alg) -> dbg:tpl(?MODULE,select_algorithm,5,x); + ssh_dbg_on(hello) -> dbg:tp(?MODULE,hello_version_msg,1,x), + dbg:tp(?MODULE,handle_hello_version,1,x); + ssh_dbg_on(raw_messages) -> ssh_dbg_on(hello); + ssh_dbg_on(ssh_messages) -> ssh_dbg_on(hello). + + +-ssh_dbg_off(alg) -> dbg:ctpl(?MODULE,select_algorithm,4); ++ssh_dbg_off(alg) -> dbg:ctpl(?MODULE,select_algorithm,5); + ssh_dbg_off(hello) -> dbg:ctpg(?MODULE,hello_version_msg,1), + dbg:ctpg(?MODULE,handle_hello_version,1); + ssh_dbg_off(raw_messages) -> ssh_dbg_off(hello); +@@ -2292,9 +2354,9 @@ ssh_dbg_format(hello, {call,{?MODULE,handle_hello_version,[Hello]}}) -> + ssh_dbg_format(hello, {return_from,{?MODULE,handle_hello_version,1},_Ret}) -> + skip; + +-ssh_dbg_format(alg, {call,{?MODULE,select_algorithm,[_,_,_,_]}}) -> ++ssh_dbg_format(alg, {call,{?MODULE,select_algorithm,[_,_,_,_,_]}}) -> + skip; +-ssh_dbg_format(alg, {return_from,{?MODULE,select_algorithm,4},{ok,Alg}}) -> ++ssh_dbg_format(alg, {return_from,{?MODULE,select_algorithm,5},{ok,Alg}}) -> + ["Negotiated algorithms:\n", + wr_record(Alg) + ]; +diff --git a/lib/ssh/src/ssh_transport.hrl b/lib/ssh/src/ssh_transport.hrl +index f424a4ff63c3..59ac9db1c1ba 100644 +--- a/lib/ssh/src/ssh_transport.hrl ++++ b/lib/ssh/src/ssh_transport.hrl +@@ -266,5 +266,7 @@ + -define(dh_group18, + {2, 16#FFFFFFFFFFFFFFFFC90FDAA22168C234C4C6628B80DC1CD129024E088A67CC74020BBEA63B139B22514A08798E3404DDEF9519B3CD3A431B302B0A6DF25F14374FE1356D6D51C245E485B576625E7EC6F44C42E9A637ED6B0BFF5CB6F406B7EDEE386BFB5A899FA5AE9F24117C4B1FE649286651ECE45B3DC2007CB8A163BF0598DA48361C55D39A69163FA8FD24CF5F83655D23DCA3AD961C62F356208552BB9ED529077096966D670C354E4ABC9804F1746C08CA18217C32905E462E36CE3BE39E772C180E86039B2783A2EC07A28FB5C55DF06F4C52C9DE2BCBF6955817183995497CEA956AE515D2261898FA051015728E5A8AAAC42DAD33170D04507A33A85521ABDF1CBA64ECFB850458DBEF0A8AEA71575D060C7DB3970F85A6E1E4C7ABF5AE8CDB0933D71E8C94E04A25619DCEE3D2261AD2EE6BF12FFA06D98A0864D87602733EC86A64521F2B18177B200CBBE117577A615D6C770988C0BAD946E208E24FA074E5AB3143DB5BFCE0FD108E4B82D120A92108011A723C12A787E6D788719A10BDBA5B2699C327186AF4E23C1A946834B6150BDA2583E9CA2AD44CE8DBBBC2DB04DE8EF92E8EFC141FBECAA6287C59474E6BC05D99B2964FA090C3A2233BA186515BE7ED1F612970CEE2D7AFB81BDD762170481CD0069127D5B05AA993B4EA988D8FDDC186FFB7DC90A6C08F4DF435C93402849236C3FAB4D27C7026C1D4DCB2602646DEC9751E763DBA37BDF8FF9406AD9E530EE5DB382F413001AEB06A53ED9027D831179727B0865A8918DA3EDBEBCF9B14ED44CE6CBACED4BB1BDB7F1447E6CC254B332051512BD7AF426FB8F401378CD2BF5983CA01C64B92ECF032EA15D1721D03F482D7CE6E74FEF6D55E702F46980C82B5A84031900B1C9E59E7C97FBEC7E8F323A97A7E36CC88BE0F1D45B7FF585AC54BD407B22B4154AACC8F6D7EBF48E1D814CC5ED20F8037E0A79715EEF29BE32806A1D58BB7C5DA76F550AA3D8A1FBFF0EB19CCB1A313D55CDA56C9EC2EF29632387FE8D76E3C0468043E8F663F4860EE12BF2D5B0B7474D6E694F91E6DBE115974A3926F12FEE5E438777CB6A932DF8CD8BEC4D073B931BA3BC832B68D9DD300741FA7BF8AFC47ED2576F6936BA424663AAB639C5AE4F5683423B4742BF1C978238F16CBE39D652DE3FDB8BEFC848AD922222E04A4037C0713EB57A81A23F0C73473FC646CEA306B4BCBC8862F8385DDFA9D4B7FA2C087E879683303ED5BDD3A062B3CF5B3A278A66D2A13F83F44F82DDF310EE074AB6A364597E899A0255DC164F31CC50846851DF9AB48195DED7EA1B1D510BD7EE74D73FAF36BC31ECFA268359046F4EB879F924009438B481C6CD7889A002ED5EE382BC9190DA6FC026E479558E4475677E9AA9E3050E2765694DFC81F56E880B96E7160C980DD98EDD3DFFFFFFFFFFFFFFFFF}). + +- ++%%% OpenSSH KEX strict ++-define(kex_strict_c, "kex-strict-c-v00@openssh.com"). ++-define(kex_strict_s, "kex-strict-s-v00@openssh.com"). + -endif. % -ifdef(ssh_transport). +diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl +index 7e94bf60c718..b4f765495fa6 100644 +--- a/lib/ssh/test/ssh_protocol_SUITE.erl ++++ b/lib/ssh/test/ssh_protocol_SUITE.erl +@@ -53,6 +53,9 @@ + empty_service_name/1, + ext_info_c/1, + ext_info_s/1, ++ kex_strict_negotiated/1, ++ kex_strict_msg_ignore/1, ++ kex_strict_msg_unknown/1, + gex_client_init_option_groups/1, + gex_client_init_option_groups_file/1, + gex_client_init_option_groups_moduli_file/1, +@@ -136,8 +139,10 @@ groups() -> + gex_client_init_option_groups_moduli_file, + gex_client_init_option_groups_file, + gex_client_old_request_exact, +- gex_client_old_request_noexact +- ]}, ++ gex_client_old_request_noexact, ++ kex_strict_negotiated, ++ kex_strict_msg_ignore, ++ kex_strict_msg_unknown]}, + {service_requests, [], [bad_service_name, + bad_long_service_name, + bad_very_long_service_name, +@@ -164,17 +169,16 @@ groups() -> + + init_per_suite(Config) -> + ?CHECK_CRYPTO(start_std_daemon( setup_dirs( start_apps(Config)))). +- ++ + end_per_suite(Config) -> + stop_apps(Config). + +- +- + init_per_testcase(no_common_alg_server_disconnects, Config) -> + start_std_daemon(Config, [{preferred_algorithms,[{public_key,['ssh-rsa']}, + {cipher,?DEFAULT_CIPHERS} + ]}]); +- ++init_per_testcase(kex_strict_negotiated, Config) -> ++ Config; + init_per_testcase(TC, Config) when TC == gex_client_init_option_groups ; + TC == gex_client_init_option_groups_moduli_file ; + TC == gex_client_init_option_groups_file ; +@@ -217,6 +221,8 @@ init_per_testcase(_TestCase, Config) -> + + end_per_testcase(no_common_alg_server_disconnects, Config) -> + stop_std_daemon(Config); ++end_per_testcase(kex_strict_negotiated, Config) -> ++ Config; + end_per_testcase(TC, Config) when TC == gex_client_init_option_groups ; + TC == gex_client_init_option_groups_moduli_file ; + TC == gex_client_init_option_groups_file ; +@@ -818,6 +824,80 @@ ext_info_c(Config) -> + {result, Pid, Error} -> ct:fail("Error: ~p",[Error]) + end. + ++%%%-------------------------------------------------------------------- ++%%% ++kex_strict_negotiated(Config0) -> ++ {ok,Pid} = ssh_test_lib:add_report_handler(), ++ Config = start_std_daemon(Config0, []), ++ {Server, Host, Port} = proplists:get_value(server, Config), ++ #{level := Level} = logger:get_primary_config(), ++ logger:set_primary_config(level, notice), ++ {ok, ConnRef} = std_connect({Host, Port}, Config, []), ++ {algorithms, A} = ssh:connection_info(ConnRef, algorithms), ++ ssh:stop_daemon(Server), ++ {ok, Reports} = ssh_test_lib:get_reports(Pid), ++ ct:log("Reports = ~p", [Reports]), ++ true = ssh_test_lib:kex_strict_negotiated(client, Reports), ++ true = ssh_test_lib:kex_strict_negotiated(server, Reports), ++ logger:set_primary_config(Level), ++ ok. ++ ++%% Connect to an erlang server and inject unexpected SSH ignore ++kex_strict_msg_ignore(Config) -> ++ ct:log("START: ~p~n=================================", [?FUNCTION_NAME]), ++ ExpectedReason = "strict KEX violation: unexpected SSH_MSG_IGNORE", ++ TestMessages = ++ [{send, ssh_msg_ignore}, ++ {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}], ++ kex_strict_helper(Config, TestMessages, ExpectedReason). ++ ++%% Connect to an erlang server and inject unexpected non-SSH binary ++kex_strict_msg_unknown(Config) -> ++ ct:log("START: ~p~n=================================", [?FUNCTION_NAME]), ++ ExpectedReason = "Bad packet: Size", ++ TestMessages = ++ [{send, ssh_msg_unknown}, ++ {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}], ++ kex_strict_helper(Config, TestMessages, ExpectedReason). ++ ++kex_strict_helper(Config, TestMessages, ExpectedReason) -> ++ {ok,HandlerPid} = ssh_test_lib:add_report_handler(), ++ #{level := Level} = logger:get_primary_config(), ++ logger:set_primary_config(level, notice), ++ %% Connect and negotiate keys ++ {ok, InitialState} = ssh_trpt_test_lib:exec( ++ [{set_options, [print_ops, print_seqnums, print_messages]}] ++ ), ++ {ok, _AfterKexState} = ++ ssh_trpt_test_lib:exec( ++ [{connect, ++ server_host(Config),server_port(Config), ++ [{preferred_algorithms,[{kex,[?DEFAULT_KEX]}, ++ {cipher,?DEFAULT_CIPHERS} ++ ]}, ++ {silently_accept_hosts, true}, ++ {recv_ext_info, false}, ++ {user_dir, user_dir(Config)}, ++ {user_interaction, false} ++ | proplists:get_value(extra_options,Config,[]) ++ ]}, ++ receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init}] ++ ++ TestMessages, ++ InitialState), ++ ct:sleep(100), ++ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), ++ ct:log("HandlerPid = ~p~nReports = ~p", [HandlerPid, Reports]), ++ true = ssh_test_lib:kex_strict_negotiated(client, Reports), ++ true = ssh_test_lib:kex_strict_negotiated(server, Reports), ++ true = ssh_test_lib:event_logged(server, Reports, ExpectedReason), ++ logger:set_primary_config(Level), ++ ok. + + %%%---------------------------------------------------------------- + %%% +@@ -839,7 +919,7 @@ modify_append(Config) -> + Ciphers = filter_supported(cipher, ?CIPHERS), + {ok,_} = + chk_pref_algs(Config, +- [?DEFAULT_KEX, ?EXTRA_KEX], ++ [?DEFAULT_KEX, ?EXTRA_KEX, list_to_atom(?kex_strict_s)], + Ciphers, + [{preferred_algorithms, [{kex,[?DEFAULT_KEX]}, + {cipher,Ciphers} +@@ -853,7 +933,7 @@ modify_prepend(Config) -> + Ciphers = filter_supported(cipher, ?CIPHERS), + {ok,_} = + chk_pref_algs(Config, +- [?EXTRA_KEX, ?DEFAULT_KEX], ++ [?EXTRA_KEX, ?DEFAULT_KEX, list_to_atom(?kex_strict_s)], + Ciphers, + [{preferred_algorithms, [{kex,[?DEFAULT_KEX]}, + {cipher,Ciphers} +@@ -867,7 +947,7 @@ modify_rm(Config) -> + Ciphers = filter_supported(cipher, ?CIPHERS), + {ok,_} = + chk_pref_algs(Config, +- [?DEFAULT_KEX], ++ [?DEFAULT_KEX, list_to_atom(?kex_strict_s)], + tl(Ciphers), + [{preferred_algorithms, [{kex,[?DEFAULT_KEX,?EXTRA_KEX]}, + {cipher,Ciphers} +@@ -886,7 +966,7 @@ modify_combo(Config) -> + LastC = lists:last(Ciphers), + {ok,_} = + chk_pref_algs(Config, +- [?DEFAULT_KEX], ++ [?DEFAULT_KEX, list_to_atom(?kex_strict_s)], + [LastC] ++ (tl(Ciphers)--[LastC]) ++ [hd(Ciphers)], + [{preferred_algorithms, [{kex,[?DEFAULT_KEX,?EXTRA_KEX]}, + {cipher,Ciphers} +diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl +index acabb66a4805..e8fe5b4203df 100644 +--- a/lib/ssh/test/ssh_test_lib.erl ++++ b/lib/ssh/test/ssh_test_lib.erl +@@ -121,7 +121,11 @@ setup_host_key_create_dir/3, + setup_host_key/3, + setup_known_host/3, + get_addr_str/0, +-file_base_name/2 ++file_base_name/2, ++add_report_handler/0, ++get_reports/1, ++kex_strict_negotiated/2, ++event_logged/3 + ]). + + -include_lib("common_test/include/ct.hrl"). +@@ -1267,3 +1271,49 @@ file_base_name(system_src, 'ecdsa-sha2-nistp521') -> "ssh_host_ecdsa_key521"; + file_base_name(system_src, Alg) -> file_base_name(system, Alg). + + %%%---------------------------------------------------------------- ++add_report_handler() -> ++ ssh_eqc_event_handler:add_report_handler(). ++ ++get_reports(Pid) -> ++ ssh_eqc_event_handler:get_reports(Pid). ++ ++-define(SEARCH_FUN(EXP), ++ begin ++ fun({info_report, _, {_, std_info, EXP}}) -> ++ true; ++ (_) -> ++ false ++ end ++ end). ++-define(SEARCH_SUFFIX, " will use strict KEX ordering"). ++ ++kex_strict_negotiated(client, Reports) -> ++ kex_strict_negotiated(?SEARCH_FUN("client" ++ ?SEARCH_SUFFIX), Reports); ++kex_strict_negotiated(server, Reports) -> ++ kex_strict_negotiated(?SEARCH_FUN("server" ++ ?SEARCH_SUFFIX), Reports); ++kex_strict_negotiated(SearchFun, Reports) when is_function(SearchFun) -> ++ case lists:search(SearchFun, Reports) of ++ {value, _} -> true; ++ _ -> false ++ end. ++ ++event_logged(Role, Reports, Reason) -> ++ SearchF = ++ fun({info_msg, _, {_, _Format, Args}}) -> ++ AnyF = fun (E) when is_list(E) -> ++ case string:find(E, Reason) of ++ nomatch -> false; ++ _ -> true ++ end; ++ (_) -> ++ false ++ end, ++ lists:member(Role, Args) andalso ++ lists:any(AnyF, Args); ++ (_) -> ++ false ++ end, ++ case lists:search(SearchF, Reports) of ++ {value, _} -> true; ++ _ -> false ++ end. +diff --git a/lib/ssh/test/ssh_to_openssh_SUITE.erl b/lib/ssh/test/ssh_to_openssh_SUITE.erl +index a36b4036a527..fdc9a4f0d64f 100644 +--- a/lib/ssh/test/ssh_to_openssh_SUITE.erl ++++ b/lib/ssh/test/ssh_to_openssh_SUITE.erl +@@ -23,6 +23,7 @@ + + -include_lib("common_test/include/ct.hrl"). + -include("ssh_test_lib.hrl"). ++-include_lib("ssh/src/ssh_transport.hrl"). + + -export([ + suite/0, +@@ -38,7 +39,9 @@ + + -export([ + erlang_server_openssh_client_renegotiate/1, ++ eserver_oclient_kex_strict/1, + erlang_shell_client_openssh_server/1, ++ eclient_oserver_kex_strict/1, + exec_direct_with_io_in_sshc/1, + exec_with_io_in_sshc/1, + tunnel_in_erlclient_erlserver/1, +@@ -73,12 +76,14 @@ groups() -> + [{erlang_client, [], [tunnel_in_erlclient_erlserver, + tunnel_out_erlclient_erlserver, + {group, tunnel_distro_server}, +- erlang_shell_client_openssh_server ++ erlang_shell_client_openssh_server, ++ eclient_oserver_kex_strict + ]}, + {tunnel_distro_server, [], [tunnel_in_erlclient_openssh_server, + tunnel_out_erlclient_openssh_server]}, + {erlang_server, [], [{group, tunnel_distro_client}, + erlang_server_openssh_client_renegotiate, ++ eserver_oclient_kex_strict, + exec_with_io_in_sshc, + exec_direct_with_io_in_sshc + ] +@@ -87,16 +92,15 @@ groups() -> + tunnel_out_non_erlclient_erlserver]} + ]. + +-init_per_suite(Config) -> ++init_per_suite(Config0) -> + ?CHECK_CRYPTO( +- case gen_tcp:connect("localhost", ?SSH_DEFAULT_PORT, []) of ++ case gen_tcp:connect("localhost", ?SSH_DEFAULT_PORT, [{active, false}]) of + {error,econnrefused} -> +- {skip,"No openssh daemon (econnrefused)"}; +- _ -> ++ {skip,"No openssh daemon (econnrefused)"}; ++ {ok, Sock} -> + ssh_test_lib:openssh_sanity_check( +- [{ptty_supported, ssh_test_lib:ptty_supported()} +- | Config] +- ) ++ [{ptty_supported, ssh_test_lib:ptty_supported()}, ++ {kex_strict, check_kex_strict(Sock)}| Config0]) + end + ). + +@@ -142,6 +146,25 @@ end_per_testcase(_TestCase, _Config) -> + %% Test Cases -------------------------------------------------------- + %%-------------------------------------------------------------------- + erlang_shell_client_openssh_server(Config) when is_list(Config) -> ++ eclient_oserver_helper(Config). ++ ++eclient_oserver_kex_strict(Config) when is_list(Config)-> ++ case proplists:get_value(kex_strict, Config) of ++ true -> ++ {ok, HandlerPid} = ssh_test_lib:add_report_handler(), ++ #{level := Level} = logger:get_primary_config(), ++ logger:set_primary_config(level, notice), ++ Result = eclient_oserver_helper(Config), ++ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), ++ ct:pal("Reports = ~p", [Reports]), ++ true = ssh_test_lib:kex_strict_negotiated(client, Reports), ++ logger:set_primary_config(Level), ++ Result; ++ _ -> ++ {skip, "KEX strict not support by local OpenSSH"} ++ end. ++ ++eclient_oserver_helper(Config) -> + process_flag(trap_exit, true), + IO = ssh_test_lib:start_io_server(), + Prev = lists:usort(supervisor:which_children(sshc_sup)), +@@ -166,7 +189,6 @@ erlang_shell_client_openssh_server(Config) when is_list(Config) -> + false + end) + end. +- + %%-------------------------------------------------------------------- + %% Test that the server could redirect stdin and stdout from/to an + %% OpensSSH client when handling an exec request +@@ -231,6 +253,25 @@ exec_direct_with_io_in_sshc(Config) when is_list(Config) -> + %%-------------------------------------------------------------------- + %% Test that the Erlang/OTP server can renegotiate with openSSH + erlang_server_openssh_client_renegotiate(Config) -> ++ eserver_oclient_renegotiate_helper(Config). ++ ++eserver_oclient_kex_strict(Config) -> ++ case proplists:get_value(kex_strict, Config) of ++ true -> ++ {ok, HandlerPid} = ssh_test_lib:add_report_handler(), ++ #{level := Level} = logger:get_primary_config(), ++ logger:set_primary_config(level, notice), ++ Result = eserver_oclient_renegotiate_helper(Config), ++ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), ++ ct:log("Reports = ~p", [Reports]), ++ true = ssh_test_lib:kex_strict_negotiated(server, Reports), ++ logger:set_primary_config(Level), ++ Result; ++ _ -> ++ {skip, "KEX strict not support by local OpenSSH"} ++ end. ++ ++eserver_oclient_renegotiate_helper(Config) -> + _PubKeyAlg = ssh_rsa, + SystemDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), +@@ -255,9 +296,9 @@ erlang_server_openssh_client_renegotiate(Config) -> + + OpenSsh = ssh_test_lib:open_port({spawn, Cmd++" < "++DataFile}), + +- Expect = fun({data,R}) -> ++ Expect = fun({data,R}) -> + try +- NonAlphaChars = [C || C<-lists:seq(1,255), ++ NonAlphaChars = [C || C<-lists:seq(1,255), + not lists:member(C,lists:seq($a,$z)), + not lists:member(C,lists:seq($A,$Z)) + ], +@@ -275,15 +316,14 @@ erlang_server_openssh_client_renegotiate(Config) -> + (_) -> + false + end, +- +- try +- ssh_test_lib:rcv_expected(Expect, OpenSsh, ?TIMEOUT) ++ try ++ ssh_test_lib:rcv_expected(Expect, OpenSsh, ?TIMEOUT) + of +- _ -> +- %% Unfortunately we can't check that there has been a renegotiation, just trust OpenSSH. +- ssh:stop_daemon(Pid) ++ _ -> ++ %% Unfortunately we can't check that there has been a renegotiation, just trust OpenSSH. ++ ssh:stop_daemon(Pid) + catch +- throw:{skip,R} -> {skip,R} ++ throw:{skip,R} -> {skip,R} + end. + + %%-------------------------------------------------------------------- +@@ -569,3 +609,17 @@ no_forwarding(Config) -> + "---- The function no_forwarding() returns ~p", + [Cmnd,TheText, FailRegExp, Result]), + Result. ++ ++check_kex_strict(Sock) -> ++ %% Send some version, in order to receive KEXINIT from server ++ ok = gen_tcp:send(Sock, "SSH-2.0-OpenSSH_9.5\r\n"), ++ ct:sleep(100), ++ {ok, Packet} = gen_tcp:recv(Sock, 0), ++ case string:find(Packet, ?kex_strict_s) of ++ nomatch -> ++ ct:log("KEX strict NOT supported by local OpenSSH"), ++ false; ++ _ -> ++ ct:log("KEX strict supported by local OpenSSH"), ++ true ++ end. +diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl +index eea392bd352a..80c570acb594 100644 +--- a/lib/ssh/test/ssh_trpt_test_lib.erl ++++ b/lib/ssh/test/ssh_trpt_test_lib.erl +@@ -73,7 +73,7 @@ exec(L, S) when is_list(L) -> lists:foldl(fun exec/2, S, L); + exec(Op, S0=#s{}) -> + S1 = init_op_traces(Op, S0), + try seqnum_trace( +- op(Op, S1)) ++ op(Op, S1), S1) + of + S = #s{} -> + case proplists:get_value(silent,S#s.opts) of +@@ -331,12 +331,20 @@ send(S0, ssh_msg_kexinit) -> + {Msg, _Bytes, _C0} = ssh_transport:key_exchange_init_msg(S0#s.ssh), + send(S0, Msg); + ++send(S0, ssh_msg_ignore) -> ++ Msg = #ssh_msg_ignore{data = "unexpected_ignore_message"}, ++ send(S0, Msg); ++ ++send(S0, ssh_msg_unknown) -> ++ Msg = binary:encode_hex(<<"0000000C060900000000000000000000">>), ++ send(S0, Msg); ++ + send(S0=#s{alg_neg={undefined,PeerMsg}}, Msg=#ssh_msg_kexinit{}) -> + S1 = opt(print_messages, S0, + fun(X) when X==true;X==detail -> {"Send~n~s~n",[format_msg(Msg)]} end), + S2 = case PeerMsg of + #ssh_msg_kexinit{} -> +- try ssh_transport:handle_kexinit_msg(PeerMsg, Msg, S1#s.ssh) of ++ try ssh_transport:handle_kexinit_msg(PeerMsg, Msg, S1#s.ssh, init) of + {ok,Cx} when ?role(S1) == server -> + S1#s{alg = Cx#ssh.algorithms}; + {ok,_NextKexMsgBin,Cx} when ?role(S1) == client -> +@@ -358,7 +366,7 @@ send(S0=#s{alg_neg={undefined,PeerMsg}}, Msg=#ssh_msg_kexinit{}) -> + send(S0, ssh_msg_kexdh_init) when ?role(S0) == client -> + {OwnMsg, PeerMsg} = S0#s.alg_neg, + {ok, NextKexMsgBin, C} = +- try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S0#s.ssh) ++ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S0#s.ssh, init) + catch + Class:Exc -> + fail("Algorithm negotiation failed!", +@@ -441,7 +449,7 @@ recv(S0 = #s{}) -> + fail("2 kexint received!!", S); + + {OwnMsg, _} -> +- try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh) of ++ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh, init) of + {ok,C} when ?role(S) == server -> + S#s{alg_neg = {OwnMsg, PeerMsg}, + alg = C#ssh.algorithms, +@@ -725,23 +733,23 @@ report_trace(Class, Term, S) -> + fun(true) -> {"~s ~p",[Class,Term]} end) + ). + +-seqnum_trace(S) -> ++seqnum_trace(S, S0) -> + opt(print_seqnums, S, +- fun(true) when S#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence, +- S#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence -> ++ fun(true) when S0#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence, ++ S0#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence -> + {"~p seq num: send ~p->~p, recv ~p->~p~n", + [?role(S), +- S#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence, +- S#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence ++ S0#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence, ++ S0#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence + ]}; +- (true) when S#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence -> ++ (true) when S0#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence -> + {"~p seq num: send ~p->~p~n", + [?role(S), +- S#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence]}; +- (true) when S#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence -> ++ S0#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence]}; ++ (true) when S0#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence -> + {"~p seq num: recv ~p->~p~n", + [?role(S), +- S#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence]} ++ S0#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence]} + end). + + print_traces(S) when S#s.prints == [] -> S; diff --git a/CVE-2025-26618.patch b/CVE-2025-26618.patch new file mode 100644 index 0000000..2b9e7bc --- /dev/null +++ b/CVE-2025-26618.patch @@ -0,0 +1,89 @@ +From 0ed2573cbd55c92e9125c9dc70fa1ca7fed82872 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Thu, 6 Feb 2025 19:00:44 +0100 +Subject: [PATCH] ssh: sftp reject packets exceeding limit + +Origin: https://github.com/erlang/otp/commit/0ed2573cbd55c92e9125c9dc70fa1ca7fed82872 +--- + lib/ssh/src/ssh_sftpd.erl | 47 ++++++++++++++++++++++++++------------- + 1 file changed, 32 insertions(+), 15 deletions(-) + +diff --git a/lib/ssh/src/ssh_sftpd.erl b/lib/ssh/src/ssh_sftpd.erl +index c86ed2cb8199..6bcad0d056e7 100644 +--- a/lib/ssh/src/ssh_sftpd.erl ++++ b/lib/ssh/src/ssh_sftpd.erl +@@ -27,7 +27,7 @@ + -behaviour(ssh_server_channel). + + -include_lib("kernel/include/file.hrl"). +- ++-include_lib("kernel/include/logger.hrl"). + -include("ssh.hrl"). + -include("ssh_xfer.hrl"). + -include("ssh_connect.hrl"). %% For ?DEFAULT_PACKET_SIZE and ?DEFAULT_WINDOW_SIZE +@@ -128,9 +128,8 @@ init(Options) -> + %% Description: Handles channel messages + %%-------------------------------------------------------------------- + handle_ssh_msg({ssh_cm, _ConnectionManager, +- {data, _ChannelId, Type, Data}}, State) -> +- State1 = handle_data(Type, Data, State), +- {ok, State1}; ++ {data, ChannelId, Type, Data}}, State) -> ++ handle_data(Type, ChannelId, Data, State); + + handle_ssh_msg({ssh_cm, _, {eof, ChannelId}}, State) -> + {stop, ChannelId, State}; +@@ -187,24 +186,42 @@ terminate(_, #state{handles=Handles, file_handler=FileMod, file_state=FS}) -> + %%-------------------------------------------------------------------- + %%% Internal functions + %%-------------------------------------------------------------------- +-handle_data(0, <>, ++handle_data(0, ChannelId, <>, + State = #state{pending = <<>>}) -> + <> = Msg, + NewState = handle_op(Op, ReqId, Data, State), + case Rest of + <<>> -> +- NewState; ++ {ok, NewState}; + _ -> +- handle_data(0, Rest, NewState) ++ handle_data(0, ChannelId, Rest, NewState) + end; +- +-handle_data(0, Data, State = #state{pending = <<>>}) -> +- State#state{pending = Data}; +- +-handle_data(Type, Data, State = #state{pending = Pending}) -> +- handle_data(Type, <>, +- State#state{pending = <<>>}). +- ++handle_data(0, _ChannelId, Data, State = #state{pending = <<>>}) -> ++ {ok, State#state{pending = Data}}; ++handle_data(Type, ChannelId, Data0, State = #state{pending = Pending}) -> ++ Data = <>, ++ Size = byte_size(Data), ++ case Size > ?SSH_MAX_PACKET_SIZE of ++ true -> ++ ReportFun = ++ fun([S]) -> ++ Report = ++ #{label => {error_logger, error_report}, ++ report => ++ io_lib:format("SFTP packet size (~B) exceeds the limit!", ++ [S])}, ++ Meta = ++ #{error_logger => ++ #{tag => error_report,type => std_error}, ++ report_cb => fun(#{report := Msg}) -> {Msg, []} end}, ++ {Report, Meta} ++ end, ++ ?LOG_ERROR(ReportFun, [Size]), ++ {stop, ChannelId, State}; ++ _ -> ++ handle_data(Type, ChannelId, Data, State#state{pending = <<>>}) ++ end. ++ + handle_op(?SSH_FXP_INIT, Version, B, State) when is_binary(B) -> + XF = State#state.xf, + Vsn = lists:min([XF#ssh_xfer.vsn, Version]), diff --git a/CVE-2025-30211-1.patch b/CVE-2025-30211-1.patch new file mode 100644 index 0000000..2bd1213 --- /dev/null +++ b/CVE-2025-30211-1.patch @@ -0,0 +1,145 @@ +From df3aad2c5570847895562ff96a725190571f028c Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +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}; + + diff --git a/CVE-2025-30211-2.patch b/CVE-2025-30211-2.patch new file mode 100644 index 0000000..1fe4ab2 --- /dev/null +++ b/CVE-2025-30211-2.patch @@ -0,0 +1,55 @@ +From 655e20a49ef80431e86ffb6c7f366d01fd4b64c3 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +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(<>, Acc, 0) -> + X = 0, + list_to_tuple(lists:reverse([X, erl_boolean(Bool) | Acc])); + decode_kex_init(<>, 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). + + + %%%================================================================ diff --git a/CVE-2025-30211-3.patch b/CVE-2025-30211-3.patch new file mode 100644 index 0000000..2484038 --- /dev/null +++ b/CVE-2025-30211-3.patch @@ -0,0 +1,36 @@ +From d64d9fb0688092356a336e38a8717499113312a0 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +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; diff --git a/CVE-2025-30211-4.patch b/CVE-2025-30211-4.patch new file mode 100644 index 0000000..1df2bc8 --- /dev/null +++ b/CVE-2025-30211-4.patch @@ -0,0 +1,142 @@ +From 5ee26eb412a76ba1c6afdf4524b62939a48d1bce Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +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 = <>, ++ <> = KeyAlgsBin0, ++ KeyAlgsBin = <>, ++ <>. ++ + %%-------------------------------------------------------------------- + %%% Algo negotiation fail. This should result in a ssh_msg_disconnect + %%% being sent from the client. +-- +2.43.0 + diff --git a/CVE-2025-32433.patch b/CVE-2025-32433.patch new file mode 100644 index 0000000..5e02471 --- /dev/null +++ b/CVE-2025-32433.patch @@ -0,0 +1,218 @@ +From 0fcd9c56524b28615e8ece65fc0c3f66ef6e4c12 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Mon, 14 Apr 2025 16:33:21 +0200 +Subject: [PATCH] ssh: early RCE fix + +- disconnect when connection protocol message arrives +- when user is not authenticated for connection +- see RFC4252 sec.6 +--- + lib/ssh/src/ssh_connection.erl | 28 ++++++++-- + lib/ssh/test/ssh_protocol_SUITE.erl | 86 +++++++++++++++-------------- + 2 files changed, 67 insertions(+), 47 deletions(-) + +diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl +index 9ee17d4a30e8..c82dd671970e 100644 +--- a/lib/ssh/src/ssh_connection.erl ++++ b/lib/ssh/src/ssh_connection.erl +@@ -26,6 +26,8 @@ + + -module(ssh_connection). + ++-include_lib("kernel/include/logger.hrl"). ++ + -include("ssh.hrl"). + -include("ssh_connect.hrl"). + -include("ssh_transport.hrl"). +@@ -468,6 +470,25 @@ channel_data(ChannelId, DataType, Data0, + %%% Replies {Reply, UpdatedConnection} + %%% + ++handle_msg(#ssh_msg_disconnect{code = Code, description = Description}, Connection, _, _SSH) -> ++ {disconnect, {Code, Description}, handle_stop(Connection)}; ++ ++handle_msg(Msg, Connection, server, Ssh = #ssh{authenticated = false}) -> ++ %% See RFC4252 6. ++ %% Message numbers of 80 and higher are reserved for protocols running ++ %% after this authentication protocol, so receiving one of them before ++ %% authentication is complete is an error, to which the server MUST ++ %% respond by disconnecting, preferably with a proper disconnect message ++ %% sent to ease troubleshooting. ++ MsgFun = fun(M) -> ++ MaxLogItemLen = ?GET_OPT(max_log_item_len, Ssh#ssh.opts), ++ io_lib:format("Connection terminated. Unexpected message for unauthenticated user." ++ " Message: ~w", [M], ++ [{chars_limit, MaxLogItemLen}]) ++ end, ++ ?LOG_DEBUG(MsgFun, [Msg]), ++ {disconnect, {?SSH_DISCONNECT_PROTOCOL_ERROR, "Connection refused"}, handle_stop(Connection)}; ++ + handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId, + sender_channel = RemoteId, + initial_window_size = WindowSz, +@@ -972,12 +993,7 @@ handle_msg(#ssh_msg_request_success{data = Data}, + #connection{requests = [{_, From, Fun} | Rest]} = Connection0, _, _SSH) -> + Connection = Fun({success,Data}, Connection0), + {[{channel_request_reply, From, {success, Data}}], +- Connection#connection{requests = Rest}}; +- +-handle_msg(#ssh_msg_disconnect{code = Code, +- description = Description}, +- Connection, _, _SSH) -> +- {disconnect, {Code, Description}, handle_stop(Connection)}. ++ Connection#connection{requests = Rest}}. + + + %%%---------------------------------------------------------------- +diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl +index 282d64eafa2a..537642cff598 100644 +--- a/lib/ssh/test/ssh_protocol_SUITE.erl ++++ b/lib/ssh/test/ssh_protocol_SUITE.erl +@@ -74,6 +74,7 @@ + no_common_alg_client_disconnects/1, + no_common_alg_server_disconnects/1, + custom_kexinit/1, ++ early_rce/1, + no_ext_info_s1/1, + no_ext_info_s2/1, + packet_length_too_large/1, +@@ -112,6 +113,7 @@ suite() -> + all() -> + [{group,tool_tests}, + client_info_line, ++ early_rce, + {group,kex}, + {group,service_requests}, + {group,authentication}, +@@ -130,10 +132,8 @@ groups() -> + ]}, + {packet_size_error, [], [packet_length_too_large, + packet_length_too_short]}, +- + {field_size_error, [], [service_name_length_too_large, + service_name_length_too_short]}, +- + {kex, [], [custom_kexinit, + no_common_alg_server_disconnects, + no_common_alg_client_disconnects, +@@ -177,7 +177,8 @@ init_per_suite(Config) -> + end_per_suite(Config) -> + stop_apps(Config). + +-init_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit -> ++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} + ]}]); +@@ -223,7 +224,8 @@ 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(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit -> ++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; +@@ -384,6 +386,44 @@ no_common_alg_server_disconnects(Config) -> + ] + ). + ++early_rce(Config) -> ++ {ok,InitialState} = ++ ssh_trpt_test_lib:exec([{set_options, [print_ops, print_seqnums, print_messages]}]), ++ TypeOpen = "session", ++ ChannelId = 0, ++ WinSz = 425984, ++ PktSz = 65536, ++ DataOpen = <<>>, ++ SshMsgChannelOpen = ssh_connection:channel_open_msg(TypeOpen, ChannelId, WinSz, PktSz, DataOpen), ++ ++ Id = 0, ++ TypeReq = "exec", ++ WantReply = true, ++ DataReq = <>)>>, ++ SshMsgChannelRequest = ++ ssh_connection:channel_request_msg(Id, TypeReq, WantReply, DataReq), ++ {ok,AfterKexState} = ++ ssh_trpt_test_lib:exec( ++ [{connect, ++ server_host(Config),server_port(Config), ++ [{preferred_algorithms,[{kex,[?DEFAULT_KEX]}, ++ {cipher,?DEFAULT_CIPHERS} ++ ]}, ++ {silently_accept_hosts, true}, ++ {recv_ext_info, false}, ++ {user_dir, user_dir(Config)}, ++ {user_interaction, false} ++ | proplists:get_value(extra_options,Config,[])]}, ++ receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, SshMsgChannelOpen}, ++ {send, SshMsgChannelRequest}, ++ {match, disconnect(), receive_msg} ++ ], InitialState), ++ ok. ++ + custom_kexinit(Config) -> + %% 16#C0 value causes unicode:characters_to_list to return a big error value + Trash = lists:duplicate(260_000, 16#C0), +@@ -410,11 +450,6 @@ custom_kexinit(Config) -> + 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}]}, +@@ -430,42 +465,11 @@ custom_kexinit(Config) -> + receive_hello, + {send, hello}, + {match, #ssh_msg_kexinit{_='_'}, receive_msg}, +- {send, {special, KexInit, PacketFun}}, % with server unsupported 'ssh-dss' ! ++ {send, KexInit}, % 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 = <>, +- <> = KeyAlgsBin0, +- KeyAlgsBin = <>, +- <>. +- + %%-------------------------------------------------------------------- + %%% Algo negotiation fail. This should result in a ssh_msg_disconnect + %%% being sent from the client. diff --git a/CVE-2025-46712-1.patch b/CVE-2025-46712-1.patch new file mode 100644 index 0000000..55cad79 --- /dev/null +++ b/CVE-2025-46712-1.patch @@ -0,0 +1,623 @@ +From e4b56a9f4a511aa9990dd86c16c61439c828df83 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Tue, 6 May 2025 17:01:29 +0200 +Subject: [PATCH] ssh: KEX strict implementation fixes + +- fixed KEX strict implementation +- draft-miller-sshm-strict-kex-01.txt +- ssh_dbg added to ssh_fsm_kexinit module +- CVE-2025-46712 +--- + lib/ssh/src/ssh_connection_handler.erl | 24 ++-- + lib/ssh/src/ssh_fsm_kexinit.erl | 129 ++++++++++++++++++-- + lib/ssh/src/ssh_transport.erl | 13 +- + lib/ssh/test/ssh_protocol_SUITE.erl | 158 ++++++++++++++++++++++--- + lib/ssh/test/ssh_trpt_test_lib.erl | 39 +++++- + 5 files changed, 313 insertions(+), 50 deletions(-) + +diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl +index 5ddafa997567..15f98dfb5c31 100644 +--- a/lib/ssh/src/ssh_connection_handler.erl ++++ b/lib/ssh/src/ssh_connection_handler.erl +@@ -34,7 +34,6 @@ + -include("ssh_transport.hrl"). + -include("ssh_auth.hrl"). + -include("ssh_connect.hrl"). +- + -include("ssh_fsm.hrl"). + + %%==================================================================== +@@ -728,16 +727,6 @@ handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D + disconnect_fun("Received disconnect: "++Desc, D), + {stop_and_reply, {shutdown,Desc}, Actions, D}; + +-handle_event(internal, #ssh_msg_ignore{}, {_StateName, _Role, init}, +- #data{ssh_params = #ssh{kex_strict_negotiated = true, +- send_sequence = SendSeq, +- recv_sequence = RecvSeq}}) -> +- ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, +- io_lib:format("strict KEX violation: unexpected SSH_MSG_IGNORE " +- "send_sequence = ~p recv_sequence = ~p", +- [SendSeq, RecvSeq]) +- ); +- + handle_event(internal, #ssh_msg_ignore{}, _StateName, _) -> + keep_state_and_data; + +@@ -1141,11 +1130,14 @@ handle_event(info, {Proto, Sock, NewData}, StateName, + of + {packet_decrypted, DecryptedBytes, EncryptedDataRest, Ssh1} -> + D1 = D0#data{ssh_params = +- Ssh1#ssh{recv_sequence = ssh_transport:next_seqnum(Ssh1#ssh.recv_sequence)}, +- decrypted_data_buffer = <<>>, +- undecrypted_packet_length = undefined, +- aead_data = <<>>, +- encrypted_data_buffer = EncryptedDataRest}, ++ Ssh1#ssh{recv_sequence = ++ ssh_transport:next_seqnum(StateName, ++ Ssh1#ssh.recv_sequence, ++ SshParams)}, ++ decrypted_data_buffer = <<>>, ++ undecrypted_packet_length = undefined, ++ aead_data = <<>>, ++ encrypted_data_buffer = EncryptedDataRest}, + try + ssh_message:decode(set_kex_overload_prefix(DecryptedBytes,D1)) + of +diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl +index 05f7bdf22f16..b8fdc29079e8 100644 +--- a/lib/ssh/src/ssh_fsm_kexinit.erl ++++ b/lib/ssh/src/ssh_fsm_kexinit.erl +@@ -43,6 +43,11 @@ + -export([callback_mode/0, handle_event/4, terminate/3, + format_status/2, code_change/4]). + ++-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]). ++ + %%==================================================================== + %% gen_statem callbacks + %%==================================================================== +@@ -53,8 +58,13 @@ callback_mode() -> + + %%-------------------------------------------------------------------- + +-%%% ######## {kexinit, client|server, init|renegotiate} #### + ++handle_event(Type, Event = prepare_next_packet, StateName, D) -> ++ ssh_connection_handler:handle_event(Type, Event, StateName, D); ++handle_event(Type, Event = {send_disconnect, _, _, _, _}, StateName, D) -> ++ ssh_connection_handler:handle_event(Type, Event, StateName, D); ++ ++%%% ######## {kexinit, client|server, init|renegotiate} #### + handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg}, + D = #data{key_exchange_init_msg = OwnKex}) -> + Ssh1 = ssh_transport:key_init(peer_role(Role), D#data.ssh_params, Payload), +@@ -67,11 +77,10 @@ handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg}, + end, + {next_state, {key_exchange,Role,ReNeg}, D#data{ssh_params=Ssh}}; + +- + %%% ######## {key_exchange, client|server, init|renegotiate} #### +- + %%%---- diffie-hellman + handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, KexdhReply, Ssh1} = ssh_transport:handle_kexdh_init(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(KexdhReply, D), + {ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1), +@@ -81,6 +90,7 @@ handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, + {next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}}; + + handle_event(internal, #ssh_msg_kexdh_reply{} = Msg, {key_exchange,client,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, NewKeys, Ssh1} = ssh_transport:handle_kexdh_reply(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(NewKeys, D), + {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1), +@@ -89,24 +99,28 @@ handle_event(internal, #ssh_msg_kexdh_reply{} = Msg, {key_exchange,client,ReNeg} + + %%%---- diffie-hellman group exchange + handle_event(internal, #ssh_msg_kex_dh_gex_request{} = Msg, {key_exchange,server,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, GexGroup, Ssh1} = ssh_transport:handle_kex_dh_gex_request(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(GexGroup, D), + Ssh = ssh_transport:parallell_gen_key(Ssh1), + {next_state, {key_exchange_dh_gex_init,server,ReNeg}, D#data{ssh_params=Ssh}}; + + handle_event(internal, #ssh_msg_kex_dh_gex_request_old{} = Msg, {key_exchange,server,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, GexGroup, Ssh1} = ssh_transport:handle_kex_dh_gex_request(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(GexGroup, D), + Ssh = ssh_transport:parallell_gen_key(Ssh1), + {next_state, {key_exchange_dh_gex_init,server,ReNeg}, D#data{ssh_params=Ssh}}; + + handle_event(internal, #ssh_msg_kex_dh_gex_group{} = Msg, {key_exchange,client,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, KexGexInit, Ssh} = ssh_transport:handle_kex_dh_gex_group(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(KexGexInit, D), + {next_state, {key_exchange_dh_gex_reply,client,ReNeg}, D#data{ssh_params=Ssh}}; + + %%%---- elliptic curve diffie-hellman + handle_event(internal, #ssh_msg_kex_ecdh_init{} = Msg, {key_exchange,server,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, KexEcdhReply, Ssh1} = ssh_transport:handle_kex_ecdh_init(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(KexEcdhReply, D), + {ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1), +@@ -116,16 +130,25 @@ handle_event(internal, #ssh_msg_kex_ecdh_init{} = Msg, {key_exchange,server,ReNe + {next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}}; + + handle_event(internal, #ssh_msg_kex_ecdh_reply{} = Msg, {key_exchange,client,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, NewKeys, Ssh1} = ssh_transport:handle_kex_ecdh_reply(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(NewKeys, D), + {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1), + ssh_connection_handler:send_bytes(ExtInfo, D), + {next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}}; + ++%%% ######## handle KEX strict ++handle_event(internal, _Event, {key_exchange,_Role,init}, ++ #data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true}, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p", ++ [SendSeq, RecvSeq])); + + %%% ######## {key_exchange_dh_gex_init, server, init|renegotiate} #### +- + handle_event(internal, #ssh_msg_kex_dh_gex_init{} = Msg, {key_exchange_dh_gex_init,server,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, KexGexReply, Ssh1} = ssh_transport:handle_kex_dh_gex_init(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(KexGexReply, D), + {ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1), +@@ -133,20 +156,33 @@ handle_event(internal, #ssh_msg_kex_dh_gex_init{} = Msg, {key_exchange_dh_gex_in + {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh2), + ssh_connection_handler:send_bytes(ExtInfo, D), + {next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}}; +- ++%%% ######## handle KEX strict ++handle_event(internal, _Event, {key_exchange_dh_gex_init,_Role,init}, ++ #data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true}, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p", ++ [SendSeq, RecvSeq])); + + %%% ######## {key_exchange_dh_gex_reply, client, init|renegotiate} #### +- + handle_event(internal, #ssh_msg_kex_dh_gex_reply{} = Msg, {key_exchange_dh_gex_reply,client,ReNeg}, D) -> ++ ok = check_kex_strict(Msg, D), + {ok, NewKeys, Ssh1} = ssh_transport:handle_kex_dh_gex_reply(Msg, D#data.ssh_params), + ssh_connection_handler:send_bytes(NewKeys, D), + {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1), + ssh_connection_handler:send_bytes(ExtInfo, D), + {next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}}; +- ++%%% ######## handle KEX strict ++handle_event(internal, _Event, {key_exchange_dh_gex_reply,_Role,init}, ++ #data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true}, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p", ++ [SendSeq, RecvSeq])); + + %%% ######## {new_keys, client|server} #### +- + %% First key exchange round: + handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,client,init}, D0) -> + {ok, Ssh1} = ssh_transport:handle_new_keys(Msg, D0#data.ssh_params), +@@ -162,6 +198,15 @@ handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,server,init}, D) -> + %% ssh_connection_handler:send_bytes(ExtInfo, D), + {next_state, {ext_info,server,init}, D#data{ssh_params=Ssh}}; + ++%%% ######## handle KEX strict ++handle_event(internal, _Event, {new_keys,_Role,init}, ++ #data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true}, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation (send_sequence = ~p recv_sequence = ~p)", ++ [SendSeq, RecvSeq])); ++ + %% Subsequent key exchange rounds (renegotiation): + handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,Role,renegotiate}, D) -> + {ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params), +@@ -183,7 +228,6 @@ handle_event(internal, #ssh_msg_ext_info{}=Msg, {ext_info,Role,renegotiate}, D0) + handle_event(internal, #ssh_msg_newkeys{}=Msg, {ext_info,_Role,renegotiate}, D) -> + {ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params), + {keep_state, D#data{ssh_params = Ssh}}; +- + + handle_event(internal, Msg, {ext_info,Role,init}, D) when is_tuple(Msg) -> + %% If something else arrives, goto next state and handle the event in that one +@@ -217,3 +261,70 @@ code_change(_OldVsn, StateName, State, _Extra) -> + peer_role(client) -> server; + peer_role(server) -> client. + ++check_kex_strict(Msg, ++ #data{ssh_params = ++ #ssh{algorithms = ++ #alg{ ++ kex = Kex, ++ kex_strict_negotiated = KexStrictNegotiated}, ++ send_sequence = SendSeq, ++ recv_sequence = RecvSeq}}) -> ++ case check_msg_group(Msg, get_alg_group(Kex), KexStrictNegotiated) of ++ ok -> ++ ok; ++ error -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p", ++ [SendSeq, RecvSeq])) ++ end. ++ ++get_alg_group(Kex) when Kex == 'diffie-hellman-group16-sha512'; ++ Kex == 'diffie-hellman-group18-sha512'; ++ Kex == 'diffie-hellman-group14-sha256'; ++ Kex == 'diffie-hellman-group14-sha1'; ++ Kex == 'diffie-hellman-group1-sha1' -> ++ dh_alg; ++get_alg_group(Kex) when Kex == 'diffie-hellman-group-exchange-sha256'; ++ Kex == 'diffie-hellman-group-exchange-sha1' -> ++ dh_gex_alg; ++get_alg_group(Kex) when Kex == 'curve25519-sha256'; ++ Kex == 'curve25519-sha256@libssh.org'; ++ Kex == 'curve448-sha512'; ++ Kex == 'ecdh-sha2-nistp521'; ++ Kex == 'ecdh-sha2-nistp384'; ++ Kex == 'ecdh-sha2-nistp256' -> ++ ecdh_alg. ++ ++check_msg_group(_Msg, _AlgGroup, false) -> ok; ++check_msg_group(#ssh_msg_kexdh_init{}, dh_alg, true) -> ok; ++check_msg_group(#ssh_msg_kexdh_reply{}, dh_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_dh_gex_request_old{}, dh_gex_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_dh_gex_request{}, dh_gex_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_dh_gex_group{}, dh_gex_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_dh_gex_init{}, dh_gex_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_dh_gex_reply{}, dh_gex_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_ecdh_init{}, ecdh_alg, true) -> ok; ++check_msg_group(#ssh_msg_kex_ecdh_reply{}, ecdh_alg, true) -> ok; ++check_msg_group(_Msg, _AlgGroup, _) -> error. ++ ++%%%################################################################ ++%%%# ++%%%# Tracing ++%%%# ++ ++ssh_dbg_trace_points() -> [connection_events]. ++ ++ssh_dbg_flags(connection_events) -> [c]. ++ ++ssh_dbg_on(connection_events) -> dbg:tp(?MODULE, handle_event, 4, x). ++ ++ssh_dbg_off(connection_events) -> dbg:ctpg(?MODULE, handle_event, 4). ++ ++ssh_dbg_format(connection_events, {call, {?MODULE,handle_event, [EventType, EventContent, State, _Data]}}) -> ++ ["Connection event\n", ++ io_lib:format("[~w] EventType: ~p~nEventContent: ~p~nState: ~p~n", [?MODULE, EventType, EventContent, State]) ++ ]; ++ssh_dbg_format(connection_events, {return_from, {?MODULE,handle_event,4}, Ret}) -> ++ ["Connection event result\n", ++ io_lib:format("[~w] ~p~n", [?MODULE, ssh_dbg:reduce_state(Ret, #data{})]) ++ ]. +diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl +index 3e96ca940200..e612ffd0fe30 100644 +--- a/lib/ssh/src/ssh_transport.erl ++++ b/lib/ssh/src/ssh_transport.erl +@@ -26,12 +26,11 @@ + + -include_lib("public_key/include/public_key.hrl"). + -include_lib("kernel/include/inet.hrl"). +- + -include("ssh_transport.hrl"). + -include("ssh.hrl"). + + -export([versions/2, hello_version_msg/1]). +--export([next_seqnum/1, ++-export([next_seqnum/3, + supported_algorithms/0, supported_algorithms/1, + default_algorithms/0, default_algorithms/1, + clear_default_algorithms_env/0, +@@ -295,7 +294,12 @@ random_id(Nlo, Nup) -> + hello_version_msg(Data) -> + [Data,"\r\n"]. + +-next_seqnum(SeqNum) -> ++next_seqnum({State, _Role, init}, 16#ffffffff, ++ #ssh{algorithms = #alg{kex_strict_negotiated = true}}) ++ when State == kexinit; State == key_exchange; State == new_keys -> ++ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ++ io_lib:format("KEX strict violation: recv_sequence = 16#ffffffff", [])); ++next_seqnum(_State, SeqNum, _) -> + (SeqNum + 1) band 16#ffffffff. + + is_valid_mac(_, _ , #ssh{recv_mac_size = 0}) -> +@@ -1080,7 +1084,7 @@ known_host_key(#ssh{opts = Opts, peer = {PeerName,{IP,Port}}} = Ssh, + %% algorithm. Each string MUST contain at least one algorithm name. + select_algorithm(Role, Client, Server, + #ssh{opts = Opts, +- kex_strict_negotiated = KexStrictNegotiated0}, ++ kex_strict_negotiated = KexStrictNegotiated0}, + ReNeg) -> + KexStrictNegotiated = + case ReNeg of +@@ -1105,7 +1109,6 @@ select_algorithm(Role, Client, Server, + _ -> + KexStrictNegotiated0 + end, +- + {Encrypt0, Decrypt0} = select_encrypt_decrypt(Role, Client, Server), + {SendMac0, RecvMac0} = select_send_recv_mac(Role, Client, Server), + +diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl +index 537642cff598..2e1c2a6c7685 100644 +--- a/lib/ssh/test/ssh_protocol_SUITE.erl ++++ b/lib/ssh/test/ssh_protocol_SUITE.erl +@@ -55,7 +55,9 @@ + ext_info_c/1, + ext_info_s/1, + kex_strict_negotiated/1, +- kex_strict_msg_ignore/1, ++ kex_strict_violation_key_exchange/1, ++ kex_strict_violation_new_keys/1, ++ kex_strict_violation/1, + kex_strict_msg_unknown/1, + gex_client_init_option_groups/1, + gex_client_init_option_groups_file/1, +@@ -144,7 +146,9 @@ groups() -> + gex_client_old_request_exact, + gex_client_old_request_noexact, + kex_strict_negotiated, +- kex_strict_msg_ignore, ++ kex_strict_violation_key_exchange, ++ kex_strict_violation_new_keys, ++ kex_strict_violation, + kex_strict_msg_unknown]}, + {service_requests, [], [bad_service_name, + bad_long_service_name, +@@ -1007,22 +1011,145 @@ kex_strict_negotiated(Config0) -> + ssh_test_lib:rm_log_handler(), + ok. + +-%% Connect to an erlang server and inject unexpected SSH ignore +-kex_strict_msg_ignore(Config) -> +- ct:log("START: ~p~n=================================", [?FUNCTION_NAME]), +- ExpectedReason = "strict KEX violation: unexpected SSH_MSG_IGNORE", +- TestMessages = +- [{send, ssh_msg_ignore}, +- {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg}, +- {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}], +- kex_strict_helper(Config, TestMessages, ExpectedReason). ++%% Connect to an erlang server and inject unexpected SSH message ++%% ssh_fsm_kexinit in key_exchange state ++kex_strict_violation_key_exchange(Config) -> ++ ExpectedReason = "KEX strict violation", ++ Injections = [ssh_msg_ignore, ssh_msg_debug, ssh_msg_unimplemented], ++ TestProcedure = ++ fun(M) -> ++ ct:log( ++ "=================== START: ~p Message: ~p Expected Fail =================================", ++ [?FUNCTION_NAME, M]), ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, M}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}] ++ end, ++ [kex_strict_helper(Config, TestProcedure(Msg), ExpectedReason) || ++ Msg <- Injections], ++ ct:log("========== END ========"), ++ ok. ++ ++%% Connect to an erlang server and inject unexpected SSH message ++%% ssh_fsm_kexinit in new_keys state ++kex_strict_violation_new_keys(Config) -> ++ ExpectedReason = "KEX strict violation", ++ Injections = [ssh_msg_ignore, ssh_msg_debug, ssh_msg_unimplemented], ++ TestProcedure = ++ fun(M) -> ++ ct:log( ++ "=================== START: ~p Message: ~p Expected Fail =================================", ++ [?FUNCTION_NAME, M]), ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init}, ++ {send, M}, ++ {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}] ++ end, ++ [kex_strict_helper(Config, TestProcedure(Msg), ExpectedReason) || ++ Msg <- Injections], ++ ct:log("========== END ========"), ++ ok. ++ ++%% Connect to an erlang server and inject unexpected SSH message ++%% duplicated KEXINIT ++kex_strict_violation(Config) -> ++ KexDhReply = ++ #ssh_msg_kexdh_reply{ ++ public_host_key = {{{'ECPoint',<<73,72,235,162,96,101,154,59,217,114,123,192,96,105,250,29,214,76,60,63,167,21,221,118,246,168,152,2,7,172,137,125>>}, ++ {namedCurve,{1,3,101,112}}}, ++ 'ssh-ed25519'}, ++ f = 18504393053016436370762156176197081926381112956345797067569792020930728564439992620494295053804030674742529174859108487694089045521619258420515443400605141150065440678508889060925968846155921972385560196703381004650914261218463420313738628465563288022895912907728767735629532940627575655703806353550720122093175255090704443612257683903495753071530605378193139909567971489952258218767352348904221407081210633467414579377014704081235998044497191940270966762124544755076128392259615566530695493013708460088312025006678879288856957348606386230195080105197251789635675011844976120745546472873505352732719507783227210178188, ++ h_sig = <<90,247,44,240,136,196,82,215,56,165,53,33,230,101,253, ++ 34,112,201,21,131,162,169,10,129,174,14,69,25,39,174, ++ 92,210,130,249,103,2,215,245,7,213,110,235,136,134,11, ++ 124,248,139,79,17,225,77,125,182,204,84,137,167,99,186, ++ 167,42,192,10>>}, ++ TestFlows = ++ [ ++ {kexinit, "KEX strict violation", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexinit}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}]}, ++ {ssh_msg_kexdh_init, "KEX strict violation", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init_dup}, ++ {match,# ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}]}, ++ {new_keys, "Message ssh_msg_newkeys in wrong state", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init}, ++ {match,# ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ {send, #ssh_msg_newkeys{}}, ++ {match, #ssh_msg_newkeys{_='_'}, receive_msg}, ++ {send, #ssh_msg_newkeys{}}, ++ {match, disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR), receive_msg}]}, ++ {ssh_msg_unexpected_dh_gex, "KEX strict violation", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ %% dh_alg is expected but dh_gex_alg is provided ++ {send, #ssh_msg_kex_dh_gex_request{min = 1000, n = 3000, max = 4000}}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}]}, ++ {wrong_role, "KEX strict violation", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ %% client should not send message below ++ {send, KexDhReply}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}]}, ++ {wrong_role2, "KEX strict violation", ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init}, ++ {match,# ssh_msg_kexdh_reply{_='_'}, receive_msg}, ++ %% client should not send message below ++ {send, KexDhReply}, ++ {match, #ssh_msg_newkeys{_='_'}, receive_msg}, ++ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}]} ++ ], ++ TestProcedure = ++ fun({Msg, _, P}) -> ++ ct:log( ++ "==== START: ~p (duplicated ~p) Expected Fail ====~n~p", ++ [?FUNCTION_NAME, Msg, P]), ++ P ++ end, ++ [kex_strict_helper(Config, TestProcedure(Procedure), Reason) || ++ Procedure = {_, Reason, _} <- TestFlows], ++ ct:log("==== END ====="), ++ ok. + + %% Connect to an erlang server and inject unexpected non-SSH binary + kex_strict_msg_unknown(Config) -> + ct:log("START: ~p~n=================================", [?FUNCTION_NAME]), + ExpectedReason = "Bad packet: Size", + TestMessages = +- [{send, ssh_msg_unknown}, ++ [receive_hello, ++ {send, hello}, ++ {send, ssh_msg_kexinit}, ++ {match, #ssh_msg_kexinit{_='_'}, receive_msg}, ++ {send, ssh_msg_kexdh_init}, ++ {send, ssh_msg_unknown}, + {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg}, + {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}], + kex_strict_helper(Config, TestMessages, ExpectedReason). +@@ -1047,12 +1174,7 @@ kex_strict_helper(Config, TestMessages, ExpectedReason) -> + {user_dir, user_dir(Config)}, + {user_interaction, false} + | proplists:get_value(extra_options,Config,[]) +- ]}, +- receive_hello, +- {send, hello}, +- {send, ssh_msg_kexinit}, +- {match, #ssh_msg_kexinit{_='_'}, receive_msg}, +- {send, ssh_msg_kexdh_init}] ++ ++ ]}] ++ + TestMessages, + InitialState), + ct:sleep(100), +diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl +index f03fee1662ed..e34db487e5a2 100644 +--- a/lib/ssh/test/ssh_trpt_test_lib.erl ++++ b/lib/ssh/test/ssh_trpt_test_lib.erl +@@ -90,7 +90,8 @@ exec(Op, S0=#s{}) -> + report_trace(throw, Term, S1), + throw({Term,Op}); + +- error:Error -> ++ error:Error:St -> ++ ct:log("Stacktrace=~n~p", [St]), + report_trace(error, Error, S1), + error({Error,Op}); + +@@ -335,6 +336,17 @@ send(S0, ssh_msg_ignore) -> + Msg = #ssh_msg_ignore{data = "unexpected_ignore_message"}, + send(S0, Msg); + ++send(S0, ssh_msg_debug) -> ++ Msg = #ssh_msg_debug{ ++ always_display = true, ++ message = "some debug message", ++ language = "en"}, ++ send(S0, Msg); ++ ++send(S0, ssh_msg_unimplemented) -> ++ Msg = #ssh_msg_unimplemented{sequence = 123}, ++ send(S0, Msg); ++ + send(S0, ssh_msg_unknown) -> + Msg = binary:encode_hex(<<"0000000C060900000000000000000000">>), + send(S0, Msg); +@@ -382,6 +394,26 @@ send(S0, ssh_msg_kexdh_init) when ?role(S0) == client -> + end), + send_bytes(NextKexMsgBin, S#s{ssh = C}); + ++send(S0, ssh_msg_kexdh_init_dup) when ?role(S0) == client -> ++ {OwnMsg, PeerMsg} = S0#s.alg_neg, ++ {ok, NextKexMsgBin, C} = ++ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S0#s.ssh, init) ++ catch ++ Class:Exc -> ++ fail("Algorithm negotiation failed!", ++ {"Algorithm negotiation failed at line ~p:~p~n~p:~s~nPeer: ~s~n Own: ~s", ++ [?MODULE,?LINE,Class,format_msg(Exc),format_msg(PeerMsg),format_msg(OwnMsg)]}, ++ S0) ++ end, ++ S = opt(print_messages, S0, ++ fun(X) when X==true;X==detail -> ++ #ssh{keyex_key = {{_Private, Public}, {_G, _P}}} = C, ++ Msg = #ssh_msg_kexdh_init{e = Public}, ++ {"Send (reconstructed)~n~s~n",[format_msg(Msg)]} ++ end), ++ send_bytes(NextKexMsgBin, S#s{ssh = C}), ++ send_bytes(NextKexMsgBin, S#s{ssh = C}); ++ + send(S0, ssh_msg_kexdh_reply) -> + Bytes = proplists:get_value(ssh_msg_kexdh_reply, S0#s.reply), + S = opt(print_messages, S0, +@@ -531,7 +563,10 @@ receive_binary_msg(S0=#s{}) -> + S0#s.ssh) + of + {packet_decrypted, DecryptedBytes, EncryptedDataRest, Ssh1} -> +- S1 = S0#s{ssh = Ssh1#ssh{recv_sequence = ssh_transport:next_seqnum(Ssh1#ssh.recv_sequence)}, ++ S1 = S0#s{ssh = Ssh1#ssh{recv_sequence = ++ ssh_transport:next_seqnum(undefined, ++ Ssh1#ssh.recv_sequence, ++ false)}, + decrypted_data_buffer = <<>>, + undecrypted_packet_length = undefined, + aead_data = <<>>, diff --git a/CVE-2025-46712-2.patch b/CVE-2025-46712-2.patch new file mode 100644 index 0000000..6c33322 --- /dev/null +++ b/CVE-2025-46712-2.patch @@ -0,0 +1,22 @@ +From 816b5f70196486e693dd0a3ce59f9dde7ba558db Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Wed, 7 May 2025 16:58:27 +0200 +Subject: [PATCH] ssh: ssh_test_lib add extra remove_handler to improve + robustness in tests + +--- + lib/ssh/test/ssh_test_lib.erl | 1 + + 1 file changed, 1 insertion(+) + +diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl +index 96b4f10392f1..210944cdb1f8 100644 +--- a/lib/ssh/test/ssh_test_lib.erl ++++ b/lib/ssh/test/ssh_test_lib.erl +@@ -1324,6 +1324,7 @@ set_log_level(Level) -> + ok = logger:set_primary_config(level, Level). + + add_log_handler() -> ++ logger:remove_handler(?MODULE), + TestRef = make_ref(), + ok = logger:add_handler(?MODULE, ?MODULE, + #{level => debug, diff --git a/CVE-2025-46712-pre-ssh-reduce-KEX-strict-message-verbosity.patch b/CVE-2025-46712-pre-ssh-reduce-KEX-strict-message-verbosity.patch new file mode 100644 index 0000000..bfd448e --- /dev/null +++ b/CVE-2025-46712-pre-ssh-reduce-KEX-strict-message-verbosity.patch @@ -0,0 +1,308 @@ +From 68b3f7d18db789845a0027004b53e5051d5a6683 Mon Sep 17 00:00:00 2001 +From: Jakub Witczak +Date: Fri, 23 Feb 2024 16:07:16 +0100 +Subject: [PATCH] ssh: reduce KEX strict message verbosity + +- emit "KEX strict" message as debug +- related test adjustments +--- + lib/ssh/src/ssh_transport.erl | 3 +- + lib/ssh/test/ssh_protocol_SUITE.erl | 35 ++++++------- + lib/ssh/test/ssh_test_lib.erl | 73 ++++++++++++++++++++------- + lib/ssh/test/ssh_to_openssh_SUITE.erl | 52 +++++++++++-------- + 4 files changed, 103 insertions(+), 60 deletions(-) + +diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl +index 7846b356a542..e6161c367ba7 100644 +--- a/lib/ssh/src/ssh_transport.erl ++++ b/lib/ssh/src/ssh_transport.erl +@@ -1097,8 +1097,7 @@ select_algorithm(Role, Client, Server, + end, + case Result of + true -> +- error_logger:info_report( +- lists:concat([Role, " will use strict KEX ordering"])); ++ logger:debug(lists:concat([Role, " will use strict KEX ordering"])); + _ -> + ok + end, +diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl +index 186c867e2fa9..3222686d9bcf 100644 +--- a/lib/ssh/test/ssh_protocol_SUITE.erl ++++ b/lib/ssh/test/ssh_protocol_SUITE.erl +@@ -827,19 +827,19 @@ ext_info_c(Config) -> + %%%-------------------------------------------------------------------- + %%% + kex_strict_negotiated(Config0) -> +- {ok,Pid} = ssh_test_lib:add_report_handler(), ++ {ok, TestRef} = ssh_test_lib:add_log_handler(), + Config = start_std_daemon(Config0, []), + {Server, Host, Port} = proplists:get_value(server, Config), +- #{level := Level} = logger:get_primary_config(), +- logger:set_primary_config(level, notice), ++ Level = ssh_test_lib:get_log_level(), ++ ssh_test_lib:set_log_level(debug), + {ok, ConnRef} = std_connect({Host, Port}, Config, []), + {algorithms, A} = ssh:connection_info(ConnRef, algorithms), + ssh:stop_daemon(Server), +- {ok, Reports} = ssh_test_lib:get_reports(Pid), +- ct:log("Reports = ~p", [Reports]), +- true = ssh_test_lib:kex_strict_negotiated(client, Reports), +- true = ssh_test_lib:kex_strict_negotiated(server, Reports), +- logger:set_primary_config(Level), ++ {ok, Events} = ssh_test_lib:get_log_events(TestRef), ++ true = ssh_test_lib:kex_strict_negotiated(client, Events), ++ true = ssh_test_lib:kex_strict_negotiated(server, Events), ++ ssh_test_lib:set_log_level(Level), ++ ssh_test_lib:rm_log_handler(), + ok. + + %% Connect to an erlang server and inject unexpected SSH ignore +@@ -863,9 +863,9 @@ kex_strict_msg_unknown(Config) -> + kex_strict_helper(Config, TestMessages, ExpectedReason). + + kex_strict_helper(Config, TestMessages, ExpectedReason) -> +- {ok,HandlerPid} = ssh_test_lib:add_report_handler(), +- #{level := Level} = logger:get_primary_config(), +- logger:set_primary_config(level, notice), ++ {ok, TestRef} = ssh_test_lib:add_log_handler(), ++ Level = ssh_test_lib:get_log_level(), ++ ssh_test_lib:set_log_level(debug), + %% Connect and negotiate keys + {ok, InitialState} = ssh_trpt_test_lib:exec( + [{set_options, [print_ops, print_seqnums, print_messages]}] +@@ -891,12 +891,13 @@ kex_strict_helper(Config, TestMessages, ExpectedReason) -> + TestMessages, + InitialState), + ct:sleep(100), +- {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), +- ct:log("HandlerPid = ~p~nReports = ~p", [HandlerPid, Reports]), +- true = ssh_test_lib:kex_strict_negotiated(client, Reports), +- true = ssh_test_lib:kex_strict_negotiated(server, Reports), +- true = ssh_test_lib:event_logged(server, Reports, ExpectedReason), +- logger:set_primary_config(Level), ++ {ok, Events} = ssh_test_lib:get_log_events(TestRef), ++ ssh_test_lib:rm_log_handler(), ++ ct:log("Events = ~p", [Events]), ++ true = ssh_test_lib:kex_strict_negotiated(client, Events), ++ true = ssh_test_lib:kex_strict_negotiated(server, Events), ++ true = ssh_test_lib:event_logged(server, Events, ExpectedReason), ++ ssh_test_lib:set_log_level(Level), + ok. + + %%%---------------------------------------------------------------- +diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl +index e364ab0baebb..04bfd122f98e 100644 +--- a/lib/ssh/test/ssh_test_lib.erl ++++ b/lib/ssh/test/ssh_test_lib.erl +@@ -122,11 +122,13 @@ setup_host_key/3, + setup_known_host/3, + get_addr_str/0, + file_base_name/2, +-add_report_handler/0, +-get_reports/1, + kex_strict_negotiated/2, + event_logged/3 + ]). ++%% logger callbacks and related helpers ++-export([log/2, ++ get_log_level/0, set_log_level/1, add_log_handler/0, ++ rm_log_handler/0, get_log_events/1]). + + -include_lib("common_test/include/ct.hrl"). + -include("ssh_transport.hrl"). +@@ -1271,15 +1273,10 @@ file_base_name(system_src, 'ecdsa-sha2-nistp521') -> "ssh_host_ecdsa_key521"; + file_base_name(system_src, Alg) -> file_base_name(system, Alg). + + %%%---------------------------------------------------------------- +-add_report_handler() -> +- ssh_eqc_event_handler:add_report_handler(). +- +-get_reports(Pid) -> +- ssh_eqc_event_handler:get_reports(Pid). +- + -define(SEARCH_FUN(EXP), + begin +- fun({info_report, _, {_, std_info, EXP}}) -> ++ fun(#{msg := {string, EXP}, ++ level := debug}) -> + true; + (_) -> + false +@@ -1287,19 +1284,20 @@ get_reports(Pid) -> + end). + -define(SEARCH_SUFFIX, " will use strict KEX ordering"). + +-kex_strict_negotiated(client, Reports) -> +- kex_strict_negotiated(?SEARCH_FUN("client" ++ ?SEARCH_SUFFIX), Reports); +-kex_strict_negotiated(server, Reports) -> +- kex_strict_negotiated(?SEARCH_FUN("server" ++ ?SEARCH_SUFFIX), Reports); +-kex_strict_negotiated(SearchFun, Reports) when is_function(SearchFun) -> +- case lists:search(SearchFun, Reports) of ++kex_strict_negotiated(client, Events) -> ++ kex_strict_negotiated(?SEARCH_FUN("client" ++ ?SEARCH_SUFFIX), Events); ++kex_strict_negotiated(server, Events) -> ++ kex_strict_negotiated(?SEARCH_FUN("server" ++ ?SEARCH_SUFFIX), Events); ++kex_strict_negotiated(SearchFun, Events) when is_function(SearchFun) -> ++ %% FIXME use event_logged? ++ case lists:search(SearchFun, Events) of + {value, _} -> true; + _ -> false + end. + +-event_logged(Role, Reports, Reason) -> ++event_logged(Role, Events, Reason) -> + SearchF = +- fun({info_msg, _, {_, _Format, Args}}) -> ++ fun(#{msg := {report, #{args := Args}}}) -> + AnyF = fun (E) when is_list(E) -> + case string:find(E, Reason) of + nomatch -> false; +@@ -1310,10 +1308,47 @@ event_logged(Role, Reports, Reason) -> + end, + lists:member(Role, Args) andalso + lists:any(AnyF, Args); +- (_) -> ++ (_Event) -> + false + end, +- case lists:search(SearchF, Reports) of ++ case lists:search(SearchF, Events) of + {value, _} -> true; + _ -> false + end. ++ ++get_log_level() -> ++ #{level := Level} = logger:get_primary_config(), ++ Level. ++ ++set_log_level(Level) -> ++ ok = logger:set_primary_config(level, Level). ++ ++add_log_handler() -> ++ TestRef = make_ref(), ++ ok = logger:add_handler(?MODULE, ?MODULE, ++ #{level => debug, ++ filter_default => log, ++ recipient => self(), ++ test_ref => TestRef}), ++ {ok, TestRef}. ++ ++rm_log_handler() -> ++ ok = logger:remove_handler(?MODULE). ++ ++get_log_events(TestRef) -> ++ {ok, get_log_events(TestRef, [])}. ++ ++get_log_events(TestRef, Acc) -> ++ receive ++ {TestRef, Event} -> ++ get_log_events(TestRef, [Event | Acc]) ++ after ++ 500 -> ++ Acc ++ end. ++ ++%% logger callbacks ++log(LogEvent = #{level:=_Level,msg:=_Msg,meta:=_Meta}, ++ #{test_ref := TestRef, recipient := Recipient}) -> ++ Recipient ! {TestRef, LogEvent}, ++ ok. +diff --git a/lib/ssh/test/ssh_to_openssh_SUITE.erl b/lib/ssh/test/ssh_to_openssh_SUITE.erl +index 5a8f4b31187d..16bedf1763b3 100644 +--- a/lib/ssh/test/ssh_to_openssh_SUITE.erl ++++ b/lib/ssh/test/ssh_to_openssh_SUITE.erl +@@ -146,29 +146,32 @@ end_per_testcase(_TestCase, _Config) -> + %% Test Cases -------------------------------------------------------- + %%-------------------------------------------------------------------- + erlang_shell_client_openssh_server(Config) when is_list(Config) -> +- eclient_oserver_helper(Config). ++ eclient_oserver_helper2(eclient_oserver_helper1(), Config). + + eclient_oserver_kex_strict(Config) when is_list(Config)-> + case proplists:get_value(kex_strict, Config) of + true -> +- {ok, HandlerPid} = ssh_test_lib:add_report_handler(), +- #{level := Level} = logger:get_primary_config(), +- logger:set_primary_config(level, notice), +- Result = eclient_oserver_helper(Config), +- {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), +- ct:pal("Reports = ~p", [Reports]), +- true = ssh_test_lib:kex_strict_negotiated(client, Reports), +- logger:set_primary_config(Level), +- Result; ++ {ok, TestRef} = ssh_test_lib:add_log_handler(), ++ Level = ssh_test_lib:get_log_level(), ++ ssh_test_lib:set_log_level(debug), ++ HelperParams = eclient_oserver_helper1(), ++ {ok, Events} = ssh_test_lib:get_log_events(TestRef), ++ true = ssh_test_lib:kex_strict_negotiated(client, Events), ++ ssh_test_lib:set_log_level(Level), ++ ssh_test_lib:rm_log_handler(), ++ eclient_oserver_helper2(HelperParams, Config); + _ -> + {skip, "KEX strict not support by local OpenSSH"} + end. + +-eclient_oserver_helper(Config) -> ++eclient_oserver_helper1() -> + process_flag(trap_exit, true), + IO = ssh_test_lib:start_io_server(), + Prev = lists:usort(supervisor:which_children(sshc_sup)), + Shell = ssh_test_lib:start_shell(?SSH_DEFAULT_PORT, IO), ++ {Shell, Prev, IO}. ++ ++eclient_oserver_helper2({Shell, Prev, IO}, Config) -> + IO ! {input, self(), "echo Hej\n"}, + case proplists:get_value(ptty_supported, Config) of + true -> +@@ -253,25 +256,28 @@ exec_direct_with_io_in_sshc(Config) when is_list(Config) -> + %%-------------------------------------------------------------------- + %% Test that the Erlang/OTP server can renegotiate with openSSH + erlang_server_openssh_client_renegotiate(Config) -> +- eserver_oclient_renegotiate_helper(Config). ++ eserver_oclient_renegotiate_helper2( ++ eserver_oclient_renegotiate_helper1(Config)). + + eserver_oclient_kex_strict(Config) -> + case proplists:get_value(kex_strict, Config) of + true -> +- {ok, HandlerPid} = ssh_test_lib:add_report_handler(), +- #{level := Level} = logger:get_primary_config(), +- logger:set_primary_config(level, notice), +- Result = eserver_oclient_renegotiate_helper(Config), +- {ok, Reports} = ssh_test_lib:get_reports(HandlerPid), +- ct:log("Reports = ~p", [Reports]), +- true = ssh_test_lib:kex_strict_negotiated(server, Reports), +- logger:set_primary_config(Level), +- Result; ++ {ok, TestRef} = ssh_test_lib:add_log_handler(), ++ Level = ssh_test_lib:get_log_level(), ++ ssh_test_lib:set_log_level(debug), ++ ++ HelperParams = eserver_oclient_renegotiate_helper1(Config), ++ {ok, Events} = ssh_test_lib:get_log_events(TestRef), ++ ct:log("Events = ~n~p", [Events]), ++ true = ssh_test_lib:kex_strict_negotiated(server, Events), ++ ssh_test_lib:set_log_level(Level), ++ ssh_test_lib:rm_log_handler(), ++ eserver_oclient_renegotiate_helper2(HelperParams); + _ -> + {skip, "KEX strict not support by local OpenSSH"} + end. + +-eserver_oclient_renegotiate_helper(Config) -> ++eserver_oclient_renegotiate_helper1(Config) -> + _PubKeyAlg = ssh_rsa, + SystemDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), +@@ -295,7 +301,9 @@ eserver_oclient_renegotiate_helper(Config) -> + + + OpenSsh = ssh_test_lib:open_port({spawn, Cmd++" < "++DataFile}), ++ {Data, OpenSsh, Pid}. + ++eserver_oclient_renegotiate_helper2({Data, OpenSsh, Pid}) -> + Expect = fun({data,R}) -> + try + NonAlphaChars = [C || C<-lists:seq(1,255), diff --git a/README.en.md b/README.en.md new file mode 100644 index 0000000..3afb629 --- /dev/null +++ b/README.en.md @@ -0,0 +1,36 @@ +# erlang + +#### Description +A general-purpose programming language and runtime environment + +#### Software Architecture +Software architecture description + +#### Installation + +1. xxxx +2. xxxx +3. xxxx + +#### Instructions + +1. xxxx +2. xxxx +3. xxxx + +#### Contribution + +1. Fork the repository +2. Create Feat_xxx branch +3. Commit your code +4. Create Pull Request + + +#### Gitee Feature + +1. You can use Readme\_XXX.md to support different languages, such as Readme\_en.md, Readme\_zh.md +2. Gitee blog [blog.gitee.com](https://blog.gitee.com) +3. Explore open source project [https://gitee.com/explore](https://gitee.com/explore) +4. The most valuable open source project [GVP](https://gitee.com/gvp) +5. The manual of Gitee [https://gitee.com/help](https://gitee.com/help) +6. The most popular members [https://gitee.com/gitee-stars/](https://gitee.com/gitee-stars/) diff --git a/README.md b/README.md new file mode 100644 index 0000000..8fccff8 --- /dev/null +++ b/README.md @@ -0,0 +1,37 @@ +# erlang + +#### 介绍 +A general-purpose programming language and runtime environment + +#### 软件架构 +软件架构说明 + + +#### 安装教程 + +1. xxxx +2. xxxx +3. xxxx + +#### 使用说明 + +1. xxxx +2. xxxx +3. xxxx + +#### 参与贡献 + +1. Fork 本仓库 +2. 新建 Feat_xxx 分支 +3. 提交代码 +4. 新建 Pull Request + + +#### 码云特技 + +1. 使用 Readme\_XXX.md 来支持不同的语言,例如 Readme\_en.md, Readme\_zh.md +2. 码云官方博客 [blog.gitee.com](https://blog.gitee.com) +3. 你可以 [https://gitee.com/explore](https://gitee.com/explore) 这个地址来了解码云上的优秀开源项目 +4. [GVP](https://gitee.com/gvp) 全称是码云最有价值开源项目,是码云综合评定出的优秀开源项目 +5. 码云官方提供的使用手册 [https://gitee.com/help](https://gitee.com/help) +6. 码云封面人物是一档用来展示码云会员风采的栏目 [https://gitee.com/gitee-stars/](https://gitee.com/gitee-stars/) diff --git a/epmd.service b/epmd.service new file mode 100644 index 0000000..6881195 --- /dev/null +++ b/epmd.service @@ -0,0 +1,25 @@ +[Unit] +Description=Erlang Port Mapper Daemon +After=network.target +Requires=epmd.socket + +[Service] +ExecStart=/usr/bin/epmd -systemd +#ExecStop=/usr/bin/epmd -kill +Type=notify +StandardOutput=journal +StandardError=journal +DeviceAllow=/dev/null rw +PrivateTmp=true +#CapabilityBoundingSet= +NoNewPrivileges=true +Restart=always +LimitNPROC=1 +LimitFSIZE=0 +User=epmd +Group=epmd + +[Install] +Also=epmd.socket +WantedBy=multi-user.target + diff --git a/epmd.socket b/epmd.socket new file mode 100644 index 0000000..34817e0 --- /dev/null +++ b/epmd.socket @@ -0,0 +1,10 @@ +[Unit] +Description=Erlang Port Mapper Daemon Activation Socket + +[Socket] +ListenStream=4369 +Accept=false + +[Install] +WantedBy=sockets.target + diff --git a/epmd@.service b/epmd@.service new file mode 100644 index 0000000..822268f --- /dev/null +++ b/epmd@.service @@ -0,0 +1,25 @@ +[Unit] +Description=Erlang Port Mapper Daemon +After=network.target +Requires=epmd@.socket + +[Service] +ExecStart=/usr/bin/epmd -systemd +#ExecStop=/usr/bin/epmd -kill +Type=notify +StandardOutput=journal +StandardError=journal +DeviceAllow=/dev/null rw +PrivateTmp=true +#CapabilityBoundingSet= +NoNewPrivileges=true +Restart=always +LimitNPROC=1 +LimitFSIZE=0 +User=epmd +Group=epmd + +[Install] +Also=epmd@.socket +WantedBy=multi-user.target + diff --git a/epmd@.socket b/epmd@.socket new file mode 100644 index 0000000..f3e5338 --- /dev/null +++ b/epmd@.socket @@ -0,0 +1,10 @@ +[Unit] +Description=Erlang Port Mapper Daemon Activation Socket + +[Socket] +ListenStream=%I +Accept=false + +[Install] +WantedBy=sockets.target + diff --git a/erlang.spec b/erlang.spec new file mode 100644 index 0000000..556197b --- /dev/null +++ b/erlang.spec @@ -0,0 +1,1807 @@ +%global need_bootstrap_set 0 +%{!?need_bootstrap: %global need_bootstrap %{need_bootstrap_set}} +%bcond_with doc +# Compile with FIPS support by default +%bcond_without fips +%global __with_emacs 1 +%global __with_examples 1 +%global __with_java 1 +%global __with_wxwidgets 1 +%global __with_sources 1 +Name: erlang +Version: 25.3.2.6 +Release: 7 +Summary: General-purpose programming language and runtime environment +License: Apache-2.0 +URL: https://www.erlang.org +VCS: scm:git:https://github.com/erlang/otp +Source0: https://github.com/erlang/otp/archive/OTP-%{version}/otp-OTP-%{version}.tar.gz +Source1: epmd.service +Source2: epmd.socket +Source3: epmd@.service +Source4: epmd@.socket +Patch1: otp-0001-Do-not-format-man-pages-and-do-not-install-miscellan.patch +Patch2: otp-0002-Remove-rpath.patch +Patch3: otp-0003-Do-not-install-C-sources.patch +Patch4: otp-0004-Do-not-install-Java-sources.patch +Patch5: otp-0005-Do-not-install-nteventlog-and-related-doc-files-on-n.patch +Patch6: otp-0006-Do-not-install-erlang-sources.patch +Patch7: otp-0007-Add-extra-search-directory.patch +Patch8: otp-0008-Avoid-forking-sed-to-get-basename.patch +Patch9: otp-0009-Load-man-pages-from-system-wide-directory.patch +Patch10: otp-0010-configure.ac-C99-fix-for-ERTS___AFTER_MORECORE_HOOK_.patch +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 +Patch19: CVE-2025-32433.patch +Patch20: CVE-2025-46712-pre-ssh-reduce-KEX-strict-message-verbosity.patch +Patch21: CVE-2025-46712-1.patch +Patch22: CVE-2025-46712-2.patch + +BuildRequires: gcc gcc-c++ flex make +%if %{with doc} +%if 0%{?need_bootstrap} < 1 +BuildRequires: erlang +%endif +%endif +BuildRequires: systemd-devel systemd +%{?systemd_requires} +Requires: systemd +BuildRequires: autoconf automake +Requires: %{name}-asn1%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-common_test%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-debugger%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +%if %{__with_wxwidgets} +Requires: %{name}-dialyzer%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-diameter%{?_isa} = %{version}-%{release} +Requires: %{name}-edoc%{?_isa} = %{version}-%{release} +Requires: %{name}-eldap%{?_isa} = %{version}-%{release} +Requires: %{name}-erl_docgen%{?_isa} = %{version}-%{release} +Requires: %{name}-erl_interface%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-et%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-eunit%{?_isa} = %{version}-%{release} +Requires: %{name}-ftp%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +%if %{__with_java} +Requires: %{name}-jinterface%{?_isa} = %{version}-%{release} +%endif # __with_java +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-megaco%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-observer%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-odbc%{?_isa} = %{version}-%{release} +Requires: %{name}-os_mon%{?_isa} = %{version}-%{release} +Requires: %{name}-parsetools%{?_isa} = %{version}-%{release} +Requires: %{name}-public_key%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-reltool%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-snmp%{?_isa} = %{version}-%{release} +Requires: %{name}-ssh%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-tftp%{?_isa} = %{version}-%{release} +Requires: %{name}-tools%{?_isa} = %{version}-%{release} +%if %{__with_wxwidgets} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +%endif %{__with_wxwidgets} +Requires: %{name}-xmerl%{?_isa} = %{version}-%{release} +%description +Erlang is a general-purpose programming language and runtime +environment. Erlang has built-in support for concurrency, distribution +and fault tolerance. Erlang is used in several large telecommunication +systems from Ericsson. + +%package asn1 +Summary: Provides support for Abstract Syntax Notation One +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description asn1 +Provides support for Abstract Syntax Notation One. +%if %{__with_wxwidgets} + +%package common_test +Summary: A portable framework for automatic testing +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-debugger%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-observer%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-snmp%{?_isa} = %{version}-%{release} +Requires: %{name}-ssh%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-tools%{?_isa} = %{version}-%{release} +Requires: %{name}-xmerl%{?_isa} = %{version}-%{release} +Obsoletes: erlang-test_server +%description common_test +A portable framework for automatic testing. +%endif %{__with_wxwidgets} + +%package compiler +Summary: A byte code compiler for Erlang which produces highly compact code +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description compiler +A byte code compiler for Erlang which produces highly compact code. + +%package crypto +Summary: Cryptographical support +BuildRequires: compat-openssl11-devel +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description crypto +Cryptographical support. +%if %{__with_wxwidgets} + +%package debugger +Summary: A debugger for debugging and testing of Erlang programs +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +%description debugger +A debugger for debugging and testing of Erlang programs. +%endif %{__with_wxwidgets} +%if %{__with_wxwidgets} + +%package dialyzer +Summary: A DIscrepancy AnaLYZer for ERlang programs +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} graphviz +Obsoletes: erlang-typer +%description dialyzer +A DIscrepancy AnaLYZer for ERlang programs. +%endif %{__with_wxwidgets} + +%package diameter +Summary: Diameter (RFC 3588) library +BuildRequires: ed +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +%description diameter +Diameter (RFC 3588) library +%if %{with doc} + +%package doc +Summary: Erlang documentation +BuildRequires: fop libxslt +BuildArch: noarch +%description doc +Documentation for Erlang. +%endif + +%package edoc +Summary: A utility used to generate documentation out of tags in source files +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-xmerl%{?_isa} = %{version}-%{release} +%description edoc +A utility used to generate documentation out of tags in source files. + +%package eldap +Summary: Erlang LDAP library +Requires: %{name}-asn1%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description eldap +Erlang LDAP library. + +%package erl_docgen +Summary: A utility used to generate erlang HTML documentation +Requires: %{name}-edoc%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-xmerl%{?_isa} = %{version}-%{release} +%description erl_docgen +A utility used to generate erlang HTML documentation. + +%package erl_interface +Summary: Low level interface to C +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +%description erl_interface +Low level interface to C. + +%package erts +Summary: Functionality necessary to run the Erlang System itself +BuildRequires: lksctp-tools-devel m4 ncurses-devel zlib-devel +Requires(pre): shadow-utils +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} lksctp-tools +Provides: erlang(erl_drv_version) = 3.3 +Provides: erlang(erl_nif_version) = 2.16 +Provides: bundled(pcre) = 8.44 +Obsoletes: erlang-appmon +Obsoletes: erlang-docbuilder +Obsoletes: erlang-gs +Obsoletes: erlang-inviso +Obsoletes: erlang-ose +Obsoletes: erlang-percept < 20.2.3 +Obsoletes: erlang-pman +Obsoletes: erlang-toolbar +Obsoletes: erlang-tv +Obsoletes: erlang-webtool +Obsoletes: erlang-hipe +Obsoletes: erlang-otp_mibs +%description erts +Functionality necessary to run the Erlang System itself. +%if %{__with_wxwidgets} + +%package et +Summary: An event tracer for Erlang programs +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +%description et +An event tracer for Erlang programs. +%endif %{__with_wxwidgets} + +%package eunit +Summary: Support for unit testing +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description eunit +Support for unit testing. +%if %{__with_examples} + +%package examples +Summary: Examples for some Erlang modules +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-public_key%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description examples +Examples for some Erlang modules. +%endif %{__with_examples} + +%package ftp +Summary: FTP client +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description ftp +FTP client. + +%package inets +Summary: A set of services such as a Web server and a HTTP client etc +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description inets +A set of services such as a Web server and a HTTP client etc. +%if %{__with_java} + +%package jinterface +Summary: A library for accessing Java from Erlang +BuildRequires: java-devel +Requires: javapackages-tools %{name}-erts%{?_isa} = %{version}-%{release} +%description jinterface +Low level interface to Java. +%endif %{__with_java} + +%package kernel +Summary: Main erlang library +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description kernel +Main erlang library. +%if %{__with_wxwidgets} + +%package megaco +Summary: Megaco/H.248 support library +Requires: %{name}-asn1%{?_isa} = %{version}-%{release} +Requires: %{name}-debugger%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-et%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description megaco +Megaco/H.248 is a protocol for control of elements in a physically +decomposed multimedia gateway, enabling separation of call control +from media conversion. +%endif %{__with_wxwidgets} + +%package mnesia +Summary: A heavy duty real-time distributed database +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description mnesia +A heavy duty real-time distributed database. +%if %{__with_wxwidgets} + +%package observer +Summary: A set of tools for tracing and investigation of distributed systems +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-et%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +%description observer +A set of tools for tracing and investigation of distributed systems. +%endif %{__with_wxwidgets} + +%package odbc +Summary: A library for unixODBC support in Erlang +BuildRequires: unixODBC-devel +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description odbc +An interface to relational SQL-databases built on ODBC (Open Database +Connectivity). + +%package os_mon +Summary: A monitor which allows inspection of the underlying operating system +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-snmp%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description os_mon +A monitor which allows inspection of the underlying operating system. + +%package parsetools +Summary: A set of parsing and lexical analysis tools +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description parsetools +A set of parsing and lexical analysis tools. + +%package public_key +Summary: API to public key infrastructure +Requires: %{name}-asn1%{?_isa} = %{version}-%{release} +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description public_key +API to public key infrastructure. +%if %{__with_wxwidgets} + +%package reltool +Summary: A release management tool +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-tools%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +%description reltool +Reltool is a release management tool. It analyses a given +Erlang/OTP installation and determines various dependencies +between applications. The graphical frontend depicts the +dependencies and enables interactive customization of a +target system. The backend provides a batch interface +for generation of customized target systems. +%endif %{__with_wxwidgets} + +%package runtime_tools +Summary: A set of tools to include in a production system +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description runtime_tools +A set of tools to include in a production system. + +%package sasl +Summary: The System Architecture Support Libraries +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-tools%{?_isa} = %{version}-%{release} +%description sasl +The System Architecture Support Libraries is a set of tools for +release upgrades and alarm handling etc. + +%package snmp +Summary: Simple Network Management Protocol (SNMP) support +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description snmp +Simple Network Management Protocol (SNMP) support including a +MIB compiler and tools for creating SNMP agents. + +%if %{__with_sources} +%package src +Summary: Erlang sources +Requires: %{name}-asn1%{?_isa} = %{version}-%{release} +Requires: %{name}-common_test%{?_isa} = %{version}-%{release} +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-debugger%{?_isa} = %{version}-%{release} +Requires: %{name}-dialyzer%{?_isa} = %{version}-%{release} +Requires: %{name}-diameter%{?_isa} = %{version}-%{release} +Requires: %{name}-edoc%{?_isa} = %{version}-%{release} +Requires: %{name}-eldap%{?_isa} = %{version}-%{release} +Requires: %{name}-erl_docgen%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-et%{?_isa} = %{version}-%{release} +Requires: %{name}-eunit%{?_isa} = %{version}-%{release} +Requires: %{name}-ftp%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-megaco%{?_isa} = %{version}-%{release} +Requires: %{name}-mnesia%{?_isa} = %{version}-%{release} +Requires: %{name}-observer%{?_isa} = %{version}-%{release} +Requires: %{name}-odbc%{?_isa} = %{version}-%{release} +Requires: %{name}-os_mon%{?_isa} = %{version}-%{release} +Requires: %{name}-parsetools%{?_isa} = %{version}-%{release} +Requires: %{name}-public_key%{?_isa} = %{version}-%{release} +Requires: %{name}-reltool%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-sasl%{?_isa} = %{version}-%{release} +Requires: %{name}-snmp%{?_isa} = %{version}-%{release} +Requires: %{name}-ssh%{?_isa} = %{version}-%{release} +Requires: %{name}-ssl%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +Requires: %{name}-syntax_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-tftp%{?_isa} = %{version}-%{release} +Requires: %{name}-tools%{?_isa} = %{version}-%{release} +Requires: %{name}-wx%{?_isa} = %{version}-%{release} +Requires: %{name}-xmerl%{?_isa} = %{version}-%{release} + +%description src +Erlang sources. It may be useful as a reference for code completion tools in +various editors, for documentation or automatical-code generation purposes. +%endif # __with_sources + + +%package ssh +Summary: Secure Shell application with sftp and ssh support +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-public_key%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description ssh +Secure Shell application with sftp and ssh support. + +%package ssl +Summary: Secure Socket Layer support +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-public_key%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description ssl +Secure Socket Layer support. + +%package stdlib +Summary: The Erlang standard libraries +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-crypto%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +%description stdlib +The Erlang standard libraries. + +%package syntax_tools +Summary: A set of tools for dealing with erlang sources +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description syntax_tools +A utility used to handle abstract Erlang syntax trees, +reading source files differently, pretty-printing syntax trees. + +%package tftp +Summary: TFTP client +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description tftp +TFTP client. + +%package tools +Summary: A set of programming tools including a coverage analyzer etc +%if %{__with_emacs} +BuildRequires: emacs emacs-el +%endif %{__with_emacs} +Requires: %{name}-compiler%{?_isa} = %{version}-%{release} +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-inets%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-runtime_tools%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%if %{__with_emacs} +Requires: emacs-filesystem +Obsoletes: emacs-erlang +Obsoletes: emacs-erlang-el +%endif %{__with_emacs} +%description tools +A set of programming tools including a coverage analyzer etc. +%if %{__with_wxwidgets} + +%package wx +Summary: A library for wxWidgets support in Erlang +BuildRequires: wxGTK3-devel +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} mesa-libGL mesa-libGLU +%description wx +A Graphics System used to write platform independent user interfaces. +%endif %{__with_wxwidgets} + +%package xmerl +Summary: Provides support for XML 1.0 +Requires: %{name}-erts%{?_isa} = %{version}-%{release} +Requires: %{name}-kernel%{?_isa} = %{version}-%{release} +Requires: %{name}-stdlib%{?_isa} = %{version}-%{release} +%description xmerl +Provides support for XML 1.0. + +%prep +%autosetup -p1 -n otp-OTP-%{version} +./otp_build autoconf + +%build +%ifarch sparcv9 sparc64 +ERL_FLAGS="${RPM_OPT_FLAGS} -mcpu=ultrasparc -fno-strict-aliasing" +%else +ERL_FLAGS="${RPM_OPT_FLAGS} -fno-strict-aliasing" +%endif +CFLAGS="${ERL_FLAGS}" CXXFLAGS="${ERL_FLAGS}" %configure --enable-shared-zlib --enable-sctp --enable-systemd --disable-silent-rules \ + %{?with_fips:--enable-fips} \ +%if %{__with_java} + \ +%else + --without-jinterface \ +%endif %{__with_java} +%if %{__with_wxwidgets} + --with-wx-config=/usr/bin/wx-config +%else + --without-common_test \ + --without-debugger \ + --without-dialyzer \ + --without-et \ + --without-megaco \ + --without-observer \ + --without-reltool \ + --without-wx +%endif %{__with_wxwidgets} +# Remove pre-built BEAM files +make clean + +%if %{__with_emacs} +# GNU Emacs/XEmacs related stuff +erlang_tools_vsn="$(sed -n 's/TOOLS_VSN = //p' lib/tools/vsn.mk)" + +# GNU Emacs related stuff +cat > emacs-erlang-init.el << EOF +(setq load-path (cons "%{_emacs_sitelispdir}/erlang" load-path)) +(setq erlang-root-dir "%{_libdir}/erlang") +(setq exec-path (cons "%{_libdir}/erlang/bin" exec-path)) +(require 'erlang-start) +EOF +mkdir emacs-erlang +cp lib/tools/emacs/*.el emacs-erlang/ +pushd emacs-erlang +%{_emacs_bytecompile} *.el +popd +%endif %{__with_emacs} +make %{?_smp_mflags} +%if %{with doc} +%ifnarch ppc %{power64} +export BASE_OPTIONS=-Xmx1024m +%else +export BASE_OPTIONS=-Xmx1536m +%endif +make %{?_smp_mflags} docs +%endif + +%install +%if %{__with_emacs} +# GNU Emacs/XEmacs related stuff +erlang_tools_vsn="$(sed -n 's/TOOLS_VSN = //p' lib/tools/vsn.mk)" + +# GNU Emacs related stuff +install -m 0755 -d "$RPM_BUILD_ROOT%{_emacs_sitestartdir}" +install -m 0755 -d "$RPM_BUILD_ROOT%{_emacs_sitelispdir}/erlang" +install -m 0644 emacs-erlang-init.el "$RPM_BUILD_ROOT%{_emacs_sitestartdir}/erlang-init.el" +for f in lib/tools/emacs/{README,*.el}; do + b="$(basename "$f")"; + ln -s "%{_libdir}/erlang/lib/tools-${erlang_tools_vsn}/emacs/$b" \ + "$RPM_BUILD_ROOT%{_emacs_sitelispdir}/erlang/" +done +install -m 0644 emacs-erlang/*.elc "$RPM_BUILD_ROOT%{_emacs_sitelispdir}/erlang/" +%endif %{__with_emacs} +make DESTDIR=$RPM_BUILD_ROOT install +%if %{with doc} +env ERL_LIBS="$RPM_BUILD_ROOT%{_libdir}/erlang/lib" make DESTDIR=$RPM_BUILD_ROOT install-docs +%endif + +# Do not install info files - they are almost empty and useless +find $RPM_BUILD_ROOT%{_libdir}/erlang -type f -name info -exec rm -f {} \; +%if %{__with_examples} +# fix 0775 permission on some directories +find $RPM_BUILD_ROOT%{_libdir}/erlang/lib/ssl-*/examples/ -type d -perm 0775 -print -exec chmod 755 {} \; +find $RPM_BUILD_ROOT%{_libdir}/erlang/lib/kernel-*/examples/uds_dist -type d -perm 0775 -print -exec chmod 755 {} \; +%else +# Remove all examples +find $RPM_BUILD_ROOT%{_libdir}/erlang/lib/ -mindepth 1 -maxdepth 2 -type d -name examples -exec rm -rf {} \; +%endif %{__with_examples} +chmod 0755 $RPM_BUILD_ROOT%{_libdir}/erlang/bin + +# Relocate doc-files into the proper directory +%if %{with doc} +mkdir -p $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version}/lib +pushd . +cd $RPM_BUILD_ROOT%{_libdir}/erlang +mv -v doc $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} +for i in erts-* ; do mv -v $i/doc $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version}/$i ; done +cd $RPM_BUILD_ROOT%{_libdir}/erlang/lib +for i in * ; do mv -v $i/doc $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version}/lib/$i || true ; done +popd +cp -av AUTHORS LICENSE.txt README.md $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} +mv -v $RPM_BUILD_ROOT%{_libdir}/erlang/PR.template $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} +mv -v $RPM_BUILD_ROOT%{_libdir}/erlang/COPYRIGHT $RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} +# We'll package it by marking it explicitly as doc - see below +rm -f $RPM_BUILD_ROOT%{_libdir}/erlang/README.md +%endif + +# Win32-specific man-pages +rm -f $RPM_BUILD_ROOT%{_libdir}/erlang/man/man1/erlsrv.* +rm -f $RPM_BUILD_ROOT%{_libdir}/erlang/man/man1/werl.* +rm -f $RPM_BUILD_ROOT%{_libdir}/erlang/man/man3/win32reg.* + +# remove empty directory +rm -r $RPM_BUILD_ROOT%{_libdir}/erlang/erts-*/man +%if %{with doc} +# Move man-pages to a system-wide directory - in the same way as Debian did +# Erlang files from man 3 have too generic names +for manpage in $RPM_BUILD_ROOT%{_libdir}/erlang/man/man3/* +do + mv ${manpage} ${manpage}erl +done +mkdir -p $RPM_BUILD_ROOT%{_mandir}/ +mv $RPM_BUILD_ROOT%{_libdir}/erlang/man/* $RPM_BUILD_ROOT%{_mandir}/ +%endif + +# remove outdated script +rm -f $RPM_BUILD_ROOT%{_libdir}/erlang/Install + +# Replace identical executables with symlinks +for exe in $RPM_BUILD_ROOT%{_libdir}/erlang/erts-*/bin/* +do + base="$(basename "$exe")" + next="$RPM_BUILD_ROOT%{_libdir}/erlang/bin/${base}" + rel="$(echo "$exe" | sed "s,^$RPM_BUILD_ROOT%{_libdir}/erlang/,../,")" + if cmp "$exe" "$next"; then + ln -sf "$rel" "$next" + fi +done +for exe in $RPM_BUILD_ROOT%{_libdir}/erlang/bin/* +do + base="$(basename "$exe")" + next="$RPM_BUILD_ROOT%{_bindir}/${base}" + rel="$(echo "$exe" | sed "s,^$RPM_BUILD_ROOT,,")" + if cmp "$exe" "$next"; then + ln -sf "$rel" "$next" + fi +done +%if %{__with_java} +# symlink *.jar files to appropriate places for subpackages +install -m 0755 -d "$RPM_BUILD_ROOT%{_javadir}/%{name}" + +# erlang-jinterface +jinterface_lib_dir="$(ls -d1 $RPM_BUILD_ROOT%{_libdir}/erlang/lib/jinterface-*/ | sed "s,^$RPM_BUILD_ROOT,,")" +test -d "$RPM_BUILD_ROOT$jinterface_lib_dir" +ln -s "${jinterface_lib_dir}priv/OtpErlang.jar" "$RPM_BUILD_ROOT%{_javadir}/%{name}/" +%endif %{__with_java} +install -D -p -m 0644 %{SOURCE1} %{buildroot}%{_unitdir}/epmd.service +install -D -p -m 0644 %{SOURCE2} %{buildroot}%{_unitdir}/epmd.socket +install -D -p -m 0644 %{SOURCE3} %{buildroot}%{_unitdir}/epmd@.service +install -D -p -m 0644 %{SOURCE4} %{buildroot}%{_unitdir}/epmd@.socket +%if %{__with_wxwidgets} +echo "No need to fix additional scripts" +%else +# FIXME workaround for broken Erlang install procedure +echo "Removing scripts which won't work w/o wxWidgets anyway" +for exe in ct_run dialyzer typer +do + rm -f $RPM_BUILD_ROOT/%{_bindir}/${exe} + rm -f $RPM_BUILD_ROOT/%{_libdir}/erlang/bin/${exe} + rm -f $RPM_BUILD_ROOT/%{_libdir}/erlang/erts-*/bin/${exe} +done +%endif %{__with_wxwidgets} +# Provide a place for noarch libs to live. +install -d -p -m 0755 %{buildroot}%{_datadir}/erlang/ +install -d -p -m 0755 %{buildroot}%{_datadir}/erlang/lib + +%check +TARGET="$(make target_configured)" +ERL_TOP="$(pwd)" +ERL_TOP=${ERL_TOP} make TARGET=${TARGET} release_tests + +%pre erts +getent group epmd >/dev/null || groupadd -r epmd +getent passwd epmd >/dev/null || \ +useradd -r -g epmd -d /dev/null -s /sbin/nologin \ +-c "Erlang Port Mapper Daemon" epmd 2>/dev/null || : + +%files +%if %{with doc} +%dir %{_docdir}/%{name}-%{version}/ +%doc %{_docdir}/%{name}-%{version}/AUTHORS +%doc %{_docdir}/%{name}-%{version}/COPYRIGHT +%doc %{_docdir}/%{name}-%{version}/LICENSE.txt +%doc %{_docdir}/%{name}-%{version}/PR.template +%doc %{_docdir}/%{name}-%{version}/README.md +%endif + +%files asn1 +%dir %{_libdir}/erlang/lib/asn1-*/ +%{_libdir}/erlang/lib/asn1-*/ebin +%{_libdir}/erlang/lib/asn1-*/priv +%{_libdir}/erlang/lib/asn1-*/src +%if %{with doc} +%{_mandir}/man3/asn1ct.* +%endif +%if %{__with_wxwidgets} + +%files common_test +%{_bindir}/ct_run +%{_libdir}/erlang/bin/ct_run +%{_libdir}/erlang/erts-*/bin/ct_run +%{_libdir}/erlang/lib/common_test-*/ +%if %{with doc} +%{_mandir}/man1/ct_run.* +%{_mandir}/man3/ct.* +%{_mandir}/man3/ct_cover.* +%{_mandir}/man3/ct_ftp.* +%{_mandir}/man3/ct_hooks.* +%{_mandir}/man3/ct_master.* +%{_mandir}/man3/ct_netconfc.* +%{_mandir}/man3/ct_property_test.* +%{_mandir}/man3/ct_rpc.* +%{_mandir}/man3/ct_slave.* +%{_mandir}/man3/ct_snmp.* +%{_mandir}/man3/ct_ssh.* +%{_mandir}/man3/ct_suite.* +%{_mandir}/man3/ct_telnet.* +%{_mandir}/man3/ct_testspec.* +%{_mandir}/man3/unix_telnet.* +%{_mandir}/man6/common_test.* +%endif +%endif %{__with_wxwidgets} + +%files compiler +%{_libdir}/erlang/lib/compiler-*/ +%if %{with doc} +%{_mandir}/man3/cerl.* +%{_mandir}/man3/cerl_clauses.* +%{_mandir}/man3/cerl_trees.* +%{_mandir}/man3/compile.* +%endif + +%files crypto +%{_libdir}/erlang/lib/crypto-*/ +%if %{with doc} +%{_mandir}/man3/crypto.* +%{_mandir}/man6/crypto.* +%endif +%if %{__with_wxwidgets} + +%files debugger +%{_libdir}/erlang/lib/debugger-*/ +%if %{with doc} +%{_mandir}/man3/debugger.* +%{_mandir}/man3/i.* +%{_mandir}/man3/int.* +%endif +%endif %{__with_wxwidgets} +%if %{__with_wxwidgets} + +%files dialyzer +%{_bindir}/dialyzer +%{_bindir}/typer +%{_libdir}/erlang/bin/dialyzer +%{_libdir}/erlang/bin/typer +%{_libdir}/erlang/erts-*/bin/dialyzer +%{_libdir}/erlang/erts-*/bin/typer +%{_libdir}/erlang/lib/dialyzer-*/ +%if %{with doc} +%{_mandir}/man3/dialyzer.* +%{_mandir}/man3/typer.* +%endif +%endif %{__with_wxwidgets} + +%files diameter +%dir %{_libdir}/erlang/lib/diameter-*/ +%{_libdir}/erlang/lib/diameter-*/bin +%{_libdir}/erlang/lib/diameter-*/ebin +%{_libdir}/erlang/lib/diameter-*/include +%{_libdir}/erlang/lib/diameter-*/src +%if %{with doc} +%{_mandir}/man1/diameterc.* +%{_mandir}/man3/diameter.* +%{_mandir}/man3/diameter_app.* +%{_mandir}/man3/diameter_codec.* +%{_mandir}/man3/diameter_make.* +%{_mandir}/man3/diameter_sctp.* +%{_mandir}/man3/diameter_tcp.* +%{_mandir}/man3/diameter_transport.* +%{_mandir}/man4/diameter_dict.* +%endif +%if %{with doc} + +%files doc +%doc %{_docdir}/%{name}-%{version}/doc +%doc %{_docdir}/%{name}-%{version}/erts-*/ +%doc %{_docdir}/%{name}-%{version}/lib/ +%endif + +%files edoc +%{_libdir}/erlang/lib/edoc-*/ +%if %{with doc} +%{_mandir}/man1/edoc.* +%{_mandir}/man3/edoc.* +%{_mandir}/man3/edoc_doclet.* +%{_mandir}/man3/edoc_doclet_chunks.* +%{_mandir}/man3/edoc_extract.* +%{_mandir}/man3/edoc_layout.* +%{_mandir}/man3/edoc_layout_chunks.* +%{_mandir}/man3/edoc_lib.* +%{_mandir}/man3/edoc_run.* +%endif + +%files eldap +%{_libdir}/erlang/lib/eldap-*/ +%if %{with doc} +%{_mandir}/man3/eldap.* +%endif + +%files erl_docgen +%{_libdir}/erlang/lib/erl_docgen-*/ +%if %{with doc} +%{_mandir}/man6/erl_docgen.* +%endif + +%files erl_interface +%{_libdir}/erlang/lib/erl_interface-*/ +%{_libdir}/erlang/bin/erl_call +%{_libdir}/erlang/erts-*/bin/erl_call +%if %{with doc} +%{_mandir}/man1/erl_call.* +%{_mandir}/man3/ei.* +%{_mandir}/man3/ei_connect.* +%{_mandir}/man3/erl_connect.* +%{_mandir}/man3/erl_error.* +%{_mandir}/man3/erl_eterm.* +%{_mandir}/man3/erl_format.* +%{_mandir}/man3/erl_global.* +%{_mandir}/man3/erl_malloc.* +%{_mandir}/man3/erl_marshal.* +%{_mandir}/man3/registry.* +%endif + +%files erts +%dir %{_datadir}/erlang/ +%dir %{_datadir}/erlang/lib/ +%dir %{_libdir}/erlang/ +%dir %{_libdir}/erlang/bin/ +%dir %{_libdir}/erlang/lib/ +%dir %{_libdir}/erlang/releases/ +%{_bindir}/epmd +%{_bindir}/erl +%{_bindir}/erlc +%{_bindir}/escript +%{_bindir}/run_erl +%{_bindir}/to_erl +%{_libdir}/erlang/bin/epmd +%{_libdir}/erlang/bin/erl +%{_libdir}/erlang/bin/erlc +%{_libdir}/erlang/bin/escript +%{_libdir}/erlang/bin/no_dot_erlang.boot +%{_libdir}/erlang/bin/run_erl +%{_libdir}/erlang/bin/start +%{_libdir}/erlang/bin/start.boot +%{_libdir}/erlang/bin/start.script +%{_libdir}/erlang/bin/start_clean.boot +%{_libdir}/erlang/bin/start_erl +%{_libdir}/erlang/bin/start_sasl.boot +%{_libdir}/erlang/bin/to_erl +%dir %{_libdir}/erlang/erts-*/ +%dir %{_libdir}/erlang/erts-*/bin/ +%{_libdir}/erlang/erts-*/bin/beam.smp +%{_libdir}/erlang/erts-*/bin/dyn_erl +%{_libdir}/erlang/erts-*/bin/epmd +%{_libdir}/erlang/erts-*/bin/erl +%{_libdir}/erlang/erts-*/bin/erl.src +%{_libdir}/erlang/erts-*/bin/erl_child_setup +%{_libdir}/erlang/erts-*/bin/erlc +%{_libdir}/erlang/erts-*/bin/erlexec +%{_libdir}/erlang/erts-*/bin/escript +%{_libdir}/erlang/erts-*/bin/heart +%{_libdir}/erlang/erts-*/bin/inet_gethost +%{_libdir}/erlang/erts-*/bin/run_erl +%{_libdir}/erlang/erts-*/bin/start +%{_libdir}/erlang/erts-*/bin/start.src +%{_libdir}/erlang/erts-*/bin/start_erl.src +%{_libdir}/erlang/erts-*/bin/to_erl +%{_libdir}/erlang/erts-*/bin/yielding_c_fun +%{_libdir}/erlang/erts-*/include +%{_libdir}/erlang/erts-*/lib/ +%{_libdir}/erlang/erts-*/src/ +%{_libdir}/erlang/lib/erts-*/ +%if %{with doc} +%{_mandir}/man1/epmd.* +%{_mandir}/man1/erl.* +%{_mandir}/man1/erlc.* +%{_mandir}/man1/escript.* +%{_mandir}/man1/run_erl.* +%{_mandir}/man1/start.* +%{_mandir}/man1/start_erl.* +%{_mandir}/man3/atomics.* +%{_mandir}/man3/counters.* +%{_mandir}/man3/driver_entry.* +%{_mandir}/man3/erl_driver.* +%{_mandir}/man3/erl_nif.* +%{_mandir}/man3/erl_prim_loader.* +%{_mandir}/man3/erl_tracer.* +%{_mandir}/man3/erlang.* +%{_mandir}/man3/erts_alloc.* +%{_mandir}/man3/init.* +%{_mandir}/man3/net.* +%{_mandir}/man3/persistent_term.* +%{_mandir}/man3/scheduler.* +%{_mandir}/man3/socket.* +%{_mandir}/man3/zlib.* +%endif +%{_libdir}/erlang/releases/* +%{_libdir}/erlang/usr/ +%{_unitdir}/epmd.service +%{_unitdir}/epmd.socket +%{_unitdir}/epmd@.service +%{_unitdir}/epmd@.socket +%if %{__with_wxwidgets} + +%files et +%dir %{_libdir}/erlang/lib/et-*/ +%{_libdir}/erlang/lib/et-*/ebin +%{_libdir}/erlang/lib/et-*/include +%{_libdir}/erlang/lib/et-*/src +%if %{with doc} +%{_mandir}/man3/et.* +%{_mandir}/man3/et_collector.* +%{_mandir}/man3/et_selector.* +%{_mandir}/man3/et_viewer.* +%endif +%endif %{__with_wxwidgets} + +%files eunit +%dir %{_libdir}/erlang/lib/eunit-*/ +%{_libdir}/erlang/lib/eunit-*/ebin +%{_libdir}/erlang/lib/eunit-*/include +%{_libdir}/erlang/lib/eunit-*/src +%if %{with doc} +%{_mandir}/man3/eunit.* +%{_mandir}/man3/eunit_surefire.* +%endif +%if %{__with_examples} + +%files examples +%{_libdir}/erlang/lib/asn1-*/examples/ +%{_libdir}/erlang/lib/diameter-*/examples/ +%if %{__with_wxwidgets} +%{_libdir}/erlang/lib/et-*/examples/ +%endif %{__with_wxwidgets} +%{_libdir}/erlang/lib/eunit-*/examples/ +%{_libdir}/erlang/lib/inets-*/examples/ +%{_libdir}/erlang/lib/kernel-*/examples/ +%{_libdir}/erlang/lib/megaco-*/examples/ +%{_libdir}/erlang/lib/mnesia-*/examples/ +%if %{__with_wxwidgets} +%{_libdir}/erlang/lib/observer-*/examples/ +%endif %{__with_wxwidgets} +%if %{__with_wxwidgets} +%{_libdir}/erlang/lib/reltool-*/examples/ +%endif %{__with_wxwidgets} +%{_libdir}/erlang/lib/runtime_tools-*/examples/ +%{_libdir}/erlang/lib/sasl-*/examples/ +%{_libdir}/erlang/lib/snmp-*/examples/ +%{_libdir}/erlang/lib/ssl-*/examples/ +%{_libdir}/erlang/lib/stdlib-*/examples/ +%{_libdir}/erlang/lib/syntax_tools-*/examples/ +%{_libdir}/erlang/lib/tools-*/examples/ +%if %{__with_wxwidgets} +%{_libdir}/erlang/lib/wx-*/examples/ +%endif %{__with_wxwidgets} +%endif %{__with_examples} + +%files ftp +%dir %{_libdir}/erlang/lib/ftp-*/ +%{_libdir}/erlang/lib/ftp-*/ebin +%{_libdir}/erlang/lib/ftp-*/src +%if %{with doc} +%{_mandir}/man3/ftp.* +%endif + +%files inets +%dir %{_libdir}/erlang/lib/inets-*/ +%{_libdir}/erlang/lib/inets-*/ebin +%{_libdir}/erlang/lib/inets-*/include +%{_libdir}/erlang/lib/inets-*/priv +%{_libdir}/erlang/lib/inets-*/src +%if %{with doc} +%{_mandir}/man3/ftp.* +%{_mandir}/man3/http_uri.* +%{_mandir}/man3/httpc.* +%{_mandir}/man3/httpd.* +%{_mandir}/man3/httpd_custom_api.* +%{_mandir}/man3/httpd_socket.* +%{_mandir}/man3/httpd_util.* +%{_mandir}/man3/inets.* +%{_mandir}/man3/mod_alias.* +%{_mandir}/man3/mod_auth.* +%{_mandir}/man3/mod_esi.* +%{_mandir}/man3/mod_security.* +%{_mandir}/man3/tftp.* +%endif +%if %{__with_java} + +%files jinterface +%dir %{_javadir}/%{name}/ +%{_javadir}/%{name}/OtpErlang.jar +%{_libdir}/erlang/lib/jinterface-*/ +%endif %{__with_java} + +%files kernel +%dir %{_libdir}/erlang/lib/kernel-*/ +%{_libdir}/erlang/lib/kernel-*/ebin +%{_libdir}/erlang/lib/kernel-*/include +%{_libdir}/erlang/lib/kernel-*/src +%if %{with doc} +%{_mandir}/man3/application.* +%{_mandir}/man3/auth.* +%{_mandir}/man3/code.* +%{_mandir}/man3/disk_log.* +%{_mandir}/man3/erl_boot_server.* +%{_mandir}/man3/erl_ddll.* +%{_mandir}/man3/erl_epmd.* +%{_mandir}/man3/erl_prim_loader_stub.* +%{_mandir}/man3/erlang_stub.* +%{_mandir}/man3/erpc.* +%{_mandir}/man3/error_handler.* +%{_mandir}/man3/error_logger.* +%{_mandir}/man3/file.* +%{_mandir}/man3/gen_sctp.* +%{_mandir}/man3/gen_tcp.* +%{_mandir}/man3/gen_udp.* +%{_mandir}/man3/global.* +%{_mandir}/man3/global_group.* +%{_mandir}/man3/heart.* +%{_mandir}/man3/inet.* +%{_mandir}/man3/inet_res.* +%{_mandir}/man3/init_stub.* +%{_mandir}/man3/logger.* +%{_mandir}/man3/logger_disk_log_h.* +%{_mandir}/man3/logger_filters.* +%{_mandir}/man3/logger_formatter.* +%{_mandir}/man3/logger_std_h.* +%{_mandir}/man3/net_adm.* +%{_mandir}/man3/net_kernel.* +%{_mandir}/man3/os.* +%{_mandir}/man3/pg.* +%{_mandir}/man3/rpc.* +%{_mandir}/man3/seq_trace.* +%{_mandir}/man3/user.* +%{_mandir}/man3/wrap_log_reader.* +%{_mandir}/man3/zlib_stub.* +%{_mandir}/man4/app.* +%{_mandir}/man4/config.* +%{_mandir}/man6/kernel.* +%endif +%if %{__with_wxwidgets} + +%files megaco +%dir %{_libdir}/erlang/lib/megaco-*/ +%{_libdir}/erlang/lib/megaco-*/ebin +%{_libdir}/erlang/lib/megaco-*/include +%{_libdir}/erlang/lib/megaco-*/priv +%{_libdir}/erlang/lib/megaco-*/src +%if %{with doc} +%{_mandir}/man3/megaco.* +%{_mandir}/man3/megaco_codec_meas.* +%{_mandir}/man3/megaco_codec_mstone1.* +%{_mandir}/man3/megaco_codec_mstone2.* +%{_mandir}/man3/megaco_codec_transform.* +%{_mandir}/man3/megaco_edist_compress.* +%{_mandir}/man3/megaco_encoder.* +%{_mandir}/man3/megaco_flex_scanner.* +%{_mandir}/man3/megaco_tcp.* +%{_mandir}/man3/megaco_transport.* +%{_mandir}/man3/megaco_udp.* +%{_mandir}/man3/megaco_user.* +%endif +%endif %{__with_wxwidgets} + +%files mnesia +%dir %{_libdir}/erlang/lib/mnesia-*/ +%{_libdir}/erlang/lib/mnesia-*/ebin +%{_libdir}/erlang/lib/mnesia-*/src +%if %{with doc} +%{_mandir}/man3/mnesia.* +%{_mandir}/man3/mnesia_frag_hash.* +%{_mandir}/man3/mnesia_registry.* +%endif +%if %{__with_wxwidgets} + +%files observer +%dir %{_libdir}/erlang/lib/observer-*/ +%{_libdir}/erlang/lib/observer-*/ebin/ +%{_libdir}/erlang/lib/observer-*/include/ +%{_libdir}/erlang/lib/observer-*/priv/ +%{_libdir}/erlang/lib/observer-*/src/ +%if %{with doc} +%{_mandir}/man1/cdv.* +%{_mandir}/man3/crashdump.* +%{_mandir}/man3/etop.* +%{_mandir}/man3/observer.* +%{_mandir}/man3/ttb.* +%{_mandir}/man6/observer.* +%endif +%endif %{__with_wxwidgets} + +%files odbc +%{_libdir}/erlang/lib/odbc-*/ +%if %{with doc} +%{_mandir}/man3/odbc.* +%endif + +%files os_mon +%{_libdir}/erlang/lib/os_mon-*/ +%if %{with doc} +%{_mandir}/man3/cpu_sup.* +%{_mandir}/man3/disksup.* +%{_mandir}/man3/memsup.* +%{_mandir}/man3/os_sup.* +%{_mandir}/man6/os_mon.* +%endif + +%files parsetools +%{_libdir}/erlang/lib/parsetools-*/ +%if %{with doc} +%{_mandir}/man3/leex.* +%{_mandir}/man3/yecc.* +%endif + +%files public_key +%{_libdir}/erlang/lib/public_key-*/ +%if %{with doc} +%{_mandir}/man3/public_key.* +%{_mandir}/man6/public_key.* +%endif +%if %{__with_wxwidgets} + +%files reltool +%dir %{_libdir}/erlang/lib/reltool-*/ +%{_libdir}/erlang/lib/reltool-*/ebin +%{_libdir}/erlang/lib/reltool-*/src +%if %{with doc} +%{_mandir}/man3/reltool.* +%endif +%endif %{__with_wxwidgets} + +%files runtime_tools +%dir %{_libdir}/erlang/lib/runtime_tools-*/ +%{_libdir}/erlang/lib/runtime_tools-*/ebin/ +%{_libdir}/erlang/lib/runtime_tools-*/include/ +%{_libdir}/erlang/lib/runtime_tools-*/priv/ +%if %{with doc} +%{_mandir}/man3/dbg.* +%{_mandir}/man3/dyntrace.* +%{_mandir}/man3/erts_alloc_config.* +%{_mandir}/man3/msacc.* +%{_mandir}/man3/system_information.* +%{_mandir}/man6/runtime_tools.* +%endif + +%files sasl +%dir %{_libdir}/erlang/lib/sasl-*/ +%{_libdir}/erlang/lib/sasl-*/ebin +%{_libdir}/erlang/lib/sasl-*/src +%if %{with doc} +%{_mandir}/man3/alarm_handler.* +%{_mandir}/man3/rb.* +%{_mandir}/man3/release_handler.* +%{_mandir}/man3/systools.* +%{_mandir}/man4/appup.* +%{_mandir}/man4/rel.* +%{_mandir}/man4/relup.* +%{_mandir}/man4/script.* +%{_mandir}/man6/sasl.* +%endif + +%files snmp +%dir %{_libdir}/erlang/lib/snmp-*/ +%{_libdir}/erlang/lib/snmp-*/bin +%{_libdir}/erlang/lib/snmp-*/ebin +%{_libdir}/erlang/lib/snmp-*/include +%{_libdir}/erlang/lib/snmp-*/mibs +%{_libdir}/erlang/lib/snmp-*/priv +%{_libdir}/erlang/lib/snmp-*/src +%if %{with doc} +%{_mandir}/man1/snmpc.* +%{_mandir}/man3/snmp.* +%{_mandir}/man3/snmpa.* +%{_mandir}/man3/snmpa_conf.* +%{_mandir}/man3/snmpa_discovery_handler.* +%{_mandir}/man3/snmpa_error.* +%{_mandir}/man3/snmpa_error_io.* +%{_mandir}/man3/snmpa_error_logger.* +%{_mandir}/man3/snmpa_error_report.* +%{_mandir}/man3/snmpa_local_db.* +%{_mandir}/man3/snmpa_mib_data.* +%{_mandir}/man3/snmpa_mib_storage.* +%{_mandir}/man3/snmpa_mpd.* +%{_mandir}/man3/snmpa_network_interface.* +%{_mandir}/man3/snmpa_network_interface_filter.* +%{_mandir}/man3/snmpa_notification_delivery_info_receiver.* +%{_mandir}/man3/snmpa_notification_filter.* +%{_mandir}/man3/snmpa_supervisor.* +%{_mandir}/man3/snmpc.* +%{_mandir}/man3/snmp_community_mib.* +%{_mandir}/man3/snmp_framework_mib.* +%{_mandir}/man3/snmp_generic.* +%{_mandir}/man3/snmp_index.* +%{_mandir}/man3/snmpm.* +%{_mandir}/man3/snmpm_conf.* +%{_mandir}/man3/snmpm_mpd.* +%{_mandir}/man3/snmpm_network_interface.* +%{_mandir}/man3/snmpm_network_interface_filter.* +%{_mandir}/man3/snmpm_user.* +%{_mandir}/man3/snmp_notification_mib.* +%{_mandir}/man3/snmp_pdus.* +%{_mandir}/man3/snmp_standard_mib.* +%{_mandir}/man3/snmp_target_mib.* +%{_mandir}/man3/snmp_user_based_sm_mib.* +%{_mandir}/man3/snmp_view_based_acm_mib.* +%{_mandir}/man6/snmp.* +%{_mandir}/man7/INET-ADDRESS-MIB.* +%{_mandir}/man7/OTP-SNMPEA-MIB.* +%{_mandir}/man7/RFC1213-MIB.* +%{_mandir}/man7/SNMP-COMMUNITY-MIB.* +%{_mandir}/man7/SNMP-FRAMEWORK-MIB.* +%{_mandir}/man7/SNMP-MPD-MIB.* +%{_mandir}/man7/SNMP-NOTIFICATION-MIB.* +%{_mandir}/man7/SNMP-TARGET-MIB.* +%{_mandir}/man7/SNMP-USER-BASED-SM-MIB.* +%{_mandir}/man7/SNMP-USM-AES-MIB.* +%{_mandir}/man7/SNMPv2-MIB.* +%{_mandir}/man7/SNMPv2-TM.* +%{_mandir}/man7/SNMP-VIEW-BASED-ACM-MIB.* +%{_mandir}/man7/STANDARD-MIB.* +%{_mandir}/man7/TRANSPORT-ADDRESS-MIB.* +%endif + +%if %{__with_sources} +%files src +%dir %{_libdir}/erlang/lib/*/src/ +%{_libdir}/erlang/lib/*/src/*.erl +%{_libdir}/erlang/lib/*/src/*.yrl +%endif + +%files ssh +%dir %{_libdir}/erlang/lib/ssh-*/ +%{_libdir}/erlang/lib/ssh-*/ebin +%{_libdir}/erlang/lib/ssh-*/include +%{_libdir}/erlang/lib/ssh-*/src +%if %{with doc} +%{_mandir}/man3/ssh.* +%{_mandir}/man3/ssh_agent.* +%{_mandir}/man3/ssh_client_channel.* +%{_mandir}/man3/ssh_client_key_api.* +%{_mandir}/man3/ssh_connection.* +%{_mandir}/man3/ssh_file.* +%{_mandir}/man3/ssh_server_channel.* +%{_mandir}/man3/ssh_server_key_api.* +%{_mandir}/man3/ssh_sftp.* +%{_mandir}/man3/ssh_sftpd.* +%{_mandir}/man6/SSH.* +%endif + +%files ssl +%dir %{_libdir}/erlang/lib/ssl-*/ +%{_libdir}/erlang/lib/ssl-*/ebin +%{_libdir}/erlang/lib/ssl-*/src +%if %{with doc} +%{_mandir}/man3/ssl.* +%{_mandir}/man3/ssl_crl_cache.* +%{_mandir}/man3/ssl_crl_cache_api.* +%{_mandir}/man3/ssl_session_cache_api.* +%{_mandir}/man6/ssl.* +%endif + +%files stdlib +%dir %{_libdir}/erlang/lib/stdlib-*/ +%{_libdir}/erlang/lib/stdlib-*/ebin +%{_libdir}/erlang/lib/stdlib-*/include +%{_libdir}/erlang/lib/stdlib-*/src +%if %{with doc} +%{_mandir}/man3/array.* +%{_mandir}/man3/base64.* +%{_mandir}/man3/beam_lib.* +%{_mandir}/man3/binary.* +%{_mandir}/man3/c.* +%{_mandir}/man3/calendar.* +%{_mandir}/man3/dets.* +%{_mandir}/man3/dict.* +%{_mandir}/man3/digraph.* +%{_mandir}/man3/digraph_utils.* +%{_mandir}/man3/epp.* +%{_mandir}/man3/erl_anno.* +%{_mandir}/man3/erl_error.* +%{_mandir}/man3/erl_eval.* +%{_mandir}/man3/erl_expand_records.* +%{_mandir}/man3/erl_features.* +%{_mandir}/man3/erl_id_trans.* +%{_mandir}/man3/erl_internal.* +%{_mandir}/man3/erl_lint.* +%{_mandir}/man3/erl_parse.* +%{_mandir}/man3/erl_pp.* +%{_mandir}/man3/erl_scan.* +%{_mandir}/man3/erl_tar.* +%{_mandir}/man3/ets.* +%{_mandir}/man3/file_sorter.* +%{_mandir}/man3/filelib.* +%{_mandir}/man3/filename.* +%{_mandir}/man3/gb_sets.* +%{_mandir}/man3/gb_trees.* +%{_mandir}/man3/gen_event.* +%{_mandir}/man3/gen_fsm.* +%{_mandir}/man3/gen_server.* +%{_mandir}/man3/gen_statem.* +%{_mandir}/man3/io.* +%{_mandir}/man3/io_lib.* +%{_mandir}/man3/lists.* +%{_mandir}/man3/log_mf_h.* +%{_mandir}/man3/maps.* +%{_mandir}/man3/math.* +%{_mandir}/man3/ms_transform.* +%{_mandir}/man3/orddict.* +%{_mandir}/man3/ordsets.* +%{_mandir}/man3/peer.* +%{_mandir}/man3/pool.* +%{_mandir}/man3/proc_lib.* +%{_mandir}/man3/proplists.* +%{_mandir}/man3/qlc.* +%{_mandir}/man3/queue.* +%{_mandir}/man3/rand.* +%{_mandir}/man3/random.* +%{_mandir}/man3/re.* +%{_mandir}/man3/sets.* +%{_mandir}/man3/shell.* +%{_mandir}/man3/shell_default.* +%{_mandir}/man3/shell_docs.* +%{_mandir}/man3/slave.* +%{_mandir}/man3/sofs.* +%{_mandir}/man3/string.* +%{_mandir}/man3/supervisor.* +%{_mandir}/man3/supervisor_bridge.* +%{_mandir}/man3/sys.* +%{_mandir}/man3/timer.* +%{_mandir}/man3/unicode.* +%{_mandir}/man3/uri_string.* +%{_mandir}/man3/zip.* +%{_mandir}/man6/stdlib.* +%endif + +%files syntax_tools +%dir %{_libdir}/erlang/lib/syntax_tools-*/ +%{_libdir}/erlang/lib/syntax_tools-*/ebin +%{_libdir}/erlang/lib/syntax_tools-*/include +%if %{with doc} +%{_mandir}/man3/epp_dodger.* +%{_mandir}/man3/erl_comment_scan.* +%{_mandir}/man3/erl_prettypr.* +%{_mandir}/man3/erl_recomment.* +%{_mandir}/man3/erl_syntax.* +%{_mandir}/man3/erl_syntax_lib.* +%{_mandir}/man3/merl.* +%{_mandir}/man3/merl_transform.* +%{_mandir}/man3/prettypr.* +%endif + +%files tftp +%dir %{_libdir}/erlang/lib/tftp-*/ +%{_libdir}/erlang/lib/tftp-*/ebin +%{_libdir}/erlang/lib/tftp-*/src +%if %{with doc} +%{_mandir}/man3/tftp.* +%endif + +%files tools +%dir %{_libdir}/erlang/lib/tools-*/ +%{_libdir}/erlang/lib/tools-*/ebin +%{_libdir}/erlang/lib/tools-*/emacs +%{_libdir}/erlang/lib/tools-*/src +%{_libdir}/erlang/lib/tools-*/priv +%if %{with doc} +%{_mandir}/man3/cover.* +%{_mandir}/man3/cprof.* +%{_mandir}/man3/eprof.* +%{_mandir}/man3/erlang_mode.* +%{_mandir}/man3/fprof.* +%{_mandir}/man3/instrument.* +%{_mandir}/man3/lcnt.* +%{_mandir}/man3/make.* +%{_mandir}/man3/tags.* +%{_mandir}/man3/xref.* +%endif +%if %{__with_emacs} +%dir %{_emacs_sitelispdir}/erlang +%doc %{_emacs_sitelispdir}/erlang/README +%{_emacs_sitelispdir}/erlang/*.el +%{_emacs_sitelispdir}/erlang/*.elc +%{_emacs_sitestartdir}/erlang-init.el +%endif %{__with_emacs} +%if %{__with_wxwidgets} + +%files wx +%dir %{_libdir}/erlang/lib/wx-*/ +%{_libdir}/erlang/lib/wx-*/ebin +%{_libdir}/erlang/lib/wx-*/include +%{_libdir}/erlang/lib/wx-*/priv +%{_libdir}/erlang/lib/wx-*/src +%if %{with doc} +%{_mandir}/man3/gl.* +%{_mandir}/man3/glu.* +%{_mandir}/man3/wx.* +%{_mandir}/man3/wxAcceleratorEntry.* +%{_mandir}/man3/wxAcceleratorTable.* +%{_mandir}/man3/wxActivateEvent.* +%{_mandir}/man3/wxArtProvider.* +%{_mandir}/man3/wxAuiDockArt.* +%{_mandir}/man3/wxAuiManager.* +%{_mandir}/man3/wxAuiManagerEvent.* +%{_mandir}/man3/wxAuiNotebook.* +%{_mandir}/man3/wxAuiNotebookEvent.* +%{_mandir}/man3/wxAuiPaneInfo.* +%{_mandir}/man3/wxAuiSimpleTabArt.* +%{_mandir}/man3/wxAuiTabArt.* +%{_mandir}/man3/wxBitmap.* +%{_mandir}/man3/wxBitmapButton.* +%{_mandir}/man3/wxBitmapDataObject.* +%{_mandir}/man3/wxBookCtrlBase.* +%{_mandir}/man3/wxBookCtrlEvent.* +%{_mandir}/man3/wxBoxSizer.* +%{_mandir}/man3/wxBrush.* +%{_mandir}/man3/wxBufferedDC.* +%{_mandir}/man3/wxBufferedPaintDC.* +%{_mandir}/man3/wxButton.* +%{_mandir}/man3/wxCalendarCtrl.* +%{_mandir}/man3/wxCalendarDateAttr.* +%{_mandir}/man3/wxCalendarEvent.* +%{_mandir}/man3/wxCaret.* +%{_mandir}/man3/wxCheckBox.* +%{_mandir}/man3/wxCheckListBox.* +%{_mandir}/man3/wxChildFocusEvent.* +%{_mandir}/man3/wxChoice.* +%{_mandir}/man3/wxChoicebook.* +%{_mandir}/man3/wxClientDC.* +%{_mandir}/man3/wxClipboard.* +%{_mandir}/man3/wxClipboardTextEvent.* +%{_mandir}/man3/wxCloseEvent.* +%{_mandir}/man3/wxColourData.* +%{_mandir}/man3/wxColourDialog.* +%{_mandir}/man3/wxColourPickerCtrl.* +%{_mandir}/man3/wxColourPickerEvent.* +%{_mandir}/man3/wxComboBox.* +%{_mandir}/man3/wxCommandEvent.* +%{_mandir}/man3/wxContextMenuEvent.* +%{_mandir}/man3/wxControl.* +%{_mandir}/man3/wxControlWithItems.* +%{_mandir}/man3/wxCursor.* +%{_mandir}/man3/wxDC.* +%{_mandir}/man3/wxDCOverlay.* +%{_mandir}/man3/wxDataObject.* +%{_mandir}/man3/wxDateEvent.* +%{_mandir}/man3/wxDatePickerCtrl.* +%{_mandir}/man3/wxDialog.* +%{_mandir}/man3/wxDirDialog.* +%{_mandir}/man3/wxDirPickerCtrl.* +%{_mandir}/man3/wxDisplay.* +%{_mandir}/man3/wxDisplayChangedEvent.* +%{_mandir}/man3/wxDropFilesEvent.* +%{_mandir}/man3/wxEraseEvent.* +%{_mandir}/man3/wxEvent.* +%{_mandir}/man3/wxEvtHandler.* +%{_mandir}/man3/wxFileDataObject.* +%{_mandir}/man3/wxFileDialog.* +%{_mandir}/man3/wxFileDirPickerEvent.* +%{_mandir}/man3/wxFilePickerCtrl.* +%{_mandir}/man3/wxFindReplaceData.* +%{_mandir}/man3/wxFindReplaceDialog.* +%{_mandir}/man3/wxFlexGridSizer.* +%{_mandir}/man3/wxFocusEvent.* +%{_mandir}/man3/wxFont.* +%{_mandir}/man3/wxFontData.* +%{_mandir}/man3/wxFontDialog.* +%{_mandir}/man3/wxFontPickerCtrl.* +%{_mandir}/man3/wxFontPickerEvent.* +%{_mandir}/man3/wxFrame.* +%{_mandir}/man3/wxGBSizerItem.* +%{_mandir}/man3/wxGCDC.* +%{_mandir}/man3/wxGLCanvas.* +%{_mandir}/man3/wxGLContext.* +%{_mandir}/man3/wxGauge.* +%{_mandir}/man3/wxGenericDirCtrl.* +%{_mandir}/man3/wxGraphicsBrush.* +%{_mandir}/man3/wxGraphicsContext.* +%{_mandir}/man3/wxGraphicsFont.* +%{_mandir}/man3/wxGraphicsGradientStops.* +%{_mandir}/man3/wxGraphicsMatrix.* +%{_mandir}/man3/wxGraphicsObject.* +%{_mandir}/man3/wxGraphicsPath.* +%{_mandir}/man3/wxGraphicsPen.* +%{_mandir}/man3/wxGraphicsRenderer.* +%{_mandir}/man3/wxGrid.* +%{_mandir}/man3/wxGridBagSizer.* +%{_mandir}/man3/wxGridCellAttr.* +%{_mandir}/man3/wxGridCellBoolEditor.* +%{_mandir}/man3/wxGridCellBoolRenderer.* +%{_mandir}/man3/wxGridCellChoiceEditor.* +%{_mandir}/man3/wxGridCellEditor.* +%{_mandir}/man3/wxGridCellFloatEditor.* +%{_mandir}/man3/wxGridCellFloatRenderer.* +%{_mandir}/man3/wxGridCellNumberEditor.* +%{_mandir}/man3/wxGridCellNumberRenderer.* +%{_mandir}/man3/wxGridCellRenderer.* +%{_mandir}/man3/wxGridCellStringRenderer.* +%{_mandir}/man3/wxGridCellTextEditor.* +%{_mandir}/man3/wxGridEvent.* +%{_mandir}/man3/wxGridSizer.* +%{_mandir}/man3/wxHelpEvent.* +%{_mandir}/man3/wxHtmlEasyPrinting.* +%{_mandir}/man3/wxHtmlLinkEvent.* +%{_mandir}/man3/wxHtmlWindow.* +%{_mandir}/man3/wxIcon.* +%{_mandir}/man3/wxIconBundle.* +%{_mandir}/man3/wxIconizeEvent.* +%{_mandir}/man3/wxIdleEvent.* +%{_mandir}/man3/wxImage.* +%{_mandir}/man3/wxImageList.* +%{_mandir}/man3/wxInitDialogEvent.* +%{_mandir}/man3/wxJoystickEvent.* +%{_mandir}/man3/wxKeyEvent.* +%{_mandir}/man3/wxLayoutAlgorithm.* +%{_mandir}/man3/wxListBox.* +%{_mandir}/man3/wxListCtrl.* +%{_mandir}/man3/wxListEvent.* +%{_mandir}/man3/wxListItem.* +%{_mandir}/man3/wxListItemAttr.* +%{_mandir}/man3/wxListView.* +%{_mandir}/man3/wxListbook.* +%{_mandir}/man3/wxLocale.* +%{_mandir}/man3/wxLogNull.* +%{_mandir}/man3/wxMDIChildFrame.* +%{_mandir}/man3/wxMDIClientWindow.* +%{_mandir}/man3/wxMDIParentFrame.* +%{_mandir}/man3/wxMask.* +%{_mandir}/man3/wxMaximizeEvent.* +%{_mandir}/man3/wxMemoryDC.* +%{_mandir}/man3/wxMenu.* +%{_mandir}/man3/wxMenuBar.* +%{_mandir}/man3/wxMenuEvent.* +%{_mandir}/man3/wxMenuItem.* +%{_mandir}/man3/wxMessageDialog.* +%{_mandir}/man3/wxMiniFrame.* +%{_mandir}/man3/wxMirrorDC.* +%{_mandir}/man3/wxMouseCaptureChangedEvent.* +%{_mandir}/man3/wxMouseCaptureLostEvent.* +%{_mandir}/man3/wxMouseEvent.* +%{_mandir}/man3/wxMoveEvent.* +%{_mandir}/man3/wxMultiChoiceDialog.* +%{_mandir}/man3/wxNavigationKeyEvent.* +%{_mandir}/man3/wxNotebook.* +%{_mandir}/man3/wxNotificationMessage.* +%{_mandir}/man3/wxNotifyEvent.* +%{_mandir}/man3/wxOverlay.* +%{_mandir}/man3/wxPageSetupDialog.* +%{_mandir}/man3/wxPageSetupDialogData.* +%{_mandir}/man3/wxPaintDC.* +%{_mandir}/man3/wxPaintEvent.* +%{_mandir}/man3/wxPalette.* +%{_mandir}/man3/wxPaletteChangedEvent.* +%{_mandir}/man3/wxPanel.* +%{_mandir}/man3/wxPasswordEntryDialog.* +%{_mandir}/man3/wxPen.* +%{_mandir}/man3/wxPickerBase.* +%{_mandir}/man3/wxPopupTransientWindow.* +%{_mandir}/man3/wxPopupWindow.* +%{_mandir}/man3/wxPostScriptDC.* +%{_mandir}/man3/wxPreviewCanvas.* +%{_mandir}/man3/wxPreviewControlBar.* +%{_mandir}/man3/wxPreviewFrame.* +%{_mandir}/man3/wxPrintData.* +%{_mandir}/man3/wxPrintDialog.* +%{_mandir}/man3/wxPrintDialogData.* +%{_mandir}/man3/wxPrintPreview.* +%{_mandir}/man3/wxPrinter.* +%{_mandir}/man3/wxPrintout.* +%{_mandir}/man3/wxProgressDialog.* +%{_mandir}/man3/wxQueryNewPaletteEvent.* +%{_mandir}/man3/wxRadioBox.* +%{_mandir}/man3/wxRadioButton.* +%{_mandir}/man3/wxRegion.* +%{_mandir}/man3/wxSashEvent.* +%{_mandir}/man3/wxSashLayoutWindow.* +%{_mandir}/man3/wxSashWindow.* +%{_mandir}/man3/wxScreenDC.* +%{_mandir}/man3/wxScrollBar.* +%{_mandir}/man3/wxScrollEvent.* +%{_mandir}/man3/wxScrollWinEvent.* +%{_mandir}/man3/wxScrolledWindow.* +%{_mandir}/man3/wxSetCursorEvent.* +%{_mandir}/man3/wxShowEvent.* +%{_mandir}/man3/wxSingleChoiceDialog.* +%{_mandir}/man3/wxSizeEvent.* +%{_mandir}/man3/wxSizer.* +%{_mandir}/man3/wxSizerFlags.* +%{_mandir}/man3/wxSizerItem.* +%{_mandir}/man3/wxSlider.* +%{_mandir}/man3/wxSpinButton.* +%{_mandir}/man3/wxSpinCtrl.* +%{_mandir}/man3/wxSpinEvent.* +%{_mandir}/man3/wxSplashScreen.* +%{_mandir}/man3/wxSplitterEvent.* +%{_mandir}/man3/wxSplitterWindow.* +%{_mandir}/man3/wxStaticBitmap.* +%{_mandir}/man3/wxStaticBox.* +%{_mandir}/man3/wxStaticBoxSizer.* +%{_mandir}/man3/wxStaticLine.* +%{_mandir}/man3/wxStaticText.* +%{_mandir}/man3/wxStatusBar.* +%{_mandir}/man3/wxStdDialogButtonSizer.* +%{_mandir}/man3/wxStyledTextCtrl.* +%{_mandir}/man3/wxStyledTextEvent.* +%{_mandir}/man3/wxSysColourChangedEvent.* +%{_mandir}/man3/wxSystemOptions.* +%{_mandir}/man3/wxSystemSettings.* +%{_mandir}/man3/wxTaskBarIcon.* +%{_mandir}/man3/wxTaskBarIconEvent.* +%{_mandir}/man3/wxTextAttr.* +%{_mandir}/man3/wxTextCtrl.* +%{_mandir}/man3/wxTextDataObject.* +%{_mandir}/man3/wxTextEntryDialog.* +%{_mandir}/man3/wxToggleButton.* +%{_mandir}/man3/wxToolBar.* +%{_mandir}/man3/wxToolTip.* +%{_mandir}/man3/wxToolbook.* +%{_mandir}/man3/wxTopLevelWindow.* +%{_mandir}/man3/wxTreeCtrl.* +%{_mandir}/man3/wxTreeEvent.* +%{_mandir}/man3/wxTreebook.* +%{_mandir}/man3/wxUpdateUIEvent.* +%{_mandir}/man3/wxWebView.* +%{_mandir}/man3/wxWebViewEvent.* +%{_mandir}/man3/wxWindow.* +%{_mandir}/man3/wxWindowCreateEvent.* +%{_mandir}/man3/wxWindowDC.* +%{_mandir}/man3/wxWindowDestroyEvent.* +%{_mandir}/man3/wxXmlResource.* +%{_mandir}/man3/wx_misc.* +%{_mandir}/man3/wx_object.* +%endif +%endif %{__with_wxwidgets} + +%files xmerl +%{_libdir}/erlang/lib/xmerl-*/ +%if %{with doc} +%{_mandir}/man3/xmerl.* +%{_mandir}/man3/xmerl_eventp.* +%{_mandir}/man3/xmerl_sax_parser.* +%{_mandir}/man3/xmerl_scan.* +%{_mandir}/man3/xmerl_xpath.* +%{_mandir}/man3/xmerl_xs.* +%{_mandir}/man3/xmerl_xsd.* +%endif + +%changelog +* Fri May 09 2025 yaoxin <1024769339@qq.com> - 25.3.2.6-7 +- Fix CVE-2025-46712 + +* Sat Apr 26 2025 Funda Wang - 25.3.2.6-6 +- fix CVE-2025-32433 + +* 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 + +* Wed May 15 2024 zhangzikang - 25.3.2.6-3 +- Fix build error for loongarch64 + +* Thu Jan 25 2024 wangkai <13474090681@163.com> - 25.3.2.6-2 +- Fix CVE-2023-48795 + +* Mon Sep 18 2023 wangkai <13474090681@163.com> - 25.3.2.6-1 +- Update to 25.3.2.6 + +* Mon May 8 2023 Wenlong Zhang - 23.3.4.9-4 +- fix build error for loongarch64 + +* Fri Feb 10 2023 yaoxin - 23.3.4.9-3 +- Fix build failed due to emacs update to 28.2 + +* Fri Feb 3 2023 liyanan - 23.3.4.9-2 +- Fix build failed due to openssl update to 3.0 + +* Thu Apr 07 2022 houyingchao - 23.3.4.9-1 +- Fix compilation failed + +* Fri Jul 30 2021 liping - 21.3.3-3 +- Support parallel compilation + +* Sat Mar 27 2021 weishengjing - 21.3.3-2 +- Support parallel compilation + +* Mon Aug 24 2020 chengzihan - 21.3.3-1 +- Package init diff --git a/erlang.yaml b/erlang.yaml new file mode 100644 index 0000000..ab8e210 --- /dev/null +++ b/erlang.yaml @@ -0,0 +1,4 @@ +version_control: github +src_repo: erlang/otp +tag_prefix: "OTP-" +seperator: "." diff --git a/otp-0001-Do-not-format-man-pages-and-do-not-install-miscellan.patch b/otp-0001-Do-not-format-man-pages-and-do-not-install-miscellan.patch new file mode 100644 index 0000000..96f0494 --- /dev/null +++ b/otp-0001-Do-not-format-man-pages-and-do-not-install-miscellan.patch @@ -0,0 +1,41 @@ +From: Peter Lemenkov +Date: Thu, 25 Feb 2010 16:45:28 +0300 +Subject: [PATCH] Do not format man-pages and do not install miscellaneous + utilities for dealing with man-pages. + +Signed-off-by: Peter Lemenkov + +diff --git a/erts/etc/common/Makefile.in b/erts/etc/common/Makefile.in +index 86f63dcf41..b74c789775 100644 +--- a/erts/etc/common/Makefile.in ++++ b/erts/etc/common/Makefile.in +@@ -555,10 +555,6 @@ endif + ifneq ($(INSTALL_TOP_BIN),) + $(INSTALL_PROGRAM) $(INSTALL_TOP_BIN) "$(RELEASE_PATH)" + endif +-ifneq ($(INSTALL_MISC),) +- $(INSTALL_DIR) "$(RELEASE_PATH)/misc" +- $(INSTALL_SCRIPT) $(INSTALL_MISC) "$(RELEASE_PATH)/misc" +-endif + ifneq ($(INSTALL_SRC),) + $(INSTALL_DIR) "$(RELEASE_PATH)/erts-$(VSN)/src" + $(INSTALL_DATA) $(INSTALL_SRC) "$(RELEASE_PATH)/erts-$(VSN)/src" +diff --git a/erts/etc/unix/Install.src b/erts/etc/unix/Install.src +index b00dd09f1a..2147774f50 100644 +--- a/erts/etc/unix/Install.src ++++ b/erts/etc/unix/Install.src +@@ -143,14 +143,5 @@ cp -p ../releases/%I_SYSTEM_VSN%/start_*.boot . + cp -p ../releases/%I_SYSTEM_VSN%/no_dot_erlang.boot . + cp -p $Name.boot start.boot + cp -p ../releases/%I_SYSTEM_VSN%/$Name.script start.script +-# +-# Fixing the man pages +-# +- +-if [ -d "$ERL_ROOT/man" ] +-then +- cd "$ERL_ROOT" +- ./misc/format_man_pages "$ERL_ROOT" +-fi + + exit 0 diff --git a/otp-0002-Remove-rpath.patch b/otp-0002-Remove-rpath.patch new file mode 100644 index 0000000..b906050 --- /dev/null +++ b/otp-0002-Remove-rpath.patch @@ -0,0 +1,19 @@ +From: Peter Lemenkov +Date: Thu, 25 Feb 2010 16:57:43 +0300 +Subject: [PATCH] Remove rpath + +Signed-off-by: Peter Lemenkov + +diff --git a/lib/crypto/c_src/Makefile.in b/lib/crypto/c_src/Makefile.in +index 25167a8a3a..2345970fa9 100644 +--- a/lib/crypto/c_src/Makefile.in ++++ b/lib/crypto/c_src/Makefile.in +@@ -147,7 +147,7 @@ endif + endif + + ifeq ($(DYNAMIC_OR_WIN_CRYPTO_LIB),yes) +-SSL_DED_LD_RUNTIME_LIBRARY_PATH = @SSL_DED_LD_RUNTIME_LIBRARY_PATH@ ++SSL_DED_LD_RUNTIME_LIBRARY_PATH = + CRYPTO_LINK_LIB=$(SSL_DED_LD_RUNTIME_LIBRARY_PATH) -L$(SSL_LIBDIR) -l$(SSL_CRYPTO_LIBNAME) + EXTRA_FLAGS = -DHAVE_DYNAMIC_CRYPTO_LIB + else diff --git a/otp-0003-Do-not-install-C-sources.patch b/otp-0003-Do-not-install-C-sources.patch new file mode 100644 index 0000000..bb55157 --- /dev/null +++ b/otp-0003-Do-not-install-C-sources.patch @@ -0,0 +1,93 @@ +From: Peter Lemenkov +Date: Fri, 18 Jun 2010 23:41:33 +0400 +Subject: [PATCH] Do not install C sources + +Don't install *.c and *.o files. + +Excepts ones from the internal erl_interface. These +API headers are necessary. See rhbz #818419 for the +explanation why they're necessary for the low-level +interaction with the Erlang nodes: + +https://bugzilla.redhat.com/818419 + +Signed-off-by: Peter Lemenkov + +diff --git a/lib/asn1/c_src/Makefile b/lib/asn1/c_src/Makefile +index 82a6b6e87a..5f2fe8ba7d 100644 +--- a/lib/asn1/c_src/Makefile ++++ b/lib/asn1/c_src/Makefile +@@ -137,8 +137,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/priv/lib" + $(INSTALL_PROGRAM) $(NIF_SHARED_OBJ_FILE) "$(RELSYSDIR)/priv/lib" +- $(INSTALL_DIR) "$(RELSYSDIR)/c_src" +- $(INSTALL_DATA) *.c "$(RELSYSDIR)/c_src" + + release_docs_spec: + +diff --git a/lib/erl_interface/src/Makefile.in b/lib/erl_interface/src/Makefile.in +index 0a5ae800be..2cc354c43e 100644 +--- a/lib/erl_interface/src/Makefile.in ++++ b/lib/erl_interface/src/Makefile.in +@@ -712,13 +712,11 @@ ifeq (@DYNAMIC_LIB@, yes) + endif + $(INSTALL_PROGRAM) $(EXE_TARGETS) "$(RELSYSDIR)/bin" + $(INSTALL_DATA) $(EXTRA) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) connect/*.[ch] "$(RELSYSDIR)/src/connect" +- $(INSTALL_DATA) decode/*.[ch] "$(RELSYSDIR)/src/decode" +- $(INSTALL_DATA) encode/*.[ch] "$(RELSYSDIR)/src/encode" +- $(INSTALL_DATA) epmd/*.[ch] "$(RELSYSDIR)/src/epmd" +- $(INSTALL_DATA) misc/*.[ch] "$(RELSYSDIR)/src/misc" +- $(INSTALL_DATA) global/*.[ch] "$(RELSYSDIR)/src/global" +- $(INSTALL_DATA) prog/*.[ch] "$(RELSYSDIR)/src/prog" ++ $(INSTALL_DATA) connect/*.h "$(RELSYSDIR)/src/connect" ++ $(INSTALL_DATA) decode/*.h "$(RELSYSDIR)/src/decode" ++ $(INSTALL_DATA) encode/*.h "$(RELSYSDIR)/src/encode" ++ $(INSTALL_DATA) epmd/*.h "$(RELSYSDIR)/src/epmd" ++ $(INSTALL_DATA) misc/*.h "$(RELSYSDIR)/src/misc" + + release_docs: + +diff --git a/lib/megaco/src/flex/Makefile.in b/lib/megaco/src/flex/Makefile.in +index 3649e2c392..d8c5c68b99 100644 +--- a/lib/megaco/src/flex/Makefile.in ++++ b/lib/megaco/src/flex/Makefile.in +@@ -251,7 +251,7 @@ release_spec: opt + $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/flex" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + ifeq ($(ENABLE_MEGACO_FLEX_SCANNER),true) +- $(INSTALL_DATA) $(FLEX_FILES) $(C_TARGETS) "$(RELSYSDIR)/src/flex" ++ $(INSTALL_DATA) $(FLEX_FILES) "$(RELSYSDIR)/src/flex" + $(INSTALL_PROGRAM) $(SOLIBS) "$(RELSYSDIR)/priv/lib" + endif + +diff --git a/lib/odbc/c_src/Makefile.in b/lib/odbc/c_src/Makefile.in +index d1b26743a6..cf8faae1f5 100644 +--- a/lib/odbc/c_src/Makefile.in ++++ b/lib/odbc/c_src/Makefile.in +@@ -129,11 +129,8 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + ifdef EXE_TARGET +- $(INSTALL_DIR) "$(RELSYSDIR)/c_src" +- $(INSTALL_DATA) $(C_FILES) $(H_FILES) "$(RELSYSDIR)/c_src" + $(INSTALL_DIR) "$(RELSYSDIR)/priv" + $(INSTALL_DIR) "$(RELSYSDIR)/priv/bin" +- $(INSTALL_DIR) "$(RELSYSDIR)/priv/obj" + $(INSTALL_PROGRAM) $(EXE_TARGET) "$(RELSYSDIR)/priv/bin" + endif + +diff --git a/lib/os_mon/c_src/Makefile.in b/lib/os_mon/c_src/Makefile.in +index 27b156a2c9..f11ff303b6 100644 +--- a/lib/os_mon/c_src/Makefile.in ++++ b/lib/os_mon/c_src/Makefile.in +@@ -126,8 +126,6 @@ $(OBJDIR)/memsup.o: memsup.h + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(C_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/priv/bin" + $(INSTALL_PROGRAM) $(TARGET_FILES) "$(RELSYSDIR)/priv/bin" + diff --git a/otp-0004-Do-not-install-Java-sources.patch b/otp-0004-Do-not-install-Java-sources.patch new file mode 100644 index 0000000..a8037ea --- /dev/null +++ b/otp-0004-Do-not-install-Java-sources.patch @@ -0,0 +1,19 @@ +From: Peter Lemenkov +Date: Sat, 19 Jun 2010 09:25:18 +0400 +Subject: [PATCH] Do not install Java sources + +Signed-off-by: Peter Lemenkov + +diff --git a/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile b/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile +index 089cf4ab1a..404654a437 100644 +--- a/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile ++++ b/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile +@@ -123,8 +123,6 @@ release release_docs release_tests release_html: + $(V_at)$(MAKE) $(MFLAGS) RELEASE_PATH="$(RELEASE_PATH)" $(TARGET_MAKEFILE) $@_spec + + release_spec: opt +- $(V_at)$(INSTALL_DIR) "$(RELSYSDIR)/java_src/com/ericsson/otp/erlang" +- $(V_at)$(INSTALL_DATA) $(JAVA_SRC) "$(RELSYSDIR)/java_src/com/ericsson/otp/erlang" + $(V_at)$(INSTALL_DIR) "$(RELSYSDIR)/priv" + $(V_at)$(INSTALL_DATA) $(JAVA_DEST_ROOT)$(JARFILE) "$(RELSYSDIR)/priv" + $(V_at)$(INSTALL_DIR) "$(RELSYSDIR)/ebin" diff --git a/otp-0005-Do-not-install-nteventlog-and-related-doc-files-on-n.patch b/otp-0005-Do-not-install-nteventlog-and-related-doc-files-on-n.patch new file mode 100644 index 0000000..1965881 --- /dev/null +++ b/otp-0005-Do-not-install-nteventlog-and-related-doc-files-on-n.patch @@ -0,0 +1,60 @@ +From: Peter Lemenkov +Date: Sat, 19 Jun 2010 09:59:39 +0400 +Subject: [PATCH] Do not install nteventlog and related doc-files on non-win32 + systems + +Signed-off-by: Peter Lemenkov + +diff --git a/lib/os_mon/doc/src/Makefile b/lib/os_mon/doc/src/Makefile +index 8e3882bfdc..ea999cf9c7 100644 +--- a/lib/os_mon/doc/src/Makefile ++++ b/lib/os_mon/doc/src/Makefile +@@ -31,11 +31,16 @@ APPLICATION=os_mon + # Target Specs + # ---------------------------------------------------- + XML_APPLICATION_FILES = ref_man.xml ++ifeq ($(findstring win32,$(TARGET)),win32) ++NTEVENTLOG_DOCFILE=nteventlog.xml ++else ++NTEVENTLOG_DOCFILE= ++endif + XML_REF3_FILES = cpu_sup.xml \ + disksup.xml \ + memsup.xml \ + os_sup.xml \ +- nteventlog.xml ++ $(NTEVENTLOG_DOCFILE) + + XML_REF6_FILES = os_mon_app.xml + +diff --git a/lib/os_mon/src/Makefile b/lib/os_mon/src/Makefile +index e28fb12548..ee32f3946f 100644 +--- a/lib/os_mon/src/Makefile ++++ b/lib/os_mon/src/Makefile +@@ -34,7 +34,13 @@ RELSYSDIR = $(RELEASE_PATH)/lib/os_mon-$(VSN) + # ---------------------------------------------------- + # Target Specs + # ---------------------------------------------------- +-MODULES= disksup memsup cpu_sup os_mon os_mon_mib os_sup os_mon_sysinfo nteventlog ++ifeq ($(findstring win32,$(TARGET)),win32) ++NTEVENTLOG=nteventlog ++else ++NTEVENTLOG= ++endif ++MODULES= disksup memsup cpu_sup os_mon os_mon_mib os_sup os_mon_sysinfo \ ++ $(NTEVENTLOG) + + INCLUDE=../include + CSRC=../c_src +@@ -78,7 +84,11 @@ docs: + # ---------------------------------------------------- + + $(APP_TARGET): $(APP_SRC) ../vsn.mk ++ifeq ($(findstring win32,$(TARGET)),win32) + $(vsn_verbose)sed -e 's;%VSN%;$(VSN);' $< > $@ ++else ++ $(vsn_verbose)sed -e 's;%VSN%;$(VSN);;s;,\s*nteventlog;;' $< > $@ ++endif + + $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + $(vsn_verbose)sed -e 's;%VSN%;$(VSN);' $< > $@ diff --git a/otp-0006-Do-not-install-erlang-sources.patch b/otp-0006-Do-not-install-erlang-sources.patch new file mode 100644 index 0000000..e40945b --- /dev/null +++ b/otp-0006-Do-not-install-erlang-sources.patch @@ -0,0 +1,660 @@ +From: Hans Ulrich Niedermann +Date: Mon, 21 Mar 2011 15:41:49 +0100 +Subject: [PATCH] Do not install erlang sources + +Don't install *.erl, *.xrl, *.yrl, and *.asn1 files at all. + +Signed-off-by: Peter Lemenkov +Signed-off-by: Hans Ulrich Niedermann + +diff --git a/erts/preloaded/src/Makefile b/erts/preloaded/src/Makefile +index 1994aa1302..007b7d44bd 100644 +--- a/erts/preloaded/src/Makefile ++++ b/erts/preloaded/src/Makefile +@@ -117,8 +117,6 @@ $(APP_TARGET): $(APP_SRC) $(ERL_TOP)/erts/vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: $(APP_TARGET) +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(BEAM_FILES) $(STUBS_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(STATIC_TARGET_FILES) $(APP_TARGET) "$(RELSYSDIR)/ebin" + +diff --git a/lib/asn1/src/Makefile b/lib/asn1/src/Makefile +index 9e13d02c8a..77ba98c2f8 100644 +--- a/lib/asn1/src/Makefile ++++ b/lib/asn1/src/Makefile +@@ -157,7 +157,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(APP_SRC) $(APPUP_SRC) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" + $(INSTALL_DATA) $(EXAMPLES) "$(RELSYSDIR)/examples" + +diff --git a/lib/common_test/src/Makefile b/lib/common_test/src/Makefile +index 00f13589f3..5bf4e50f14 100644 +--- a/lib/common_test/src/Makefile ++++ b/lib/common_test/src/Makefile +@@ -157,7 +157,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/common_test/test_server/Makefile b/lib/common_test/test_server/Makefile +index 4ff5e678ee..4e3fa5c60f 100644 +--- a/lib/common_test/test_server/Makefile ++++ b/lib/common_test/test_server/Makefile +@@ -83,9 +83,9 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_tests_spec: opt + $(INSTALL_DIR) "$(RELEASE_PATH)/test_server" +- $(INSTALL_DATA) $(TS_ERL_FILES) $(TS_HRL_FILES) \ ++ $(INSTALL_DATA) $(TS_HRL_FILES) \ + $(TS_TARGET_FILES) \ +- $(AUTOCONF_FILES) $(CONFIG) \ ++ $(CONFIG) \ + "$(RELEASE_PATH)/test_server" + $(INSTALL_SCRIPT) $(PROGRAMS) "$(RELEASE_PATH)/test_server" + +diff --git a/lib/compiler/src/Makefile b/lib/compiler/src/Makefile +index d801d6baa0..4eed19b516 100644 +--- a/lib/compiler/src/Makefile ++++ b/lib/compiler/src/Makefile +@@ -188,8 +188,8 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(EXTRA_FILES) \ +- $(YRL_FILE) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) $(EXTRA_FILES) \ ++ "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(INSTALL_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/crypto/src/Makefile b/lib/crypto/src/Makefile +index 893f679390..6f8a329421 100644 +--- a/lib/crypto/src/Makefile ++++ b/lib/crypto/src/Makefile +@@ -81,8 +81,6 @@ docs: + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/debugger/src/Makefile b/lib/debugger/src/Makefile +index 2fb955b2e3..6ddce27ec1 100644 +--- a/lib/debugger/src/Makefile ++++ b/lib/debugger/src/Makefile +@@ -117,7 +117,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) $(TOOLBOX_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(TOOLBOX_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(TARGET_TOOLBOX_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/dialyzer/src/Makefile b/lib/dialyzer/src/Makefile +index c934ecdc2b..cc266f48e2 100644 +--- a/lib/dialyzer/src/Makefile ++++ b/lib/dialyzer/src/Makefile +@@ -162,7 +162,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(EXTRA_FILES) \ ++ $(INSTALL_DATA) $(HRL_FILES) $(EXTRA_FILES) \ + "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(INSTALL_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/diameter/src/Makefile b/lib/diameter/src/Makefile +index 75e23d4191..7097541548 100644 +--- a/lib/diameter/src/Makefile ++++ b/lib/diameter/src/Makefile +@@ -266,11 +266,8 @@ release_spec: opt + $(MAKE) ERL_DETERMINISTIC=$(ERL_DETERMINISTIC) $(EXAMPLE_DIRS:%/=release_examples_%) + + $(TARGET_DIRS:%/=release_src_%): release_src_%: +- $(INSTALL_DIR) "$(RELSYSDIR)/src/$*" +- $(INSTALL_DATA) $(filter $*/%, $(TARGET_MODULES:%=%.erl) \ +- $(INTERNAL_HRLS)) \ +- $(filter $*/%, compiler/$(DICT_YRL).yrl) \ +- "$(RELSYSDIR)/src/$*" ++ $(INSTALL_DATA) $(filter $*/%, $(INTERNAL_HRLS)) \ ++ "$(RELSYSDIR)/src/$*" || true + + $(EXAMPLE_DIRS:%/=release_examples_%): release_examples_%: + $(INSTALL_DIR) "$(RELSYSDIR)/examples/$*" +diff --git a/lib/edoc/src/Makefile b/lib/edoc/src/Makefile +index a455662049..e5b2f886ed 100644 +--- a/lib/edoc/src/Makefile ++++ b/lib/edoc/src/Makefile +@@ -87,7 +87,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(OBJECTS) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(SOURCES) $(HRL_FILES) $(YRL_FILE) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + + release_docs_spec: + +diff --git a/lib/eldap/src/Makefile b/lib/eldap/src/Makefile +index 04a84a4766..78fc4a9687 100644 +--- a/lib/eldap/src/Makefile ++++ b/lib/eldap/src/Makefile +@@ -98,13 +98,9 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +- $(INSTALL_DATA) $(ASN1_HRL) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" +- $(INSTALL_DIR) "$(RELSYSDIR)/asn1" +- $(INSTALL_DATA) ../asn1/$(ASN1_FILES) "$(RELSYSDIR)/asn1" ++ $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +- $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + + release_docs_spec: + +diff --git a/lib/erl_docgen/src/Makefile b/lib/erl_docgen/src/Makefile +index 458094e35f..cc3368ad02 100644 +--- a/lib/erl_docgen/src/Makefile ++++ b/lib/erl_docgen/src/Makefile +@@ -91,8 +91,6 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/et/src/Makefile b/lib/et/src/Makefile +index fc66cc1eaf..a567965ed4 100644 +--- a/lib/et/src/Makefile ++++ b/lib/et/src/Makefile +@@ -109,7 +109,6 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/eunit/src/Makefile b/lib/eunit/src/Makefile +index f4eaf6807a..2a49a2ca7a 100644 +--- a/lib/eunit/src/Makefile ++++ b/lib/eunit/src/Makefile +@@ -121,7 +121,6 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(PARSE_TRANSFORM_BIN) $(OBJECTS) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(PARSE_TRANSFORM) $(SOURCES) $(BEHAVIOUR_SOURCES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(INCLUDE_DELIVERABLES) "$(RELSYSDIR)/include" +diff --git a/lib/inets/src/http_client/Makefile b/lib/inets/src/http_client/Makefile +index 62f62792f0..ca4b539017 100644 +--- a/lib/inets/src/http_client/Makefile ++++ b/lib/inets/src/http_client/Makefile +@@ -92,7 +92,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_client" +- $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_client" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_client" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/http_lib/Makefile b/lib/inets/src/http_lib/Makefile +index 481c4f66eb..896a806695 100644 +--- a/lib/inets/src/http_lib/Makefile ++++ b/lib/inets/src/http_lib/Makefile +@@ -90,7 +90,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_lib" +- $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_lib" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_lib" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/http_server/Makefile b/lib/inets/src/http_server/Makefile +index abf8413f33..42925ba58f 100644 +--- a/lib/inets/src/http_server/Makefile ++++ b/lib/inets/src/http_server/Makefile +@@ -134,7 +134,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_server" +- $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_server" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_server" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(BEHAVIOUR_TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/inets_app/Makefile b/lib/inets/src/inets_app/Makefile +index 405e86105a..a8b932772a 100644 +--- a/lib/inets/src/inets_app/Makefile ++++ b/lib/inets/src/inets_app/Makefile +@@ -114,7 +114,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/inets_app" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/inets_app" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/inets_app" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/kernel/src/Makefile b/lib/kernel/src/Makefile +index 2149e89776..891d3e6f6a 100644 +--- a/lib/kernel/src/Makefile ++++ b/lib/kernel/src/Makefile +@@ -229,7 +229,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/megaco/src/app/Makefile b/lib/megaco/src/app/Makefile +index c681b88428..8cb286181a 100644 +--- a/lib/megaco/src/app/Makefile ++++ b/lib/megaco/src/app/Makefile +@@ -114,7 +114,7 @@ release_spec: opt + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/app" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/app" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/app" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" + +diff --git a/lib/megaco/src/binary/Makefile b/lib/megaco/src/binary/Makefile +index 9ecb649f0c..3ca5654eb3 100644 +--- a/lib/megaco/src/binary/Makefile ++++ b/lib/megaco/src/binary/Makefile +@@ -154,7 +154,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/binary" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(ASN1_FILES) "$(RELSYSDIR)/src/binary" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/binary" + + + release_docs_spec: +diff --git a/lib/megaco/src/engine/Makefile b/lib/megaco/src/engine/Makefile +index cc4974e09d..b7a7c703b3 100644 +--- a/lib/megaco/src/engine/Makefile ++++ b/lib/megaco/src/engine/Makefile +@@ -102,7 +102,7 @@ release_spec: opt + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/engine" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/engine" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/engine" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + + +diff --git a/lib/megaco/src/flex/Makefile.in b/lib/megaco/src/flex/Makefile.in +index d8c5c68b99..2053d3297b 100644 +--- a/lib/megaco/src/flex/Makefile.in ++++ b/lib/megaco/src/flex/Makefile.in +@@ -248,7 +248,6 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src/flex" + $(INSTALL_DIR) "$(RELSYSDIR)/priv/lib" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/flex" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + ifeq ($(ENABLE_MEGACO_FLEX_SCANNER),true) + $(INSTALL_DATA) $(FLEX_FILES) "$(RELSYSDIR)/src/flex" +diff --git a/lib/megaco/src/tcp/Makefile b/lib/megaco/src/tcp/Makefile +index ef4232244a..85cfb4b4ee 100644 +--- a/lib/megaco/src/tcp/Makefile ++++ b/lib/megaco/src/tcp/Makefile +@@ -94,7 +94,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/tcp" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/tcp" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/tcp" + + + release_docs_spec: +diff --git a/lib/megaco/src/text/Makefile b/lib/megaco/src/text/Makefile +index 6872b0ec04..a097be4d48 100644 +--- a/lib/megaco/src/text/Makefile ++++ b/lib/megaco/src/text/Makefile +@@ -133,7 +133,7 @@ release_spec: opt + $(INSTALL_DATA) $(BEAM_TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/text" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_YRL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/text" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/text" + + + release_docs_spec: +diff --git a/lib/megaco/src/udp/Makefile b/lib/megaco/src/udp/Makefile +index 5699c3e952..f8dcb5c681 100644 +--- a/lib/megaco/src/udp/Makefile ++++ b/lib/megaco/src/udp/Makefile +@@ -94,7 +94,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/udp" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/udp" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/udp" + + + release_docs_spec: +diff --git a/lib/mnesia/src/Makefile b/lib/mnesia/src/Makefile +index 72aa054fb3..08c6c5ffc1 100644 +--- a/lib/mnesia/src/Makefile ++++ b/lib/mnesia/src/Makefile +@@ -135,7 +135,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/observer/src/Makefile b/lib/observer/src/Makefile +index 2edb2ceb3e..884e69c7b7 100644 +--- a/lib/observer/src/Makefile ++++ b/lib/observer/src/Makefile +@@ -151,7 +151,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" + $(INSTALL_DATA) $(EXAMPLE_FILES) "$(RELSYSDIR)/examples" +diff --git a/lib/odbc/src/Makefile b/lib/odbc/src/Makefile +index e18628e94d..fa01850f38 100644 +--- a/lib/odbc/src/Makefile ++++ b/lib/odbc/src/Makefile +@@ -110,7 +110,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXT_HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/os_mon/src/Makefile b/lib/os_mon/src/Makefile +index ee32f3946f..2413fb68bf 100644 +--- a/lib/os_mon/src/Makefile ++++ b/lib/os_mon/src/Makefile +@@ -105,7 +105,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/parsetools/src/Makefile b/lib/parsetools/src/Makefile +index c7971750a7..f6024f1184 100644 +--- a/lib/parsetools/src/Makefile ++++ b/lib/parsetools/src/Makefile +@@ -91,8 +91,6 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/public_key/asn1/Makefile b/lib/public_key/asn1/Makefile +index c1adf58ed4..bba7cae5d6 100644 +--- a/lib/public_key/asn1/Makefile ++++ b/lib/public_key/asn1/Makefile +@@ -103,8 +103,6 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/asn1" + $(INSTALL_DATA) $(ASN_ASNS) $(ASN_CONFIGS) \ + "$(RELSYSDIR)/asn1" +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ASN_ERLS) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/public_key/src/Makefile b/lib/public_key/src/Makefile +index 9b2b442794..a5dcba4ec3 100644 +--- a/lib/public_key/src/Makefile ++++ b/lib/public_key/src/Makefile +@@ -111,8 +111,6 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/reltool/src/Makefile b/lib/reltool/src/Makefile +index 173a557d58..6864febbc3 100644 +--- a/lib/reltool/src/Makefile ++++ b/lib/reltool/src/Makefile +@@ -100,7 +100,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/runtime_tools/src/Makefile b/lib/runtime_tools/src/Makefile +index 8e8c4074f5..6e380e1b11 100644 +--- a/lib/runtime_tools/src/Makefile ++++ b/lib/runtime_tools/src/Makefile +@@ -99,8 +99,6 @@ docs: + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" +diff --git a/lib/sasl/src/Makefile b/lib/sasl/src/Makefile +index 490e03595d..739830ae3f 100644 +--- a/lib/sasl/src/Makefile ++++ b/lib/sasl/src/Makefile +@@ -94,7 +94,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/agent/Makefile.in b/lib/snmp/src/agent/Makefile.in +index 6ab9ed437a..14ae0bbc79 100644 +--- a/lib/snmp/src/agent/Makefile.in ++++ b/lib/snmp/src/agent/Makefile.in +@@ -161,7 +161,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/agent" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/agent" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/agent" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/app/Makefile b/lib/snmp/src/app/Makefile +index f5a74aa78e..0340088eb3 100644 +--- a/lib/snmp/src/app/Makefile ++++ b/lib/snmp/src/app/Makefile +@@ -144,7 +144,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/app" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/app" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/app" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/compile/Makefile b/lib/snmp/src/compile/Makefile +index f255237a04..04232658c7 100644 +--- a/lib/snmp/src/compile/Makefile ++++ b/lib/snmp/src/compile/Makefile +@@ -141,7 +141,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/compiler" +- $(INSTALL_DATA) $(ESCRIPT_SRC) $(PARSER_SRC) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/compiler" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/compiler" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(EBIN_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/bin" +diff --git a/lib/snmp/src/manager/Makefile b/lib/snmp/src/manager/Makefile +index 693ef75469..61b8dc4692 100644 +--- a/lib/snmp/src/manager/Makefile ++++ b/lib/snmp/src/manager/Makefile +@@ -135,7 +135,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/manager" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/manager" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/manager" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + # $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/snmp/src/misc/Makefile b/lib/snmp/src/misc/Makefile +index e92506e855..8dc421d2a1 100644 +--- a/lib/snmp/src/misc/Makefile ++++ b/lib/snmp/src/misc/Makefile +@@ -125,7 +125,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/misc" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/misc" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/misc" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + # $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/ssh/src/Makefile b/lib/ssh/src/Makefile +index 2fcb164301..2c7acf384d 100644 +--- a/lib/ssh/src/Makefile ++++ b/lib/ssh/src/Makefile +@@ -182,7 +182,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/ssl/src/Makefile b/lib/ssl/src/Makefile +index 789bed5c3f..9cd7f7226c 100644 +--- a/lib/ssl/src/Makefile ++++ b/lib/ssl/src/Makefile +@@ -211,7 +211,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile +index 761d6c4c28..43e7a650a5 100644 +--- a/lib/stdlib/src/Makefile ++++ b/lib/stdlib/src/Makefile +@@ -230,7 +230,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) erl_parse.yrl "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/syntax_tools/src/Makefile b/lib/syntax_tools/src/Makefile +index dc0ac61734..5bb265e2c2 100644 +--- a/lib/syntax_tools/src/Makefile ++++ b/lib/syntax_tools/src/Makefile +@@ -96,8 +96,6 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(OBJECTS) "$(RELSYSDIR)/ebin" +- $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(SOURCES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(INCLUDE_DELIVERABLES) "$(RELSYSDIR)/include" + +diff --git a/lib/tftp/src/Makefile b/lib/tftp/src/Makefile +index cfcb1ea134..fba9cc5873 100644 +--- a/lib/tftp/src/Makefile ++++ b/lib/tftp/src/Makefile +@@ -101,7 +101,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/tools/src/Makefile b/lib/tools/src/Makefile +index b05ce883ec..f8d143922d 100644 +--- a/lib/tools/src/Makefile ++++ b/lib/tools/src/Makefile +@@ -109,7 +109,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(YRL_FILE) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/wx/src/Makefile b/lib/wx/src/Makefile +index ce14c0b6df..f052399c0f 100644 +--- a/lib/wx/src/Makefile ++++ b/lib/wx/src/Makefile +@@ -121,9 +121,9 @@ $(EBIN)/%.beam: $(EGEN)/%.erl $(HEADER_FILES) + include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/gen" +- $(INSTALL_DATA) $(GEN_HRL) $(GEN_FILES) "$(RELSYSDIR)/src/gen" ++ $(INSTALL_DATA) $(GEN_HRL) "$(RELSYSDIR)/src/gen" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXT_HRL) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/xmerl/src/Makefile b/lib/xmerl/src/Makefile +index e7e7c8e978..37b7843605 100644 +--- a/lib/xmerl/src/Makefile ++++ b/lib/xmerl/src/Makefile +@@ -223,9 +223,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) $(APP_SRC) $(APPUP_SRC) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) xmerl_xpath_parse.yrl "$(RELSYSDIR)/src" +- $(INSTALL_DATA) xmerl_b64Bin.yrl "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + diff --git a/otp-0007-Add-extra-search-directory.patch b/otp-0007-Add-extra-search-directory.patch new file mode 100644 index 0000000..cb84b30 --- /dev/null +++ b/otp-0007-Add-extra-search-directory.patch @@ -0,0 +1,32 @@ +From: Peter Lemenkov +Date: Wed, 2 Aug 2017 16:12:19 +0300 +Subject: [PATCH] Add extra search directory + +Signed-off-by: Peter Lemenkov + +diff --git a/lib/kernel/src/code_server.erl b/lib/kernel/src/code_server.erl +index af8531271f..66050d6cdb 100644 +--- a/lib/kernel/src/code_server.erl ++++ b/lib/kernel/src/code_server.erl +@@ -79,11 +79,17 @@ init(Ref, Parent, [Root,Mode]) -> + IPath = + case Mode of + interactive -> +- LibDir = filename:append(Root, "lib"), +- {ok,Dirs} = erl_prim_loader:list_dir(LibDir), +- Paths = make_path(LibDir, Dirs), ++ F = fun(R) -> ++ LD = filename:append(R, "lib"), ++ case erl_prim_loader:list_dir(LD) of ++ error -> []; ++ {ok, D} -> make_path(LD, D) ++ end ++ end, ++ Paths = F(Root), ++ SharedPaths = F("/usr/share/erlang"), + UserLibPaths = get_user_lib_dirs(), +- ["."] ++ UserLibPaths ++ Paths; ++ ["."] ++ UserLibPaths ++ Paths ++ SharedPaths; + _ -> + [] + end, diff --git a/otp-0008-Avoid-forking-sed-to-get-basename.patch b/otp-0008-Avoid-forking-sed-to-get-basename.patch new file mode 100644 index 0000000..d146ab2 --- /dev/null +++ b/otp-0008-Avoid-forking-sed-to-get-basename.patch @@ -0,0 +1,31 @@ +From: Jan Pazdziora +Date: Thu, 10 May 2018 18:35:02 +0200 +Subject: [PATCH] Avoid forking sed to get basename. + + +diff --git a/erts/etc/unix/erl.src.src b/erts/etc/unix/erl.src.src +index 536fa139d9..4dcffbc4c8 100644 +--- a/erts/etc/unix/erl.src.src ++++ b/erts/etc/unix/erl.src.src +@@ -49,7 +49,7 @@ else + fi + BINDIR="$ROOTDIR/erts-%VSN%/bin" + EMU=%EMULATOR%%EMULATOR_NUMBER% +-PROGNAME=`basename "$0"` ++PROGNAME=${0##*/} + export EMU + export ROOTDIR + export BINDIR +diff --git a/erts/etc/unix/start_erl.src b/erts/etc/unix/start_erl.src +index 34e0369710..62e613bba1 100644 +--- a/erts/etc/unix/start_erl.src ++++ b/erts/etc/unix/start_erl.src +@@ -37,7 +37,7 @@ VSN=`awk '{print $2}' $DataFile` + + BINDIR=$ROOTDIR/erts-$ERTS_VSN/bin + EMU=beam +-PROGNAME=`echo $0 | sed 's/.*\///'` ++PROGNAME=${0##*/} + export EMU + export ROOTDIR + export BINDIR diff --git a/otp-0009-Load-man-pages-from-system-wide-directory.patch b/otp-0009-Load-man-pages-from-system-wide-directory.patch new file mode 100644 index 0000000..2075f81 --- /dev/null +++ b/otp-0009-Load-man-pages-from-system-wide-directory.patch @@ -0,0 +1,25 @@ +From: Francois-Denis Gonthier +Date: Thu, 20 Sep 2018 15:01:18 +0300 +Subject: [PATCH] Load man-pages from system-wide directory + +Patch allows one to use standard man path with erl -man command. +(Erlang manual pages are placed to /usr/share/man/ hierarchy +as required by Debian policy.) + +diff --git a/erts/etc/common/erlexec.c b/erts/etc/common/erlexec.c +index fa951ae770..9cce3857db 100644 +--- a/erts/etc/common/erlexec.c ++++ b/erts/etc/common/erlexec.c +@@ -709,8 +709,10 @@ int main(int argc, char **argv) + error("-man not supported on Windows"); + #else + argv[i] = "man"; +- erts_snprintf(tmpStr, sizeof(tmpStr), "%s/man", rootdir); +- set_env("MANPATH", tmpStr); ++ /* ++ * Conform to erlang-manpages content. ++ */ ++ putenv(strsave("MANSECT=3erl:1:5:7")); + execvp("man", argv+i); + error("Could not execute the 'man' command."); + #endif diff --git a/otp-0010-configure.ac-C99-fix-for-ERTS___AFTER_MORECORE_HOOK_.patch b/otp-0010-configure.ac-C99-fix-for-ERTS___AFTER_MORECORE_HOOK_.patch new file mode 100644 index 0000000..dc89898 --- /dev/null +++ b/otp-0010-configure.ac-C99-fix-for-ERTS___AFTER_MORECORE_HOOK_.patch @@ -0,0 +1,35 @@ +From: Florian Weimer +Date: Thu, 24 Nov 2022 11:57:49 +0100 +Subject: [PATCH] configure.ac: C99 fix for + ERTS___AFTER_MORECORE_HOOK_CAN_TRACK_MALLOC + +#include for the sbrk function if the header is available. + +diff --git a/erts/configure b/erts/configure +index fbdb6baba8..46e882e99a 100755 +--- a/erts/configure ++++ b/erts/configure +@@ -20644,6 +20644,9 @@ else $as_nop + #ifdef HAVE_MALLOC_H + # include + #endif ++#ifdef HAVE_UNISTD_H ++# include ++#endif + #if defined(HAVE_END_SYMBOL) + extern char end; + #elif defined(HAVE__END_SYMBOL) +diff --git a/erts/configure.ac b/erts/configure.ac +index 307be5042d..316345079b 100644 +--- a/erts/configure.ac ++++ b/erts/configure.ac +@@ -2436,6 +2436,9 @@ AC_CACHE_CHECK([if __after_morecore_hook can track malloc()s core memory use], + #ifdef HAVE_MALLOC_H + # include + #endif ++#ifdef HAVE_UNISTD_H ++# include ++#endif + #if defined(HAVE_END_SYMBOL) + extern char end; + #elif defined(HAVE__END_SYMBOL) diff --git a/otp-0011-configure.ac-C99-fixes-for-poll_works-check.patch b/otp-0011-configure.ac-C99-fixes-for-poll_works-check.patch new file mode 100644 index 0000000..d3d2a71 --- /dev/null +++ b/otp-0011-configure.ac-C99-fixes-for-poll_works-check.patch @@ -0,0 +1,72 @@ +From: Florian Weimer +Date: Thu, 24 Nov 2022 11:59:22 +0100 +Subject: [PATCH] configure.ac: C99 fixes for poll_works check + +Include if it is available for the open prototype. +Return from main instead of calling exit, so that no function +declaration is needed. + +diff --git a/erts/configure b/erts/configure +index 46e882e99a..7cc6f802ce 100755 +--- a/erts/configure ++++ b/erts/configure +@@ -24575,10 +24575,13 @@ else $as_nop + /* end confdefs.h. */ + + #include +-main() ++#ifdef HAVE_FCNTL_H ++#include ++#endif ++int main() + { + #ifdef _POLL_EMUL_H_ +- exit(1); /* Implemented using select() -- fail */ ++ return 1; /* Implemented using select() -- fail */ + #else + struct pollfd fds[1]; + int fd; +@@ -24587,9 +24590,9 @@ main() + fds[0].events = POLLIN; + fds[0].revents = 0; + if (poll(fds, 1, 0) < 0 || (fds[0].revents & POLLNVAL) != 0) { +- exit(1); /* Does not work for devices -- fail */ ++ return 1; /* Does not work for devices -- fail */ + } +- exit(0); ++ return 0; + #endif + } + +diff --git a/erts/configure.ac b/erts/configure.ac +index 316345079b..439ec5d4a1 100644 +--- a/erts/configure.ac ++++ b/erts/configure.ac +@@ -3055,10 +3055,13 @@ poll_works=no + + AC_RUN_IFELSE([AC_LANG_SOURCE([[ + #include +-main() ++#ifdef HAVE_FCNTL_H ++#include ++#endif ++int main() + { + #ifdef _POLL_EMUL_H_ +- exit(1); /* Implemented using select() -- fail */ ++ return 1; /* Implemented using select() -- fail */ + #else + struct pollfd fds[1]; + int fd; +@@ -3067,9 +3070,9 @@ main() + fds[0].events = POLLIN; + fds[0].revents = 0; + if (poll(fds, 1, 0) < 0 || (fds[0].revents & POLLNVAL) != 0) { +- exit(1); /* Does not work for devices -- fail */ ++ return 1; /* Does not work for devices -- fail */ + } +- exit(0); ++ return 0; + #endif + } + ]])],[poll_works=yes],[poll_works=no],[ diff --git a/otp-0012-Revert-Do-not-install-erlang-sources.patch b/otp-0012-Revert-Do-not-install-erlang-sources.patch new file mode 100644 index 0000000..1a0bb85 --- /dev/null +++ b/otp-0012-Revert-Do-not-install-erlang-sources.patch @@ -0,0 +1,657 @@ +From: Peter Lemenkov +Date: Wed, 4 Jan 2023 20:49:01 +0100 +Subject: [PATCH] Revert "Do not install erlang sources" + +This reverts commit 02d89974af96987a7cbcfe9d18533d509ad33690. + +diff --git a/erts/preloaded/src/Makefile b/erts/preloaded/src/Makefile +index 007b7d44bd..1994aa1302 100644 +--- a/erts/preloaded/src/Makefile ++++ b/erts/preloaded/src/Makefile +@@ -117,6 +117,8 @@ $(APP_TARGET): $(APP_SRC) $(ERL_TOP)/erts/vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: $(APP_TARGET) ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(BEAM_FILES) $(STUBS_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(STATIC_TARGET_FILES) $(APP_TARGET) "$(RELSYSDIR)/ebin" + +diff --git a/lib/asn1/src/Makefile b/lib/asn1/src/Makefile +index 77ba98c2f8..9e13d02c8a 100644 +--- a/lib/asn1/src/Makefile ++++ b/lib/asn1/src/Makefile +@@ -157,7 +157,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(APP_SRC) $(APPUP_SRC) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" + $(INSTALL_DATA) $(EXAMPLES) "$(RELSYSDIR)/examples" + +diff --git a/lib/common_test/src/Makefile b/lib/common_test/src/Makefile +index 5bf4e50f14..00f13589f3 100644 +--- a/lib/common_test/src/Makefile ++++ b/lib/common_test/src/Makefile +@@ -157,7 +157,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/common_test/test_server/Makefile b/lib/common_test/test_server/Makefile +index 4e3fa5c60f..4ff5e678ee 100644 +--- a/lib/common_test/test_server/Makefile ++++ b/lib/common_test/test_server/Makefile +@@ -83,9 +83,9 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_tests_spec: opt + $(INSTALL_DIR) "$(RELEASE_PATH)/test_server" +- $(INSTALL_DATA) $(TS_HRL_FILES) \ ++ $(INSTALL_DATA) $(TS_ERL_FILES) $(TS_HRL_FILES) \ + $(TS_TARGET_FILES) \ +- $(CONFIG) \ ++ $(AUTOCONF_FILES) $(CONFIG) \ + "$(RELEASE_PATH)/test_server" + $(INSTALL_SCRIPT) $(PROGRAMS) "$(RELEASE_PATH)/test_server" + +diff --git a/lib/compiler/src/Makefile b/lib/compiler/src/Makefile +index 4eed19b516..d801d6baa0 100644 +--- a/lib/compiler/src/Makefile ++++ b/lib/compiler/src/Makefile +@@ -188,8 +188,8 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) $(EXTRA_FILES) \ +- "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(EXTRA_FILES) \ ++ $(YRL_FILE) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(INSTALL_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/crypto/src/Makefile b/lib/crypto/src/Makefile +index 6f8a329421..893f679390 100644 +--- a/lib/crypto/src/Makefile ++++ b/lib/crypto/src/Makefile +@@ -81,6 +81,8 @@ docs: + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/debugger/src/Makefile b/lib/debugger/src/Makefile +index 6ddce27ec1..2fb955b2e3 100644 +--- a/lib/debugger/src/Makefile ++++ b/lib/debugger/src/Makefile +@@ -117,7 +117,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(TOOLBOX_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) $(TOOLBOX_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(TARGET_TOOLBOX_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/dialyzer/src/Makefile b/lib/dialyzer/src/Makefile +index cc266f48e2..c934ecdc2b 100644 +--- a/lib/dialyzer/src/Makefile ++++ b/lib/dialyzer/src/Makefile +@@ -162,7 +162,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) $(EXTRA_FILES) \ ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(EXTRA_FILES) \ + "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(INSTALL_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/diameter/src/Makefile b/lib/diameter/src/Makefile +index 7097541548..75e23d4191 100644 +--- a/lib/diameter/src/Makefile ++++ b/lib/diameter/src/Makefile +@@ -266,8 +266,11 @@ release_spec: opt + $(MAKE) ERL_DETERMINISTIC=$(ERL_DETERMINISTIC) $(EXAMPLE_DIRS:%/=release_examples_%) + + $(TARGET_DIRS:%/=release_src_%): release_src_%: +- $(INSTALL_DATA) $(filter $*/%, $(INTERNAL_HRLS)) \ +- "$(RELSYSDIR)/src/$*" || true ++ $(INSTALL_DIR) "$(RELSYSDIR)/src/$*" ++ $(INSTALL_DATA) $(filter $*/%, $(TARGET_MODULES:%=%.erl) \ ++ $(INTERNAL_HRLS)) \ ++ $(filter $*/%, compiler/$(DICT_YRL).yrl) \ ++ "$(RELSYSDIR)/src/$*" + + $(EXAMPLE_DIRS:%/=release_examples_%): release_examples_%: + $(INSTALL_DIR) "$(RELSYSDIR)/examples/$*" +diff --git a/lib/edoc/src/Makefile b/lib/edoc/src/Makefile +index e5b2f886ed..a455662049 100644 +--- a/lib/edoc/src/Makefile ++++ b/lib/edoc/src/Makefile +@@ -87,7 +87,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(OBJECTS) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(SOURCES) $(HRL_FILES) $(YRL_FILE) "$(RELSYSDIR)/src" + + release_docs_spec: + +diff --git a/lib/eldap/src/Makefile b/lib/eldap/src/Makefile +index 78fc4a9687..04a84a4766 100644 +--- a/lib/eldap/src/Makefile ++++ b/lib/eldap/src/Makefile +@@ -98,9 +98,13 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +- $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" ++ $(INSTALL_DATA) $(ASN1_HRL) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DIR) "$(RELSYSDIR)/asn1" ++ $(INSTALL_DATA) ../asn1/$(ASN1_FILES) "$(RELSYSDIR)/asn1" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" ++ $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" + + release_docs_spec: + +diff --git a/lib/erl_docgen/src/Makefile b/lib/erl_docgen/src/Makefile +index cc3368ad02..458094e35f 100644 +--- a/lib/erl_docgen/src/Makefile ++++ b/lib/erl_docgen/src/Makefile +@@ -91,6 +91,8 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/et/src/Makefile b/lib/et/src/Makefile +index a567965ed4..fc66cc1eaf 100644 +--- a/lib/et/src/Makefile ++++ b/lib/et/src/Makefile +@@ -109,6 +109,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/eunit/src/Makefile b/lib/eunit/src/Makefile +index 2a49a2ca7a..f4eaf6807a 100644 +--- a/lib/eunit/src/Makefile ++++ b/lib/eunit/src/Makefile +@@ -121,6 +121,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(PARSE_TRANSFORM_BIN) $(OBJECTS) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(PARSE_TRANSFORM) $(SOURCES) $(BEHAVIOUR_SOURCES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(INCLUDE_DELIVERABLES) "$(RELSYSDIR)/include" +diff --git a/lib/inets/src/http_client/Makefile b/lib/inets/src/http_client/Makefile +index ca4b539017..62f62792f0 100644 +--- a/lib/inets/src/http_client/Makefile ++++ b/lib/inets/src/http_client/Makefile +@@ -92,7 +92,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_client" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_client" ++ $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_client" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/http_lib/Makefile b/lib/inets/src/http_lib/Makefile +index 896a806695..481c4f66eb 100644 +--- a/lib/inets/src/http_lib/Makefile ++++ b/lib/inets/src/http_lib/Makefile +@@ -90,7 +90,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_lib" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_lib" ++ $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_lib" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/http_server/Makefile b/lib/inets/src/http_server/Makefile +index 42925ba58f..abf8413f33 100644 +--- a/lib/inets/src/http_server/Makefile ++++ b/lib/inets/src/http_server/Makefile +@@ -134,7 +134,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/http_server" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/http_server" ++ $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/http_server" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(BEHAVIOUR_TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/inets/src/inets_app/Makefile b/lib/inets/src/inets_app/Makefile +index a8b932772a..405e86105a 100644 +--- a/lib/inets/src/inets_app/Makefile ++++ b/lib/inets/src/inets_app/Makefile +@@ -114,7 +114,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/inets_app" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/inets_app" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src/inets_app" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/kernel/src/Makefile b/lib/kernel/src/Makefile +index 891d3e6f6a..2149e89776 100644 +--- a/lib/kernel/src/Makefile ++++ b/lib/kernel/src/Makefile +@@ -229,6 +229,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/megaco/src/app/Makefile b/lib/megaco/src/app/Makefile +index 8cb286181a..c681b88428 100644 +--- a/lib/megaco/src/app/Makefile ++++ b/lib/megaco/src/app/Makefile +@@ -114,7 +114,7 @@ release_spec: opt + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/app" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/app" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/app" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXTERNAL_HRL_FILES) "$(RELSYSDIR)/include" + +diff --git a/lib/megaco/src/binary/Makefile b/lib/megaco/src/binary/Makefile +index 3ca5654eb3..9ecb649f0c 100644 +--- a/lib/megaco/src/binary/Makefile ++++ b/lib/megaco/src/binary/Makefile +@@ -154,7 +154,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/binary" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/binary" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(ASN1_FILES) "$(RELSYSDIR)/src/binary" + + + release_docs_spec: +diff --git a/lib/megaco/src/engine/Makefile b/lib/megaco/src/engine/Makefile +index b7a7c703b3..cc4974e09d 100644 +--- a/lib/megaco/src/engine/Makefile ++++ b/lib/megaco/src/engine/Makefile +@@ -102,7 +102,7 @@ release_spec: opt + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/engine" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/engine" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/engine" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + + +diff --git a/lib/megaco/src/flex/Makefile.in b/lib/megaco/src/flex/Makefile.in +index 2053d3297b..d8c5c68b99 100644 +--- a/lib/megaco/src/flex/Makefile.in ++++ b/lib/megaco/src/flex/Makefile.in +@@ -248,6 +248,7 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src/flex" + $(INSTALL_DIR) "$(RELSYSDIR)/priv/lib" + $(INSTALL_DIR) "$(RELSYSDIR)/include" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/flex" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + ifeq ($(ENABLE_MEGACO_FLEX_SCANNER),true) + $(INSTALL_DATA) $(FLEX_FILES) "$(RELSYSDIR)/src/flex" +diff --git a/lib/megaco/src/tcp/Makefile b/lib/megaco/src/tcp/Makefile +index 85cfb4b4ee..ef4232244a 100644 +--- a/lib/megaco/src/tcp/Makefile ++++ b/lib/megaco/src/tcp/Makefile +@@ -94,7 +94,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/tcp" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/tcp" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/tcp" + + + release_docs_spec: +diff --git a/lib/megaco/src/text/Makefile b/lib/megaco/src/text/Makefile +index a097be4d48..6872b0ec04 100644 +--- a/lib/megaco/src/text/Makefile ++++ b/lib/megaco/src/text/Makefile +@@ -133,7 +133,7 @@ release_spec: opt + $(INSTALL_DATA) $(BEAM_TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/text" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/text" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_YRL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/text" + + + release_docs_spec: +diff --git a/lib/megaco/src/udp/Makefile b/lib/megaco/src/udp/Makefile +index f8dcb5c681..5699c3e952 100644 +--- a/lib/megaco/src/udp/Makefile ++++ b/lib/megaco/src/udp/Makefile +@@ -94,7 +94,7 @@ release_spec: opt + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/udp" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/udp" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/udp" + + + release_docs_spec: +diff --git a/lib/mnesia/src/Makefile b/lib/mnesia/src/Makefile +index 08c6c5ffc1..72aa054fb3 100644 +--- a/lib/mnesia/src/Makefile ++++ b/lib/mnesia/src/Makefile +@@ -135,7 +135,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/observer/src/Makefile b/lib/observer/src/Makefile +index 884e69c7b7..2edb2ceb3e 100644 +--- a/lib/observer/src/Makefile ++++ b/lib/observer/src/Makefile +@@ -151,6 +151,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" + $(INSTALL_DATA) $(EXAMPLE_FILES) "$(RELSYSDIR)/examples" +diff --git a/lib/odbc/src/Makefile b/lib/odbc/src/Makefile +index fa01850f38..e18628e94d 100644 +--- a/lib/odbc/src/Makefile ++++ b/lib/odbc/src/Makefile +@@ -110,7 +110,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXT_HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/os_mon/src/Makefile b/lib/os_mon/src/Makefile +index 2413fb68bf..ee32f3946f 100644 +--- a/lib/os_mon/src/Makefile ++++ b/lib/os_mon/src/Makefile +@@ -105,6 +105,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/parsetools/src/Makefile b/lib/parsetools/src/Makefile +index f6024f1184..c7971750a7 100644 +--- a/lib/parsetools/src/Makefile ++++ b/lib/parsetools/src/Makefile +@@ -91,6 +91,8 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/public_key/asn1/Makefile b/lib/public_key/asn1/Makefile +index bba7cae5d6..c1adf58ed4 100644 +--- a/lib/public_key/asn1/Makefile ++++ b/lib/public_key/asn1/Makefile +@@ -103,6 +103,8 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/asn1" + $(INSTALL_DATA) $(ASN_ASNS) $(ASN_CONFIGS) \ + "$(RELSYSDIR)/asn1" ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ASN_ERLS) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + +diff --git a/lib/public_key/src/Makefile b/lib/public_key/src/Makefile +index a5dcba4ec3..9b2b442794 100644 +--- a/lib/public_key/src/Makefile ++++ b/lib/public_key/src/Makefile +@@ -111,6 +111,8 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/reltool/src/Makefile b/lib/reltool/src/Makefile +index 6864febbc3..173a557d58 100644 +--- a/lib/reltool/src/Makefile ++++ b/lib/reltool/src/Makefile +@@ -100,7 +100,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(APP_TARGET) $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/runtime_tools/src/Makefile b/lib/runtime_tools/src/Makefile +index 6e380e1b11..8e8c4074f5 100644 +--- a/lib/runtime_tools/src/Makefile ++++ b/lib/runtime_tools/src/Makefile +@@ -99,6 +99,8 @@ docs: + include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/examples" +diff --git a/lib/sasl/src/Makefile b/lib/sasl/src/Makefile +index 739830ae3f..490e03595d 100644 +--- a/lib/sasl/src/Makefile ++++ b/lib/sasl/src/Makefile +@@ -94,6 +94,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/agent/Makefile.in b/lib/snmp/src/agent/Makefile.in +index 14ae0bbc79..6ab9ed437a 100644 +--- a/lib/snmp/src/agent/Makefile.in ++++ b/lib/snmp/src/agent/Makefile.in +@@ -161,7 +161,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/agent" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/agent" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/agent" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/app/Makefile b/lib/snmp/src/app/Makefile +index 0340088eb3..f5a74aa78e 100644 +--- a/lib/snmp/src/app/Makefile ++++ b/lib/snmp/src/app/Makefile +@@ -144,7 +144,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/app" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/app" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/app" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/snmp/src/compile/Makefile b/lib/snmp/src/compile/Makefile +index 04232658c7..f255237a04 100644 +--- a/lib/snmp/src/compile/Makefile ++++ b/lib/snmp/src/compile/Makefile +@@ -141,7 +141,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/compiler" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/compiler" ++ $(INSTALL_DATA) $(ESCRIPT_SRC) $(PARSER_SRC) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src/compiler" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(EBIN_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/bin" +diff --git a/lib/snmp/src/manager/Makefile b/lib/snmp/src/manager/Makefile +index 61b8dc4692..693ef75469 100644 +--- a/lib/snmp/src/manager/Makefile ++++ b/lib/snmp/src/manager/Makefile +@@ -135,7 +135,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/manager" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/manager" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/manager" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + # $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/snmp/src/misc/Makefile b/lib/snmp/src/misc/Makefile +index 8dc421d2a1..e92506e855 100644 +--- a/lib/snmp/src/misc/Makefile ++++ b/lib/snmp/src/misc/Makefile +@@ -125,7 +125,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/misc" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src/misc" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src/misc" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + # $(INSTALL_DIR) "$(RELSYSDIR)/include" +diff --git a/lib/ssh/src/Makefile b/lib/ssh/src/Makefile +index 2c7acf384d..2fcb164301 100644 +--- a/lib/ssh/src/Makefile ++++ b/lib/ssh/src/Makefile +@@ -182,7 +182,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(INTERNAL_HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/ssl/src/Makefile b/lib/ssl/src/Makefile +index 9cd7f7226c..789bed5c3f 100644 +--- a/lib/ssl/src/Makefile ++++ b/lib/ssl/src/Makefile +@@ -211,7 +211,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile +index 43e7a650a5..761d6c4c28 100644 +--- a/lib/stdlib/src/Makefile ++++ b/lib/stdlib/src/Makefile +@@ -230,6 +230,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) erl_parse.yrl "$(RELSYSDIR)/src" + $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" +diff --git a/lib/syntax_tools/src/Makefile b/lib/syntax_tools/src/Makefile +index 5bb265e2c2..dc0ac61734 100644 +--- a/lib/syntax_tools/src/Makefile ++++ b/lib/syntax_tools/src/Makefile +@@ -96,6 +96,8 @@ include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(OBJECTS) "$(RELSYSDIR)/ebin" ++ $(INSTALL_DIR) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(SOURCES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(INCLUDE_DELIVERABLES) "$(RELSYSDIR)/include" + +diff --git a/lib/tftp/src/Makefile b/lib/tftp/src/Makefile +index fba9cc5873..cfcb1ea134 100644 +--- a/lib/tftp/src/Makefile ++++ b/lib/tftp/src/Makefile +@@ -101,7 +101,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(BEHAVIOUR_TARGET_FILES) $(TARGET_FILES) $(APP_TARGET) \ + $(APPUP_TARGET) "$(RELSYSDIR)/ebin" +diff --git a/lib/tools/src/Makefile b/lib/tools/src/Makefile +index f8d143922d..b05ce883ec 100644 +--- a/lib/tools/src/Makefile ++++ b/lib/tools/src/Makefile +@@ -109,7 +109,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk + + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(YRL_FILE) $(HRL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) $(APP_TARGET) $(APPUP_TARGET) \ + "$(RELSYSDIR)/ebin" +diff --git a/lib/wx/src/Makefile b/lib/wx/src/Makefile +index f052399c0f..ce14c0b6df 100644 +--- a/lib/wx/src/Makefile ++++ b/lib/wx/src/Makefile +@@ -121,9 +121,9 @@ $(EBIN)/%.beam: $(EGEN)/%.erl $(HEADER_FILES) + include $(ERL_TOP)/make/otp_release_targets.mk + release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(HRL_FILES) $(ERL_FILES) "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/src/gen" +- $(INSTALL_DATA) $(GEN_HRL) "$(RELSYSDIR)/src/gen" ++ $(INSTALL_DATA) $(GEN_HRL) $(GEN_FILES) "$(RELSYSDIR)/src/gen" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(EXT_HRL) "$(RELSYSDIR)/include" + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" +diff --git a/lib/xmerl/src/Makefile b/lib/xmerl/src/Makefile +index 37b7843605..e7e7c8e978 100644 +--- a/lib/xmerl/src/Makefile ++++ b/lib/xmerl/src/Makefile +@@ -223,7 +223,9 @@ release_spec: opt + $(INSTALL_DIR) "$(RELSYSDIR)/ebin" + $(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin" + $(INSTALL_DIR) "$(RELSYSDIR)/src" +- $(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) $(ERL_FILES) $(INTERNAL_HRL_FILES) $(APP_SRC) $(APPUP_SRC) "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) xmerl_xpath_parse.yrl "$(RELSYSDIR)/src" ++ $(INSTALL_DATA) xmerl_b64Bin.yrl "$(RELSYSDIR)/src" + $(INSTALL_DIR) "$(RELSYSDIR)/include" + $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include" + diff --git a/otp-OTP-25.3.2.6.tar.gz b/otp-OTP-25.3.2.6.tar.gz new file mode 100644 index 0000000..46d50d8 Binary files /dev/null and b/otp-OTP-25.3.2.6.tar.gz differ