转换LFS仓库为普通仓库
This commit is contained in:
commit
aed1a61f76
593
CVE-2022-37026.patch
Normal file
593
CVE-2022-37026.patch
Normal file
@ -0,0 +1,593 @@
|
||||
From cd5024867e7b7d3a6e94194af9e01e1fb77e36c9 Mon Sep 17 00:00:00 2001
|
||||
From: Ingela Anderton Andin <ingela@erlang.org>
|
||||
Date: Tue, 24 May 2022 17:52:02 +0200
|
||||
Subject: [PATCH] ssl: Enhanch handling of unexpected messages
|
||||
|
||||
Origin:
|
||||
https://github.com/erlang/otp/commit/cd5024867e7b7d3a6e94194af9e01e1fb77e36c9
|
||||
https://github.com/erlang/otp/commit/6a1baa36e4e6c1b682e8b48e0c141602e0b8e6e5
|
||||
|
||||
Make better use of gen_statem. Rename flag and values to better names.
|
||||
---
|
||||
lib/ssl/src/dtls_connection.erl | 25 ++++-
|
||||
lib/ssl/src/ssl_connection.hrl | 6 +-
|
||||
lib/ssl/src/ssl_gen_statem.erl | 3 -
|
||||
lib/ssl/src/tls_connection.erl | 21 +++-
|
||||
lib/ssl/src/tls_dtls_connection.erl | 155 +++++++++++++++++-----------
|
||||
lib/ssl/src/tls_gen_connection.erl | 23 ++++-
|
||||
lib/ssl/src/tls_handshake_1_3.erl | 8 +-
|
||||
lib/ssl/test/ssl_npn_SUITE.erl | 8 +-
|
||||
8 files changed, 171 insertions(+), 78 deletions(-)
|
||||
|
||||
diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
|
||||
index 78348826e471..5a85bf8016ed 100644
|
||||
--- a/lib/ssl/src/dtls_connection.erl
|
||||
+++ b/lib/ssl/src/dtls_connection.erl
|
||||
@@ -46,7 +46,8 @@
|
||||
%% ClientKeyExchange \
|
||||
%% CertificateVerify* Flight 5
|
||||
%% [ChangeCipherSpec] /
|
||||
-%% Finished --------> /
|
||||
+%% NextProtocol* /
|
||||
+%% Finished --------> /
|
||||
%%
|
||||
%% [ChangeCipherSpec] \ Flight 6
|
||||
%% <-------- Finished /
|
||||
@@ -64,7 +65,8 @@
|
||||
%% <-------- Finished / part 2
|
||||
%%
|
||||
%% [ChangeCipherSpec] \ Abbrev Flight 3
|
||||
-%% Finished --------> /
|
||||
+%% NextProtocol* /
|
||||
+%% Finished --------> /
|
||||
%%
|
||||
%%
|
||||
%% Message Flights for Abbbriviated Handshake
|
||||
@@ -140,6 +142,7 @@
|
||||
user_hello/3,
|
||||
wait_ocsp_stapling/3,
|
||||
certify/3,
|
||||
+ wait_cert_verify/3,
|
||||
cipher/3,
|
||||
abbreviated/3,
|
||||
connection/3]).
|
||||
@@ -462,6 +465,24 @@ certify(state_timeout, Event, State) ->
|
||||
certify(Type, Event, State) ->
|
||||
gen_handshake(?FUNCTION_NAME, Type, Event, State).
|
||||
|
||||
+
|
||||
+%%--------------------------------------------------------------------
|
||||
+-spec wait_cert_verify(gen_statem:event_type(), term(), #state{}) ->
|
||||
+ gen_statem:state_function_result().
|
||||
+%%--------------------------------------------------------------------
|
||||
+wait_cert_verify(enter, _Event, State0) ->
|
||||
+ {State, Actions} = handle_flight_timer(State0),
|
||||
+ {keep_state, State, Actions};
|
||||
+wait_cert_verify(info, Event, State) ->
|
||||
+ gen_info(Event, ?FUNCTION_NAME, State);
|
||||
+wait_cert_verify(state_timeout, Event, State) ->
|
||||
+ handle_state_timeout(Event, ?FUNCTION_NAME, State);
|
||||
+wait_cert_verify(Type, Event, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
|
||||
+ try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
|
||||
+ catch throw:#alert{} = Alert ->
|
||||
+ ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State)
|
||||
+ end.
|
||||
+
|
||||
%%--------------------------------------------------------------------
|
||||
-spec cipher(gen_statem:event_type(), term(), #state{}) ->
|
||||
gen_statem:state_function_result().
|
||||
diff --git a/lib/ssl/src/ssl_connection.hrl b/lib/ssl/src/ssl_connection.hrl
|
||||
index 4f9584bb9ffe..9534ae023446 100644
|
||||
--- a/lib/ssl/src/ssl_connection.hrl
|
||||
+++ b/lib/ssl/src/ssl_connection.hrl
|
||||
@@ -115,7 +115,7 @@
|
||||
%% need to worry about packet loss in TLS. In DTLS we
|
||||
%% need to track DTLS handshake seqnr
|
||||
flight_buffer = [] :: list() | map(),
|
||||
- client_certificate_requested = false :: boolean(),
|
||||
+ client_certificate_status = not_requested :: not_requested | requested | empty | needs_verifying | verified,
|
||||
protocol_specific = #{} :: map(),
|
||||
session :: #session{} | secret_printout(),
|
||||
key_share,
|
||||
@@ -147,8 +147,8 @@
|
||||
%% session_cache_cb - not implemented
|
||||
%% crl_db - not implemented
|
||||
%% client_hello_version - Bleichenbacher mitigation in TLS 1.2
|
||||
-%% client_certificate_requested - Built into TLS 1.3 state machine
|
||||
-%% key_algorithm - not used
|
||||
+%% client_certificate_status - only uses non_requested| requested
|
||||
+%% key_algorithm - only uses not_requested and requested
|
||||
%% diffie_hellman_params - used in TLS 1.2 ECDH key exchange
|
||||
%% diffie_hellman_keys - used in TLS 1.2 ECDH key exchange
|
||||
%% psk_identity - not used
|
||||
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
|
||||
index e6268b4876cf..cde74b6acf00 100644
|
||||
--- a/lib/ssl/src/ssl_gen_statem.erl
|
||||
+++ b/lib/ssl/src/ssl_gen_statem.erl
|
||||
@@ -669,9 +669,6 @@ handle_common_event(internal, {protocol_record, TLSorDTLSRecord}, StateName,
|
||||
Connection:handle_protocol_record(TLSorDTLSRecord, StateName, State);
|
||||
handle_common_event(timeout, hibernate, _, _) ->
|
||||
{keep_state_and_data, [hibernate]};
|
||||
-handle_common_event(internal, #change_cipher_spec{type = <<1>>}, StateName,
|
||||
- #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
|
||||
- handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE), Version, StateName, State);
|
||||
handle_common_event({timeout, handshake}, close, _StateName, #state{start_or_recv_from = StartFrom} = State) ->
|
||||
{stop_and_reply,
|
||||
{shutdown, user_timeout},
|
||||
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
|
||||
index 8f25e5a3cd43..d87d6c15a224 100644
|
||||
--- a/lib/ssl/src/tls_connection.erl
|
||||
+++ b/lib/ssl/src/tls_connection.erl
|
||||
@@ -34,6 +34,7 @@
|
||||
%% ClientKeyExchange \
|
||||
%% CertificateVerify* Flight 3 part 1
|
||||
%% [ChangeCipherSpec] /
|
||||
+%% NextProtocol*
|
||||
%% Finished --------> / Flight 3 part 2
|
||||
%% [ChangeCipherSpec]
|
||||
%% <-------- Finished Flight 4
|
||||
@@ -48,6 +49,7 @@
|
||||
%% [ChangeCipherSpec]
|
||||
%% <-------- Finished Abbrev Flight 2 part 2
|
||||
%% [ChangeCipherSpec]
|
||||
+%% NextProtocol*
|
||||
%% Finished --------> Abbrev Flight 3
|
||||
%% Application Data <-------> Application Data
|
||||
%%
|
||||
@@ -70,13 +72,14 @@
|
||||
%% |
|
||||
%% New session | Resumed session
|
||||
%% WAIT_OCSP_STAPELING CERTIFY <----------------------------------> ABBRIVIATED
|
||||
-%%
|
||||
+%% WAIT_CERT_VERIFY
|
||||
%% <- Possibly Receive -- | |
|
||||
-%% OCSP Stapel ------> | Flight 3 part 1 |
|
||||
+%% OCSP Stapel/CertVerify -> | Flight 3 part 1 |
|
||||
%% | |
|
||||
%% V | Abbrev Flight 2 part 2 to Abbrev Flight 3
|
||||
%% CIPHER |
|
||||
%% | |
|
||||
+%% | |
|
||||
%% | Fligth 3 part 2 to Flight 4 |
|
||||
%% | |
|
||||
%% V V
|
||||
@@ -121,6 +124,7 @@
|
||||
user_hello/3,
|
||||
wait_ocsp_stapling/3,
|
||||
certify/3,
|
||||
+ wait_cert_verify/3,
|
||||
cipher/3,
|
||||
abbreviated/3,
|
||||
connection/3]).
|
||||
@@ -303,6 +307,19 @@ certify(info, Event, State) ->
|
||||
certify(Type, Event, State) ->
|
||||
tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
|
||||
|
||||
+
|
||||
+%%--------------------------------------------------------------------
|
||||
+-spec wait_cert_verify(gen_statem:event_type(), term(), #state{}) ->
|
||||
+ gen_statem:state_function_result().
|
||||
+%%--------------------------------------------------------------------
|
||||
+wait_cert_verify(info, Event, State) ->
|
||||
+ gen_info(Event, ?FUNCTION_NAME, State);
|
||||
+wait_cert_verify(Type, Event, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
|
||||
+ try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
|
||||
+ catch throw:#alert{} = Alert ->
|
||||
+ ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State)
|
||||
+ end.
|
||||
+
|
||||
%%--------------------------------------------------------------------
|
||||
-spec cipher(gen_statem:event_type(), term(), #state{}) ->
|
||||
gen_statem:state_function_result().
|
||||
diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl
|
||||
index 02c55f3941b6..7d659baea0e7 100644
|
||||
--- a/lib/ssl/src/tls_dtls_connection.erl
|
||||
+++ b/lib/ssl/src/tls_dtls_connection.erl
|
||||
@@ -54,6 +54,7 @@
|
||||
user_hello/3,
|
||||
abbreviated/3,
|
||||
certify/3,
|
||||
+ wait_cert_verify/3,
|
||||
wait_ocsp_stapling/3,
|
||||
cipher/3,
|
||||
connection/3,
|
||||
@@ -319,7 +320,7 @@ certify(internal, #certificate{asn1_certificates = []},
|
||||
ssl_options = #{verify := verify_peer,
|
||||
fail_if_no_peer_cert := false}} =
|
||||
State0) ->
|
||||
- Connection:next_event(?FUNCTION_NAME, no_record, State0#state{client_certificate_requested = false});
|
||||
+ Connection:next_event(?FUNCTION_NAME, no_record, State0#state{client_certificate_status = empty});
|
||||
certify(internal, #certificate{},
|
||||
#state{static_env = #static_env{role = server},
|
||||
connection_env = #connection_env{negotiated_version = Version},
|
||||
@@ -344,16 +345,21 @@ certify(internal, #certificate{asn1_certificates = [Peer|_]} = Cert,
|
||||
ocsp_stapling_state = #{ocsp_expect := Status} = OcspState},
|
||||
connection_env = #connection_env{
|
||||
negotiated_version = Version},
|
||||
- ssl_options = Opts} = State) when Status =/= staple ->
|
||||
+ ssl_options = Opts} = State0) when Status =/= staple ->
|
||||
OcspInfo = ocsp_info(OcspState, Opts, Peer),
|
||||
case ssl_handshake:certify(Cert, CertDbHandle, CertDbRef,
|
||||
Opts, CRLDbInfo, Role, Host,
|
||||
ensure_tls(Version), OcspInfo) of
|
||||
{PeerCert, PublicKeyInfo} ->
|
||||
- handle_peer_cert(Role, PeerCert, PublicKeyInfo,
|
||||
- State#state{client_certificate_requested = false}, Connection, []);
|
||||
+ State = case Role of
|
||||
+ server ->
|
||||
+ State0#state{client_certificate_status = needs_verifying};
|
||||
+ client ->
|
||||
+ State0
|
||||
+ end,
|
||||
+ handle_peer_cert(Role, PeerCert, PublicKeyInfo, State, Connection, []);
|
||||
#alert{} = Alert ->
|
||||
- ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State)
|
||||
+ ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State0)
|
||||
end;
|
||||
certify(internal, #server_key_exchange{exchange_keys = Keys},
|
||||
#state{static_env = #static_env{role = client,
|
||||
@@ -421,7 +427,7 @@ certify(internal, #certificate_request{},
|
||||
%% The client does not have a certificate and will send an empty reply, the server may fail
|
||||
%% or accept the connection by its own preference. No signature algorihms needed as there is
|
||||
%% no certificate to verify.
|
||||
- Connection:next_event(?FUNCTION_NAME, no_record, State#state{client_certificate_requested = true});
|
||||
+ Connection:next_event(?FUNCTION_NAME, no_record, State#state{client_certificate_status = requested});
|
||||
certify(internal, #certificate_request{} = CertRequest,
|
||||
#state{static_env = #static_env{role = client,
|
||||
protocol_cb = Connection},
|
||||
@@ -435,7 +441,7 @@ certify(internal, #certificate_request{} = CertRequest,
|
||||
ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State);
|
||||
NegotiatedHashSign ->
|
||||
Connection:next_event(?FUNCTION_NAME, no_record,
|
||||
- State#state{client_certificate_requested = true,
|
||||
+ State#state{client_certificate_status = requested,
|
||||
handshake_env = HsEnv#handshake_env{cert_hashsign_algorithm = NegotiatedHashSign}})
|
||||
end;
|
||||
%% PSK and RSA_PSK might bypass the Server-Key-Exchange
|
||||
@@ -514,14 +520,6 @@ certify(internal, #server_hello_done{},
|
||||
#alert{} = Alert ->
|
||||
ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State0)
|
||||
end;
|
||||
-certify(internal = Type, #client_key_exchange{} = Msg,
|
||||
- #state{static_env = #static_env{role = server},
|
||||
- client_certificate_requested = true,
|
||||
- connection_env = #connection_env{negotiated_version = Version},
|
||||
- ssl_options = #{fail_if_no_peer_cert := true}} = State) ->
|
||||
- %% We expect a certificate here
|
||||
- Alert = ?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE, {unexpected_msg, {Type, Msg}}),
|
||||
- ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State);
|
||||
certify(internal, #client_key_exchange{exchange_keys = Keys},
|
||||
State = #state{handshake_env = #handshake_env{kex_algorithm = KeyAlg},
|
||||
static_env = #static_env{protocol_cb = Connection},
|
||||
@@ -539,37 +537,53 @@ certify(Type, Event, State) ->
|
||||
ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State).
|
||||
|
||||
%%--------------------------------------------------------------------
|
||||
--spec cipher(gen_statem:event_type(),
|
||||
- #hello_request{} | #certificate_verify{} | #finished{} | term(),
|
||||
+-spec wait_cert_verify(gen_statem:event_type(),
|
||||
+ #hello_request{} | #certificate_verify{} | term(),
|
||||
#state{}) ->
|
||||
gen_statem:state_function_result().
|
||||
%%--------------------------------------------------------------------
|
||||
-cipher({call, From}, Msg, State) ->
|
||||
- handle_call(Msg, From, ?FUNCTION_NAME, State);
|
||||
-cipher(info, Msg, State) ->
|
||||
- handle_info(Msg, ?FUNCTION_NAME, State);
|
||||
-cipher(internal, #certificate_verify{signature = Signature,
|
||||
- hashsign_algorithm = CertHashSign},
|
||||
- #state{static_env = #static_env{role = server,
|
||||
- protocol_cb = Connection},
|
||||
- handshake_env = #handshake_env{tls_handshake_history = Hist,
|
||||
- kex_algorithm = KexAlg,
|
||||
- public_key_info = PubKeyInfo} = HsEnv,
|
||||
- connection_env = #connection_env{negotiated_version = Version},
|
||||
- session = #session{master_secret = MasterSecret}
|
||||
- } = State) ->
|
||||
+wait_cert_verify(internal, #certificate_verify{signature = Signature,
|
||||
+ hashsign_algorithm = CertHashSign},
|
||||
+ #state{static_env = #static_env{role = server,
|
||||
+ protocol_cb = Connection},
|
||||
+ client_certificate_status = needs_verifying,
|
||||
+ handshake_env = #handshake_env{tls_handshake_history = Hist,
|
||||
+ kex_algorithm = KexAlg,
|
||||
+ public_key_info = PubKeyInfo},
|
||||
+ connection_env = #connection_env{negotiated_version = Version},
|
||||
+ session = #session{master_secret = MasterSecret} = Session0
|
||||
+ } = State) ->
|
||||
|
||||
TLSVersion = ssl:tls_version(Version),
|
||||
- %% Use negotiated value if TLS-1.2 otherwhise return default
|
||||
+ %% Use negotiated value if TLS-1.2 otherwise return default
|
||||
HashSign = negotiated_hashsign(CertHashSign, KexAlg, PubKeyInfo, TLSVersion),
|
||||
case ssl_handshake:certificate_verify(Signature, PubKeyInfo,
|
||||
TLSVersion, HashSign, MasterSecret, Hist) of
|
||||
valid ->
|
||||
- Connection:next_event(?FUNCTION_NAME, no_record,
|
||||
- State#state{handshake_env = HsEnv#handshake_env{cert_hashsign_algorithm = HashSign}});
|
||||
+ Connection:next_event(cipher, no_record,
|
||||
+ State#state{client_certificate_status = verified,
|
||||
+ session = Session0#session{sign_alg = HashSign}});
|
||||
#alert{} = Alert ->
|
||||
- ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State)
|
||||
+ throw(Alert)
|
||||
end;
|
||||
+
|
||||
+wait_cert_verify(internal, #hello_request{}, _) ->
|
||||
+ keep_state_and_data;
|
||||
+wait_cert_verify(Type, Event, State) ->
|
||||
+ ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State).
|
||||
+
|
||||
+%%--------------------------------------------------------------------
|
||||
+-spec cipher(gen_statem:event_type(),
|
||||
+ #hello_request{} | #finished{} | term(),
|
||||
+ #state{}) ->
|
||||
+ gen_statem:state_function_result().
|
||||
+%%--------------------------------------------------------------------
|
||||
+cipher({call, From}, Msg, State) ->
|
||||
+ handle_call(Msg, From, ?FUNCTION_NAME, State);
|
||||
+cipher(info, Msg, State) ->
|
||||
+ handle_info(Msg, ?FUNCTION_NAME, State);
|
||||
+
|
||||
+
|
||||
%% client must send a next protocol message if we are expecting it
|
||||
cipher(internal, #finished{},
|
||||
#state{static_env = #static_env{role = server},
|
||||
@@ -609,6 +623,7 @@ cipher(internal, #next_protocol{selected_protocol = SelectedProtocol},
|
||||
Connection:next_event(?FUNCTION_NAME, no_record,
|
||||
State#state{handshake_env = HsEnv#handshake_env{negotiated_protocol = SelectedProtocol,
|
||||
expecting_next_protocol_negotiation = false}});
|
||||
+
|
||||
cipher(internal, #change_cipher_spec{type = <<1>>},
|
||||
#state{handshake_env = HsEnv,
|
||||
static_env = #static_env{protocol_cb = Connection},
|
||||
@@ -881,12 +896,12 @@ handle_peer_cert_key(_, _, _, _, State) ->
|
||||
certify_client(#state{static_env = #static_env{role = client,
|
||||
cert_db = CertDbHandle,
|
||||
cert_db_ref = CertDbRef},
|
||||
- client_certificate_requested = true,
|
||||
+ client_certificate_status = requested,
|
||||
session = #session{own_certificates = OwnCerts}}
|
||||
= State, Connection) ->
|
||||
Certificate = ssl_handshake:certificate(OwnCerts, CertDbHandle, CertDbRef, client),
|
||||
Connection:queue_handshake(Certificate, State);
|
||||
-certify_client(#state{client_certificate_requested = false} = State, _) ->
|
||||
+certify_client(#state{client_certificate_status = not_requested} = State, _) ->
|
||||
State.
|
||||
|
||||
verify_client_cert(#state{static_env = #static_env{role = client},
|
||||
@@ -894,7 +909,7 @@ verify_client_cert(#state{static_env = #static_env{role = client},
|
||||
cert_hashsign_algorithm = HashSign},
|
||||
connection_env = #connection_env{negotiated_version = Version,
|
||||
private_key = PrivateKey},
|
||||
- client_certificate_requested = true,
|
||||
+ client_certificate_status = requested,
|
||||
session = #session{master_secret = MasterSecret,
|
||||
own_certificates = OwnCerts}} = State, Connection) ->
|
||||
|
||||
@@ -907,7 +922,7 @@ verify_client_cert(#state{static_env = #static_env{role = client},
|
||||
#alert{} = Alert ->
|
||||
throw(Alert)
|
||||
end;
|
||||
-verify_client_cert(#state{client_certificate_requested = false} = State, _) ->
|
||||
+verify_client_cert(#state{client_certificate_status = not_requested} = State, _) ->
|
||||
State.
|
||||
|
||||
client_certify_and_key_exchange(#state{connection_env = #connection_env{negotiated_version = Version}} =
|
||||
@@ -917,7 +932,7 @@ client_certify_and_key_exchange(#state{connection_env = #connection_env{negotiat
|
||||
{State2, Actions} = finalize_handshake(State1, certify, Connection),
|
||||
State = State2#state{
|
||||
%% Reinitialize
|
||||
- client_certificate_requested = false},
|
||||
+ client_certificate_status = not_requested},
|
||||
Connection:next_event(cipher, no_record, State, Actions)
|
||||
catch
|
||||
throw:#alert{} = Alert ->
|
||||
@@ -936,8 +951,8 @@ server_certify_and_key_exchange(State0, Connection) ->
|
||||
|
||||
certify_client_key_exchange(#encrypted_premaster_secret{premaster_secret= EncPMS},
|
||||
#state{connection_env = #connection_env{private_key = Key},
|
||||
- handshake_env = #handshake_env{client_hello_version = {Major, Minor} = Version}}
|
||||
- = State, Connection) ->
|
||||
+ handshake_env = #handshake_env{client_hello_version = {Major, Minor} = Version},
|
||||
+ client_certificate_status = CCStatus} = State, Connection) ->
|
||||
FakeSecret = make_premaster_secret(Version, rsa),
|
||||
%% Countermeasure for Bleichenbacher attack always provide some kind of premaster secret
|
||||
%% and fail handshake later.RFC 5246 section 7.4.7.1.
|
||||
@@ -955,56 +970,74 @@ certify_client_key_exchange(#encrypted_premaster_secret{premaster_secret= EncPMS
|
||||
catch
|
||||
#alert{description = ?DECRYPT_ERROR} ->
|
||||
FakeSecret
|
||||
- end,
|
||||
- calculate_master_secret(PremasterSecret, State, Connection, certify, cipher);
|
||||
+ end,
|
||||
+ calculate_master_secret(PremasterSecret, State, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_diffie_hellman_public{dh_public = ClientPublicDhKey},
|
||||
#state{handshake_env = #handshake_env{diffie_hellman_params = #'DHParameter'{} = Params,
|
||||
- kex_keys = {_, ServerDhPrivateKey}}
|
||||
+ kex_keys = {_, ServerDhPrivateKey}},
|
||||
+ client_certificate_status = CCStatus
|
||||
} = State,
|
||||
Connection) ->
|
||||
PremasterSecret = ssl_handshake:premaster_secret(ClientPublicDhKey, ServerDhPrivateKey, Params),
|
||||
- calculate_master_secret(PremasterSecret, State, Connection, certify, cipher);
|
||||
+ calculate_master_secret(PremasterSecret, State, Connection, certify, client_kex_next_state(CCStatus));
|
||||
|
||||
certify_client_key_exchange(#client_ec_diffie_hellman_public{dh_public = ClientPublicEcDhPoint},
|
||||
- #state{handshake_env = #handshake_env{kex_keys = ECDHKey}} = State, Connection) ->
|
||||
+ #state{handshake_env = #handshake_env{kex_keys = ECDHKey},
|
||||
+ client_certificate_status = CCStatus
|
||||
+ } = State, Connection) ->
|
||||
PremasterSecret = ssl_handshake:premaster_secret(#'ECPoint'{point = ClientPublicEcDhPoint}, ECDHKey),
|
||||
- calculate_master_secret(PremasterSecret, State, Connection, certify, cipher);
|
||||
+ calculate_master_secret(PremasterSecret, State, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_psk_identity{} = ClientKey,
|
||||
#state{ssl_options =
|
||||
- #{user_lookup_fun := PSKLookup}} = State0,
|
||||
+ #{user_lookup_fun := PSKLookup},
|
||||
+ client_certificate_status = CCStatus
|
||||
+ } = State0,
|
||||
Connection) ->
|
||||
PremasterSecret = ssl_handshake:premaster_secret(ClientKey, PSKLookup),
|
||||
- calculate_master_secret(PremasterSecret, State0, Connection, certify, cipher);
|
||||
+ calculate_master_secret(PremasterSecret, State0, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_dhe_psk_identity{} = ClientKey,
|
||||
#state{handshake_env = #handshake_env{diffie_hellman_params = #'DHParameter'{} = Params,
|
||||
kex_keys = {_, ServerDhPrivateKey}},
|
||||
ssl_options =
|
||||
- #{user_lookup_fun := PSKLookup}} = State0,
|
||||
+ #{user_lookup_fun := PSKLookup},
|
||||
+ client_certificate_status = CCStatus
|
||||
+ } = State0,
|
||||
Connection) ->
|
||||
PremasterSecret =
|
||||
ssl_handshake:premaster_secret(ClientKey, ServerDhPrivateKey, Params, PSKLookup),
|
||||
- calculate_master_secret(PremasterSecret, State0, Connection, certify, cipher);
|
||||
+ calculate_master_secret(PremasterSecret, State0, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_ecdhe_psk_identity{} = ClientKey,
|
||||
#state{handshake_env = #handshake_env{kex_keys = ServerEcDhPrivateKey},
|
||||
ssl_options =
|
||||
- #{user_lookup_fun := PSKLookup}} = State,
|
||||
+ #{user_lookup_fun := PSKLookup},
|
||||
+ client_certificate_status = CCStatus
|
||||
+ } = State,
|
||||
Connection) ->
|
||||
PremasterSecret =
|
||||
ssl_handshake:premaster_secret(ClientKey, ServerEcDhPrivateKey, PSKLookup),
|
||||
- calculate_master_secret(PremasterSecret, State, Connection, certify, cipher);
|
||||
+ calculate_master_secret(PremasterSecret, State, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_rsa_psk_identity{} = ClientKey,
|
||||
- #state{connection_env = #connection_env{private_key = Key},
|
||||
+ #state{connection_env = #connection_env{private_key = PrivateKey},
|
||||
ssl_options =
|
||||
- #{user_lookup_fun := PSKLookup}} = State0,
|
||||
+ #{user_lookup_fun := PSKLookup},
|
||||
+ client_certificate_status = CCStatus} = State0,
|
||||
Connection) ->
|
||||
- PremasterSecret = ssl_handshake:premaster_secret(ClientKey, Key, PSKLookup),
|
||||
- calculate_master_secret(PremasterSecret, State0, Connection, certify, cipher);
|
||||
+ PremasterSecret = ssl_handshake:premaster_secret(ClientKey, PrivateKey, PSKLookup),
|
||||
+ calculate_master_secret(PremasterSecret, State0, Connection, certify, client_kex_next_state(CCStatus));
|
||||
certify_client_key_exchange(#client_srp_public{} = ClientKey,
|
||||
#state{handshake_env = #handshake_env{srp_params = Params,
|
||||
- kex_keys = Key}
|
||||
+ kex_keys = Key},
|
||||
+ client_certificate_status = CCStatus
|
||||
} = State0, Connection) ->
|
||||
PremasterSecret = ssl_handshake:premaster_secret(ClientKey, Key, Params),
|
||||
- calculate_master_secret(PremasterSecret, State0, Connection, certify, cipher).
|
||||
+ calculate_master_secret(PremasterSecret, State0, Connection, certify, client_kex_next_state(CCStatus)).
|
||||
+
|
||||
+client_kex_next_state(needs_verifying) ->
|
||||
+ wait_cert_verify;
|
||||
+client_kex_next_state(empty) ->
|
||||
+ cipher;
|
||||
+client_kex_next_state(not_requested) ->
|
||||
+ cipher.
|
||||
|
||||
certify_server(#state{handshake_env = #handshake_env{kex_algorithm = KexAlg}} =
|
||||
State, _) when KexAlg == dh_anon;
|
||||
@@ -1334,7 +1367,7 @@ request_client_cert(#state{static_env = #static_env{cert_db = CertDbHandle,
|
||||
Msg = ssl_handshake:certificate_request(CipherSuite, CertDbHandle, CertDbRef,
|
||||
HashSigns, TLSVersion),
|
||||
State = Connection:queue_handshake(Msg, State0),
|
||||
- State#state{client_certificate_requested = true};
|
||||
+ State#state{client_certificate_status = requested};
|
||||
|
||||
request_client_cert(#state{ssl_options = #{verify := verify_none}} =
|
||||
State, _) ->
|
||||
diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl
|
||||
index 5da87e79d6be..37106ea6ff21 100644
|
||||
--- a/lib/ssl/src/tls_gen_connection.erl
|
||||
+++ b/lib/ssl/src/tls_gen_connection.erl
|
||||
@@ -349,7 +349,28 @@ next_event(StateName, #alert{} = Alert, State, Actions) ->
|
||||
{next_state, StateName, State, [{next_event, internal, Alert} | Actions]}.
|
||||
|
||||
%%% TLS record protocol level application data messages
|
||||
-handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, StateName,
|
||||
+handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA}, StateName,
|
||||
+ #state{static_env = #static_env{role = server},
|
||||
+ connection_env = #connection_env{negotiated_version = Version},
|
||||
+ handshake_env = #handshake_env{renegotiation = {false, first}}
|
||||
+ } = State) when StateName == initial_hello;
|
||||
+ StateName == hello;
|
||||
+ StateName == certify;
|
||||
+ StateName == wait_cert_verify;
|
||||
+ StateName == wait_ocsp_stapling;
|
||||
+ StateName == abbreviated;
|
||||
+ StateName == cipher
|
||||
+ ->
|
||||
+ %% Application data can not be sent before initial handshake pre TLS-1.3.
|
||||
+ Alert = ?ALERT_REC(?FATAL, ?UNEXPECTED_MESSAGE, application_data_before_initial_handshake),
|
||||
+ ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State);
|
||||
+handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA}, start = StateName,
|
||||
+ #state{static_env = #static_env{role = server},
|
||||
+ connection_env = #connection_env{negotiated_version = Version}
|
||||
+ } = State) ->
|
||||
+ Alert = ?ALERT_REC(?FATAL, ?DECODE_ERROR, invalid_tls_13_message),
|
||||
+ ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State);
|
||||
+handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, StateName,
|
||||
#state{start_or_recv_from = From,
|
||||
socket_options = #socket_options{active = false}} = State0) when From =/= undefined ->
|
||||
case ssl_gen_statem:read_application_data(Data, State0) of
|
||||
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
|
||||
index a6014739c681..7fd1b8767201 100644
|
||||
--- a/lib/ssl/src/tls_handshake_1_3.erl
|
||||
+++ b/lib/ssl/src/tls_handshake_1_3.erl
|
||||
@@ -1187,7 +1187,7 @@ maybe_append_change_cipher_spec(#state{
|
||||
maybe_append_change_cipher_spec(State, Bin) ->
|
||||
{State, Bin}.
|
||||
|
||||
-maybe_queue_cert_cert_cv(#state{client_certificate_requested = false} = State) ->
|
||||
+maybe_queue_cert_cert_cv(#state{client_certificate_status = not_requested} = State) ->
|
||||
{ok, State};
|
||||
maybe_queue_cert_cert_cv(#state{connection_states = _ConnectionStates0,
|
||||
session = #session{session_id = _SessionId,
|
||||
@@ -1408,7 +1408,7 @@ create_change_cipher_spec(#state{ssl_options = #{log_level := LogLevel}}) ->
|
||||
|
||||
process_certificate_request(#certificate_request_1_3{},
|
||||
#state{session = #session{own_certificates = undefined}} = State) ->
|
||||
- {ok, {State#state{client_certificate_requested = true}, wait_cert}};
|
||||
+ {ok, {State#state{client_certificate_status = requested}, wait_cert}};
|
||||
|
||||
process_certificate_request(#certificate_request_1_3{
|
||||
extensions = Extensions},
|
||||
@@ -1427,11 +1427,11 @@ process_certificate_request(#certificate_request_1_3{
|
||||
%% Check if server supports signature algorithm of client certificate
|
||||
case check_cert_sign_algo(SignAlgo, SignHash, ServerSignAlgs, ServerSignAlgsCert) of
|
||||
ok ->
|
||||
- {ok, {State#state{client_certificate_requested = true,
|
||||
+ {ok, {State#state{client_certificate_status = requested,
|
||||
session = Session#session{sign_alg = SelectedSignAlg}}, wait_cert}};
|
||||
{error, _} ->
|
||||
%% Certificate not supported: send empty certificate in state 'wait_finished'
|
||||
- {ok, {State#state{client_certificate_requested = true,
|
||||
+ {ok, {State#state{client_certificate_status = requested,
|
||||
session = Session#session{own_certificates = undefined}}, wait_cert}}
|
||||
end
|
||||
catch
|
||||
diff --git a/lib/ssl/test/ssl_npn_SUITE.erl b/lib/ssl/test/ssl_npn_SUITE.erl
|
||||
index 81c75ecff04a..914563b782ed 100644
|
||||
--- a/lib/ssl/test/ssl_npn_SUITE.erl
|
||||
+++ b/lib/ssl/test/ssl_npn_SUITE.erl
|
||||
@@ -68,14 +68,18 @@
|
||||
all() ->
|
||||
[{group, 'tlsv1.2'},
|
||||
{group, 'tlsv1.1'},
|
||||
- {group, 'tlsv1'}
|
||||
+ {group, 'tlsv1'},
|
||||
+ {group, 'dtlsv1.2'},
|
||||
+ {group, 'dtlsv1'}
|
||||
].
|
||||
|
||||
groups() ->
|
||||
[
|
||||
{'tlsv1.2', [], next_protocol_tests()},
|
||||
{'tlsv1.1', [], next_protocol_tests()},
|
||||
- {'tlsv1', [], next_protocol_tests()}
|
||||
+ {'tlsv1', [], next_protocol_tests()},
|
||||
+ {'dtlsv1.2', [], next_protocol_tests()},
|
||||
+ {'dtlsv1', [], next_protocol_tests()}
|
||||
].
|
||||
|
||||
next_protocol_tests() ->
|
||||
825
CVE-2023-48795-erlang23.patch
Normal file
825
CVE-2023-48795-erlang23.patch
Normal file
@ -0,0 +1,825 @@
|
||||
From ee67d46285394db95133709cef74b0c462d665aa Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
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 | 12 ++-
|
||||
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 ++++----
|
||||
8 files changed, 335 insertions(+), 66 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
|
||||
index e37a14a..7df6d4d 100644
|
||||
--- a/lib/ssh/src/ssh.hrl
|
||||
+++ b/lib/ssh/src/ssh.hrl
|
||||
@@ -431,6 +431,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
|
||||
@@ -502,7 +504,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 625f177..8e8c082 100644
|
||||
--- a/lib/ssh/src/ssh_connection_handler.erl
|
||||
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
||||
@@ -741,7 +741,7 @@ handle_event(_, no_hello_received, {hello,_Role}=StateName, D0) ->
|
||||
handle_event(_, {#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 ->
|
||||
send_bytes(NextKexMsg, D),
|
||||
Ssh2;
|
||||
@@ -1114,6 +1114,16 @@ handle_event(_, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D0) ->
|
||||
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(_, #ssh_msg_ignore{}, _, _) ->
|
||||
keep_state_and_data;
|
||||
|
||||
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
|
||||
index 9bbd8b9..8e17dae 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,
|
||||
@@ -213,7 +213,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}]},
|
||||
@@ -221,6 +220,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}]},
|
||||
@@ -336,7 +336,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),
|
||||
@@ -364,10 +365,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 ->
|
||||
@@ -380,10 +383,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 ->
|
||||
@@ -459,6 +464,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
|
||||
@@ -821,6 +841,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) ->
|
||||
@@ -1029,7 +1052,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),
|
||||
|
||||
@@ -1080,7 +1131,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
|
||||
}}.
|
||||
|
||||
|
||||
@@ -1178,7 +1230,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) ->
|
||||
@@ -1190,22 +1243,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),
|
||||
@@ -2161,6 +2215,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
|
||||
@@ -2187,14 +2249,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);
|
||||
@@ -2217,9 +2279,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 f424a4f..59ac9db 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 ab854e4..ecdc74b 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,
|
||||
@@ -134,8 +137,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,
|
||||
@@ -160,17 +165,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 ;
|
||||
@@ -213,6 +217,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 ;
|
||||
@@ -814,6 +820,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.
|
||||
|
||||
%%%----------------------------------------------------------------
|
||||
%%%
|
||||
@@ -835,7 +915,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}
|
||||
@@ -849,7 +929,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}
|
||||
@@ -863,7 +943,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}
|
||||
@@ -882,7 +962,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 fb7365e..c20acdf 100644
|
||||
--- a/lib/ssh/test/ssh_test_lib.erl
|
||||
+++ b/lib/ssh/test/ssh_test_lib.erl
|
||||
@@ -120,7 +120,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").
|
||||
@@ -1227,3 +1231,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 96072cb..f677a87 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,
|
||||
@@ -74,12 +77,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", 22, []) of
|
||||
+ case gen_tcp:connect("localhost", 22, [{active, false}]) of
|
||||
{error,econnrefused} ->
|
||||
- {skip,"No openssh deamon (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
|
||||
@@ -233,6 +255,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),
|
||||
@@ -258,9 +299,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))
|
||||
],
|
||||
@@ -278,15 +319,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.
|
||||
|
||||
%%--------------------------------------------------------------------
|
||||
@@ -571,3 +611,17 @@ no_forwarding() ->
|
||||
"---- 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 eea392b..80c570a 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("Algoritm 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;
|
||||
--
|
||||
2.33.0
|
||||
|
||||
89
CVE-2025-26618.patch
Normal file
89
CVE-2025-26618.patch
Normal file
@ -0,0 +1,89 @@
|
||||
From 0ed2573cbd55c92e9125c9dc70fa1ca7fed82872 Mon Sep 17 00:00:00 2001
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
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, <<?UINT32(Len), Msg:Len/binary, Rest/binary>>,
|
||||
+handle_data(0, ChannelId, <<?UINT32(Len), Msg:Len/binary, Rest/binary>>,
|
||||
State = #state{pending = <<>>}) ->
|
||||
<<Op, ?UINT32(ReqId), Data/binary>> = 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, <<Pending/binary, Data/binary>>,
|
||||
- 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 = <<Pending/binary, Data0/binary>>,
|
||||
+ 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]),
|
||||
59
CVE-2025-30211-1.patch
Normal file
59
CVE-2025-30211-1.patch
Normal file
@ -0,0 +1,59 @@
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Fri, 21 Mar 2025 12:17:07 +0100
|
||||
Subject: [PATCH] ssh: ignore too long names
|
||||
|
||||
origin: backport, https://github.com/erlang/otp/commit/655e20a49ef80431e86ffb6c7f366d01fd4b64c3
|
||||
bug: https://github.com/erlang/otp/security/advisories/GHSA-vvr3-fjhh-cfwc
|
||||
bug-debian: https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=1101713
|
||||
|
||||
[backport]
|
||||
Drop CVE-2025-30211-1.patch from bookworm that does not apply and is cosmetic
|
||||
---
|
||||
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 fab9c50..b78d755 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").
|
||||
@@ -37,6 +38,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) ->
|
||||
@@ -727,8 +729,22 @@ decode_kex_init(<<?BYTE(Bool)>>, Acc, 0) ->
|
||||
X = 0,
|
||||
list_to_tuple(lists:reverse([X, erl_boolean(Bool) | Acc]));
|
||||
decode_kex_init(<<?DEC_BIN(Data,__0), Rest/binary>>, Acc, N) ->
|
||||
- Names = string:tokens(?unicode_list(Data), ","),
|
||||
- decode_kex_init(Rest, [Names | Acc], N -1).
|
||||
+ BinParts = binary:split(Data, <<$,>>, [global]),
|
||||
+ Process =
|
||||
+ fun(<<>>, PAcc) ->
|
||||
+ PAcc;
|
||||
+ (Part, PAcc) ->
|
||||
+ case byte_size(Part) > ?ALG_NAME_LIMIT of
|
||||
+ true ->
|
||||
+ ?LOG_DEBUG("Ignoring too long name", []),
|
||||
+ PAcc;
|
||||
+ false ->
|
||||
+ Name = binary:bin_to_list(Part),
|
||||
+ [Name | PAcc]
|
||||
+ end
|
||||
+ end,
|
||||
+ Names = lists:foldr(Process, [], BinParts),
|
||||
+ decode_kex_init(Rest, [Names | Acc], N - 1).
|
||||
|
||||
|
||||
%%%================================================================
|
||||
37
CVE-2025-30211-2.patch
Normal file
37
CVE-2025-30211-2.patch
Normal file
@ -0,0 +1,37 @@
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Fri, 21 Mar 2025 17:50:21 +0100
|
||||
Subject: [PATCH] ssh: use chars_limit for bad packets error messages
|
||||
|
||||
origin: backport, https://github.com/erlang/otp/commit/d64d9fb0688092356a336e38a8717499113312a0
|
||||
bug: https://github.com/erlang/otp/security/advisories/GHSA-vvr3-fjhh-cfwc
|
||||
bug-debian: https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=1101713
|
||||
---
|
||||
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 b8c89b8..b8eb798 100644
|
||||
--- a/lib/ssh/src/ssh_connection_handler.erl
|
||||
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
||||
@@ -1554,8 +1554,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;
|
||||
@@ -1589,8 +1589,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;
|
||||
140
CVE-2025-30211-3.patch
Normal file
140
CVE-2025-30211-3.patch
Normal file
@ -0,0 +1,140 @@
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Mon, 24 Mar 2025 11:31:39 +0100
|
||||
Subject: [PATCH] ssh: custom_kexinit test added
|
||||
|
||||
origin: backport, https://github.com/erlang/otp/commit/5ee26eb412a76ba1c6afdf4524b62939a48d1bce
|
||||
bug: https://github.com/erlang/otp/security/advisories/GHSA-vvr3-fjhh-cfwc
|
||||
bug-debian: https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=1101713
|
||||
---
|
||||
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 a73d54b..76fdbad 100644
|
||||
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
@@ -69,6 +69,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,
|
||||
@@ -130,7 +131,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,
|
||||
@@ -169,7 +171,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}
|
||||
]}]);
|
||||
@@ -215,7 +217,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;
|
||||
@@ -376,6 +378,88 @@ no_common_alg_server_disconnects(Config) ->
|
||||
]
|
||||
).
|
||||
|
||||
+custom_kexinit(Config) ->
|
||||
+ %% 16#C0 value causes unicode:characters_to_list to return a big error value
|
||||
+ Trash = lists:duplicate(260_000, 16#C0),
|
||||
+ FunnyAlg = "curve25519-sha256",
|
||||
+ KexInit =
|
||||
+ #ssh_msg_kexinit{cookie = <<"Ã/Ï!9zñKá:ñÀv¿JÜ">>,
|
||||
+ kex_algorithms =
|
||||
+ [FunnyAlg ++ Trash],
|
||||
+ server_host_key_algorithms = ["ssh-rsa"],
|
||||
+ encryption_algorithms_client_to_server =
|
||||
+ ["aes256-ctr","aes192-ctr","aes128-ctr","aes128-cbc","3des-cbc"],
|
||||
+ encryption_algorithms_server_to_client =
|
||||
+ ["aes256-ctr","aes192-ctr","aes128-ctr","aes128-cbc","3des-cbc"],
|
||||
+ mac_algorithms_client_to_server =
|
||||
+ ["hmac-sha2-512-etm@openssh.com","hmac-sha2-256-etm@openssh.com",
|
||||
+ "hmac-sha2-512","hmac-sha2-256","hmac-sha1-etm@openssh.com","hmac-sha1"],
|
||||
+ mac_algorithms_server_to_client =
|
||||
+ ["hmac-sha2-512-etm@openssh.com","hmac-sha2-256-etm@openssh.com",
|
||||
+ "hmac-sha2-512","hmac-sha2-256","hmac-sha1-etm@openssh.com","hmac-sha1"],
|
||||
+ compression_algorithms_client_to_server = ["none","zlib@openssh.com","zlib"],
|
||||
+ compression_algorithms_server_to_client = ["none","zlib@openssh.com","zlib"],
|
||||
+ languages_client_to_server = [],
|
||||
+ languages_server_to_client = [],
|
||||
+ first_kex_packet_follows = false,
|
||||
+ reserved = 0
|
||||
+ },
|
||||
+ PacketFun =
|
||||
+ fun(Msg, Ssh) ->
|
||||
+ BinMsg = custom_encode(Msg),
|
||||
+ ssh_transport:pack(BinMsg, Ssh, 0)
|
||||
+ end,
|
||||
+ {ok,_} =
|
||||
+ ssh_trpt_test_lib:exec(
|
||||
+ [{set_options, [print_ops, {print_messages,detail}]},
|
||||
+ {connect,
|
||||
+ server_host(Config),server_port(Config),
|
||||
+ [{silently_accept_hosts, true},
|
||||
+ {user_dir, user_dir(Config)},
|
||||
+ {user_interaction, false},
|
||||
+ {preferred_algorithms,[{public_key,['ssh-rsa']},
|
||||
+ {cipher,?DEFAULT_CIPHERS}
|
||||
+ ]}
|
||||
+ ]},
|
||||
+ receive_hello,
|
||||
+ {send, hello},
|
||||
+ {match, #ssh_msg_kexinit{_='_'}, receive_msg},
|
||||
+ {send, {special, KexInit, PacketFun}}, % with server unsupported 'ssh-dss' !
|
||||
+ {match, disconnect(), receive_msg}
|
||||
+ ]
|
||||
+ ).
|
||||
+
|
||||
+custom_encode(#ssh_msg_kexinit{
|
||||
+ cookie = Cookie,
|
||||
+ kex_algorithms = KeyAlgs,
|
||||
+ server_host_key_algorithms = HostKeyAlgs,
|
||||
+ encryption_algorithms_client_to_server = EncAlgC2S,
|
||||
+ encryption_algorithms_server_to_client = EncAlgS2C,
|
||||
+ mac_algorithms_client_to_server = MacAlgC2S,
|
||||
+ mac_algorithms_server_to_client = MacAlgS2C,
|
||||
+ compression_algorithms_client_to_server = CompAlgS2C,
|
||||
+ compression_algorithms_server_to_client = CompAlgC2S,
|
||||
+ languages_client_to_server = LangC2S,
|
||||
+ languages_server_to_client = LangS2C,
|
||||
+ first_kex_packet_follows = Bool,
|
||||
+ reserved = Reserved
|
||||
+ }) ->
|
||||
+ KeyAlgsBin0 = <<?Ename_list(KeyAlgs)>>,
|
||||
+ <<?UINT32(Len0), Data:Len0/binary>> = KeyAlgsBin0,
|
||||
+ KeyAlgsBin = <<?UINT32(Len0), Data/binary>>,
|
||||
+ <<?Ebyte(?SSH_MSG_KEXINIT), Cookie/binary,
|
||||
+ KeyAlgsBin/binary,
|
||||
+ ?Ename_list(HostKeyAlgs),
|
||||
+ ?Ename_list(EncAlgC2S),
|
||||
+ ?Ename_list(EncAlgS2C),
|
||||
+ ?Ename_list(MacAlgC2S),
|
||||
+ ?Ename_list(MacAlgS2C),
|
||||
+ ?Ename_list(CompAlgS2C),
|
||||
+ ?Ename_list(CompAlgC2S),
|
||||
+ ?Ename_list(LangC2S),
|
||||
+ ?Ename_list(LangS2C),
|
||||
+ ?Eboolean(Bool), ?Euint32(Reserved)>>.
|
||||
+
|
||||
%%--------------------------------------------------------------------
|
||||
%%% Algo negotiation fail. This should result in a ssh_msg_disconnect
|
||||
%%% being sent from the client.
|
||||
57
CVE-2025-30211-pre1.patch
Normal file
57
CVE-2025-30211-pre1.patch
Normal file
@ -0,0 +1,57 @@
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
Date: Fri, 27 Jan 2023 17:13:31 +0100
|
||||
Subject: [PATCH] ssh: reduce log length
|
||||
|
||||
origin: backport, https://github.com/erlang/otp/commit/e93e40cf8150539338e7320b9fd9bad825b0a6d0
|
||||
bug: https://github.com/erlang/otp/security/advisories/GHSA-vvr3-fjhh-cfwc
|
||||
bug-debian: https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=1101713
|
||||
---
|
||||
lib/ssh/src/ssh_connection_handler.erl | 19 ++++++++++++-------
|
||||
1 file changed, 12 insertions(+), 7 deletions(-)
|
||||
|
||||
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
|
||||
index 53b7d5c..b8c89b8 100644
|
||||
--- a/lib/ssh/src/ssh_connection_handler.erl
|
||||
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
||||
@@ -1504,8 +1504,10 @@ handle_event(info, {Proto, Sock, Info}, {hello,_}, #data{socket = Sock,
|
||||
end;
|
||||
|
||||
|
||||
-handle_event(info, {Proto, Sock, NewData}, StateName, D0 = #data{socket = Sock,
|
||||
- transport_protocol = Proto}) ->
|
||||
+handle_event(info, {Proto, Sock, NewData}, StateName,
|
||||
+ D0 = #data{socket = Sock,
|
||||
+ transport_protocol = Proto,
|
||||
+ ssh_params = SshParams}) ->
|
||||
try ssh_transport:handle_packet_part(
|
||||
D0#data.decrypted_data_buffer,
|
||||
<<(D0#data.encrypted_data_buffer)/binary, NewData/binary>>,
|
||||
@@ -1549,10 +1551,11 @@ handle_event(info, {Proto, Sock, NewData}, StateName, D0 = #data{socket = Sock,
|
||||
]}
|
||||
catch
|
||||
C:E:ST ->
|
||||
- {Shutdown, D} =
|
||||
+ 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]),
|
||||
+ io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~P",
|
||||
+ [C,E,ST,MaxLogItemLen]),
|
||||
StateName, D1),
|
||||
{stop, Shutdown, D}
|
||||
end;
|
||||
@@ -1583,9 +1586,11 @@ handle_event(info, {Proto, Sock, NewData}, StateName, D0 = #data{socket = Sock,
|
||||
{stop, Shutdown, D}
|
||||
catch
|
||||
C:E:ST ->
|
||||
- {Shutdown, D} =
|
||||
+ 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]),
|
||||
+ io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~P",
|
||||
+ [C,E,ST,MaxLogItemLen]),
|
||||
StateName, D0),
|
||||
{stop, Shutdown, D}
|
||||
end;
|
||||
221
CVE-2025-32433.patch
Normal file
221
CVE-2025-32433.patch
Normal file
@ -0,0 +1,221 @@
|
||||
From: Jakub Witczak <kuba@erlang.org>
|
||||
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
|
||||
|
||||
origin: https://github.com/erlang/otp/commit/0fcd9c56524b28615e8ece65fc0c3f66ef6e4c12
|
||||
bug: https://github.com/erlang/otp/security/advisories/GHSA-37cp-fgq5-7wc2
|
||||
bug-debian: https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=1103442
|
||||
---
|
||||
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 a966f7b..3a607a5 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,
|
||||
@@ -973,12 +994,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 76fdbad..18f5441 100644
|
||||
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
|
||||
@@ -70,6 +70,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,
|
||||
@@ -110,6 +111,7 @@ suite() ->
|
||||
all() ->
|
||||
[{group,tool_tests},
|
||||
client_info_line,
|
||||
+ early_rce,
|
||||
{group,kex},
|
||||
{group,service_requests},
|
||||
{group,authentication},
|
||||
@@ -127,10 +129,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,
|
||||
@@ -171,7 +171,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}
|
||||
]}]);
|
||||
@@ -217,7 +218,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;
|
||||
@@ -378,6 +380,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 = <<?STRING(<<"lists:seq(1,10).">>)>>,
|
||||
+ 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),
|
||||
@@ -404,11 +444,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}]},
|
||||
@@ -424,42 +459,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 = <<?Ename_list(KeyAlgs)>>,
|
||||
- <<?UINT32(Len0), Data:Len0/binary>> = KeyAlgsBin0,
|
||||
- KeyAlgsBin = <<?UINT32(Len0), Data/binary>>,
|
||||
- <<?Ebyte(?SSH_MSG_KEXINIT), Cookie/binary,
|
||||
- KeyAlgsBin/binary,
|
||||
- ?Ename_list(HostKeyAlgs),
|
||||
- ?Ename_list(EncAlgC2S),
|
||||
- ?Ename_list(EncAlgS2C),
|
||||
- ?Ename_list(MacAlgC2S),
|
||||
- ?Ename_list(MacAlgS2C),
|
||||
- ?Ename_list(CompAlgS2C),
|
||||
- ?Ename_list(CompAlgC2S),
|
||||
- ?Ename_list(LangC2S),
|
||||
- ?Ename_list(LangS2C),
|
||||
- ?Eboolean(Bool), ?Euint32(Reserved)>>.
|
||||
-
|
||||
%%--------------------------------------------------------------------
|
||||
%%% Algo negotiation fail. This should result in a ssh_msg_disconnect
|
||||
%%% being sent from the client.
|
||||
25
epmd.service
Normal file
25
epmd.service
Normal file
@ -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
|
||||
|
||||
10
epmd.socket
Normal file
10
epmd.socket
Normal file
@ -0,0 +1,10 @@
|
||||
[Unit]
|
||||
Description=Erlang Port Mapper Daemon Activation Socket
|
||||
|
||||
[Socket]
|
||||
ListenStream=4369
|
||||
Accept=false
|
||||
|
||||
[Install]
|
||||
WantedBy=sockets.target
|
||||
|
||||
25
epmd@.service
Normal file
25
epmd@.service
Normal file
@ -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
|
||||
|
||||
10
epmd@.socket
Normal file
10
epmd@.socket
Normal file
@ -0,0 +1,10 @@
|
||||
[Unit]
|
||||
Description=Erlang Port Mapper Daemon Activation Socket
|
||||
|
||||
[Socket]
|
||||
ListenStream=%I
|
||||
Accept=false
|
||||
|
||||
[Install]
|
||||
WantedBy=sockets.target
|
||||
|
||||
1839
erlang.spec
Normal file
1839
erlang.spec
Normal file
File diff suppressed because it is too large
Load Diff
@ -0,0 +1,41 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
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 <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/erts/etc/common/Makefile.in b/erts/etc/common/Makefile.in
|
||||
index 7a2b821c46..f5f3ee69cb 100644
|
||||
--- a/erts/etc/common/Makefile.in
|
||||
+++ b/erts/etc/common/Makefile.in
|
||||
@@ -528,10 +528,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 2dbf628972..5151f5130a 100644
|
||||
--- a/erts/etc/unix/Install.src
|
||||
+++ b/erts/etc/unix/Install.src
|
||||
@@ -142,14 +142,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
|
||||
32
otp-0002-Remove-rpath.patch
Normal file
32
otp-0002-Remove-rpath.patch
Normal file
@ -0,0 +1,32 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
Date: Thu, 25 Feb 2010 16:57:43 +0300
|
||||
Subject: [PATCH] Remove rpath
|
||||
|
||||
Signed-off-by: Peter Lemenkov <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/lib/crypto/c_src/Makefile.in b/lib/crypto/c_src/Makefile.in
|
||||
index 0821bd8d00..c94f01420e 100644
|
||||
--- a/lib/crypto/c_src/Makefile.in
|
||||
+++ b/lib/crypto/c_src/Makefile.in
|
||||
@@ -126,7 +126,7 @@ TEST_ENGINE_LIB = $(LIBDIR)/otp_test_engine$(TYPEMARKER).@DED_EXT@
|
||||
DYNAMIC_CRYPTO_LIB=@SSL_DYNAMIC_ONLY@
|
||||
|
||||
ifeq ($(DYNAMIC_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/lib/crypto/priv/Makefile b/lib/crypto/priv/Makefile
|
||||
index ff9d3e1dc9..d3aba77808 100644
|
||||
--- a/lib/crypto/priv/Makefile
|
||||
+++ b/lib/crypto/priv/Makefile
|
||||
@@ -61,7 +61,7 @@ OBJS = $(OBJDIR)/crypto.o
|
||||
# ----------------------------------------------------
|
||||
|
||||
$(SO_NIFLIB): $(OBJS)
|
||||
- $(SO_LD) $(SO_LDFLAGS) -L$(SO_SSL_LIBDIR) -Wl,-R$(SO_SSL_LIBDIR) \
|
||||
+ $(SO_LD) $(SO_LDFLAGS) -L$(SO_SSL_LIBDIR) \
|
||||
-o $@ $^ -lcrypto
|
||||
|
||||
$(DLL_NIFLIB): $(OBJS)
|
||||
130
otp-0003-Do-not-install-C-sources.patch
Normal file
130
otp-0003-Do-not-install-C-sources.patch
Normal file
@ -0,0 +1,130 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
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 <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/lib/asn1/c_src/Makefile b/lib/asn1/c_src/Makefile
|
||||
index cb606fd74e..48a7c2f4f1 100644
|
||||
--- a/lib/asn1/c_src/Makefile
|
||||
+++ b/lib/asn1/c_src/Makefile
|
||||
@@ -136,8 +136,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/crypto/c_src/Makefile.in b/lib/crypto/c_src/Makefile.in
|
||||
index c94f01420e..e2cae1692f 100644
|
||||
--- a/lib/crypto/c_src/Makefile.in
|
||||
+++ b/lib/crypto/c_src/Makefile.in
|
||||
@@ -237,16 +237,11 @@ docs:
|
||||
include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
- $(INSTALL_DIR) "$(RELSYSDIR)/priv/obj"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/priv/lib"
|
||||
- $(INSTALL_DATA) $(NIF_MAKEFILE) "$(RELSYSDIR)/priv/obj"
|
||||
- $(INSTALL_PROGRAM) $(CRYPTO_OBJS) "$(RELSYSDIR)/priv/obj"
|
||||
$(INSTALL_PROGRAM) $(NIF_LIB) "$(RELSYSDIR)/priv/lib"
|
||||
ifeq ($(DYNAMIC_CRYPTO_LIB),yes)
|
||||
- $(INSTALL_PROGRAM) $(CALLBACK_OBJS) "$(RELSYSDIR)/priv/obj"
|
||||
$(INSTALL_PROGRAM) $(CALLBACK_LIB) "$(RELSYSDIR)/priv/lib"
|
||||
endif
|
||||
- $(INSTALL_PROGRAM) $(TEST_ENGINE_OBJS) "$(RELSYSDIR)/priv/obj"
|
||||
$(INSTALL_PROGRAM) $(TEST_ENGINE_LIB) "$(RELSYSDIR)/priv/lib"
|
||||
|
||||
release_docs_spec:
|
||||
diff --git a/lib/erl_interface/src/Makefile.in b/lib/erl_interface/src/Makefile.in
|
||||
index 7ff3f09abb..2b94ce7de0 100644
|
||||
--- a/lib/erl_interface/src/Makefile.in
|
||||
+++ b/lib/erl_interface/src/Makefile.in
|
||||
@@ -748,14 +748,13 @@ release: opt
|
||||
$(INSTALL_DATA) $(OBJ_TARGETS) "$(RELEASE_PATH)/usr/lib"
|
||||
$(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) registry/*.[ch] "$(RELSYSDIR)/src/registry"
|
||||
- $(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"
|
||||
+ $(INSTALL_DATA) registry/*.h "$(RELSYSDIR)/src/registry"
|
||||
+ $(INSTALL_DATA) prog/*.h "$(RELSYSDIR)/src/prog"
|
||||
|
||||
release_docs:
|
||||
|
||||
diff --git a/lib/megaco/src/flex/Makefile.in b/lib/megaco/src/flex/Makefile.in
|
||||
index cd409fa54f..c65e817385 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 3c16e7e294..82fe1492ef 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/lib/tools/c_src/Makefile.in b/lib/tools/c_src/Makefile.in
|
||||
index 8e13571786..ae18ef3cf4 100644
|
||||
--- a/lib/tools/c_src/Makefile.in
|
||||
+++ b/lib/tools/c_src/Makefile.in
|
||||
@@ -188,8 +188,6 @@ include ../vsn.mk
|
||||
RELSYSDIR = $(RELEASE_PATH)/lib/tools-$(TOOLS_VSN)
|
||||
|
||||
release_spec: all
|
||||
- $(INSTALL_DIR) "$(RELSYSDIR)/c_src"
|
||||
- $(INSTALL_DATA) $(EMEM_SRCS) $(EMEM_HEADERS) "$(RELSYSDIR)/c_src"
|
||||
ifneq ($(PROGS),)
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/bin"
|
||||
$(INSTALL_PROGRAM) $(PROGS) "$(RELSYSDIR)/bin"
|
||||
19
otp-0004-Do-not-install-Java-sources.patch
Normal file
19
otp-0004-Do-not-install-Java-sources.patch
Normal file
@ -0,0 +1,19 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
Date: Sat, 19 Jun 2010 09:25:18 +0400
|
||||
Subject: [PATCH] Do not install Java sources
|
||||
|
||||
Signed-off-by: Peter Lemenkov <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile b/lib/jinterface/java_src/com/ericsson/otp/erlang/Makefile
|
||||
index bcbb206db6..1451378b35 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"
|
||||
@ -0,0 +1,60 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
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 <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/lib/os_mon/doc/src/Makefile b/lib/os_mon/doc/src/Makefile
|
||||
index d16f2b4831..c5b721f995 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 98c5ced068..e2f4d5a090 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);' $< > $@
|
||||
774
otp-0006-Do-not-install-erlang-sources.patch
Normal file
774
otp-0006-Do-not-install-erlang-sources.patch
Normal file
@ -0,0 +1,774 @@
|
||||
From: Hans Ulrich Niedermann <hun@n-dimensional.de>
|
||||
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 <lemenkov@gmail.com>
|
||||
Signed-off-by: Hans Ulrich Niedermann <hun@n-dimensional.de>
|
||||
|
||||
diff --git a/erts/preloaded/src/Makefile b/erts/preloaded/src/Makefile
|
||||
index b0c205cec8..7fad1ddc75 100644
|
||||
--- a/erts/preloaded/src/Makefile
|
||||
+++ b/erts/preloaded/src/Makefile
|
||||
@@ -121,8 +121,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 a6ff72898c..35d4530f32 100644
|
||||
--- a/lib/asn1/src/Makefile
|
||||
+++ b/lib/asn1/src/Makefile
|
||||
@@ -155,7 +155,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 7d7b5ed203..9151e4097b 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 f015064b39..57f96d2929 100644
|
||||
--- a/lib/common_test/test_server/Makefile
|
||||
+++ b/lib/common_test/test_server/Makefile
|
||||
@@ -86,9 +86,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 b1531ac985..dbcfe0042c 100644
|
||||
--- a/lib/compiler/src/Makefile
|
||||
+++ b/lib/compiler/src/Makefile
|
||||
@@ -184,8 +184,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 c3f1c859e5..0d72d6c82d 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 118cb6b758..86722d8767 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 1f5b308c7d..1f728c56d6 100644
|
||||
--- a/lib/dialyzer/src/Makefile
|
||||
+++ b/lib/dialyzer/src/Makefile
|
||||
@@ -161,7 +161,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 348cc350e1..9d87858def 100644
|
||||
--- a/lib/diameter/src/Makefile
|
||||
+++ b/lib/diameter/src/Makefile
|
||||
@@ -260,11 +260,8 @@ release_spec: opt
|
||||
$(MAKE) $(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 ea2f45dc4c..84af08eb67 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 b79a537424..d0b231e5fc 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 4c6f542ebb..d0cd6d8f68 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 b6347d8b6d..a695d2cc2d 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 32f75202a0..a89fa7f2d2 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) "$(RELSYSDIR)/src"
|
||||
$(INSTALL_DATA) $(INTERNAL_HRL_FILES) "$(RELSYSDIR)/src"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/include"
|
||||
$(INSTALL_DATA) $(INCLUDE_DELIVERABLES) "$(RELSYSDIR)/include"
|
||||
diff --git a/lib/hipe/cerl/Makefile b/lib/hipe/cerl/Makefile
|
||||
index affbb10ff6..44598beff2 100644
|
||||
--- a/lib/hipe/cerl/Makefile
|
||||
+++ b/lib/hipe/cerl/Makefile
|
||||
@@ -105,7 +105,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/cerl"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/cerl"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/cerl"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/flow/Makefile b/lib/hipe/flow/Makefile
|
||||
index d883eecf36..3119bc4638 100644
|
||||
--- a/lib/hipe/flow/Makefile
|
||||
+++ b/lib/hipe/flow/Makefile
|
||||
@@ -102,7 +102,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/flow"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(INC_FILES) "$(RELSYSDIR)/flow"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) $(INC_FILES) "$(RELSYSDIR)/flow"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/icode/Makefile b/lib/hipe/icode/Makefile
|
||||
index b220bc16a0..d4073277be 100644
|
||||
--- a/lib/hipe/icode/Makefile
|
||||
+++ b/lib/hipe/icode/Makefile
|
||||
@@ -120,7 +120,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/icode"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/icode"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/icode"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/llvm/Makefile b/lib/hipe/llvm/Makefile
|
||||
index 5e8f2076db..06d3f2684d 100644
|
||||
--- a/lib/hipe/llvm/Makefile
|
||||
+++ b/lib/hipe/llvm/Makefile
|
||||
@@ -104,7 +104,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) $(RELSYSDIR)/llvm
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(RELSYSDIR)/llvm
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) $(RELSYSDIR)/llvm
|
||||
$(INSTALL_DIR) $(RELSYSDIR)/ebin
|
||||
$(INSTALL_DATA) $(TARGET_FILES) $(RELSYSDIR)/ebin
|
||||
|
||||
diff --git a/lib/hipe/main/Makefile b/lib/hipe/main/Makefile
|
||||
index 8ef31dbb46..80d28819f2 100644
|
||||
--- a/lib/hipe/main/Makefile
|
||||
+++ b/lib/hipe/main/Makefile
|
||||
@@ -118,7 +118,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
release_spec: opt
|
||||
$(INSTALL_DATA) ../vsn.mk "$(RELSYSDIR)"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/main"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/main"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/main"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/misc/Makefile b/lib/hipe/misc/Makefile
|
||||
index e5033e444b..74a444b386 100644
|
||||
--- a/lib/hipe/misc/Makefile
|
||||
+++ b/lib/hipe/misc/Makefile
|
||||
@@ -102,7 +102,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/misc"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/misc"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/misc"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/rtl/Makefile b/lib/hipe/rtl/Makefile
|
||||
index 67485875a6..f83a2bb9e2 100644
|
||||
--- a/lib/hipe/rtl/Makefile
|
||||
+++ b/lib/hipe/rtl/Makefile
|
||||
@@ -108,7 +108,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/rtl"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/rtl"
|
||||
+ $(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/rtl"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/hipe/util/Makefile b/lib/hipe/util/Makefile
|
||||
index 20b1c3bf50..40c642a441 100644
|
||||
--- a/lib/hipe/util/Makefile
|
||||
+++ b/lib/hipe/util/Makefile
|
||||
@@ -50,7 +50,6 @@ HIPE_MODULES =
|
||||
endif
|
||||
MODULES = hipe_timing hipe_dot hipe_digraph hipe_dsets $(HIPE_MODULES)
|
||||
|
||||
-HRL_FILES=
|
||||
ERL_FILES= $(MODULES:%=%.erl)
|
||||
TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))
|
||||
DOC_FILES= $(MODULES:%=$(DOCS)/%.html)
|
||||
@@ -104,8 +103,6 @@ $(DOCS)/%.html:%.erl
|
||||
include $(ERL_TOP)/make/otp_release_targets.mk
|
||||
|
||||
release_spec: opt
|
||||
- $(INSTALL_DIR) "$(RELSYSDIR)/util"
|
||||
- $(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) "$(RELSYSDIR)/util"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
|
||||
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
|
||||
|
||||
diff --git a/lib/inets/src/http_client/Makefile b/lib/inets/src/http_client/Makefile
|
||||
index a1c1f36b70..f2eb86f7ac 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 8248e37c44..1f1b23184b 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 da9549406f..eaa14b628f 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 ec1ae70305..88c084ef58 100644
|
||||
--- a/lib/inets/src/inets_app/Makefile
|
||||
+++ b/lib/inets/src/inets_app/Makefile
|
||||
@@ -116,7 +116,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 6c75bcffee..d15bdb867a 100644
|
||||
--- a/lib/kernel/src/Makefile
|
||||
+++ b/lib/kernel/src/Makefile
|
||||
@@ -236,7 +236,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 ab45548099..5c7a7f0be9 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 7fc90fd6d5..6ad086ed01 100644
|
||||
--- a/lib/megaco/src/binary/Makefile
|
||||
+++ b/lib/megaco/src/binary/Makefile
|
||||
@@ -177,7 +177,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 869b516b05..fa7d774d84 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 c65e817385..3bc4dea207 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 d07db3fa4b..7f421d24cc 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 3dd24b1df7..836e163499 100644
|
||||
--- a/lib/megaco/src/text/Makefile
|
||||
+++ b/lib/megaco/src/text/Makefile
|
||||
@@ -131,7 +131,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 028a63e98e..9e11e9bfb2 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 90e8780754..1a13d764b3 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 f9f239db37..dd061f29f4 100644
|
||||
--- a/lib/observer/src/Makefile
|
||||
+++ b/lib/observer/src/Makefile
|
||||
@@ -150,7 +150,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 7ca59495ed..a52ade2fe3 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 e2f4d5a090..57f21a145b 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 ba206904ec..281cc8657c 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 1fef168463..e5411b903b 100644
|
||||
--- a/lib/public_key/asn1/Makefile
|
||||
+++ b/lib/public_key/asn1/Makefile
|
||||
@@ -96,8 +96,8 @@ release_spec: opt
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/include"
|
||||
$(INSTALL_DATA) $(HRL_FILES) "$(RELSYSDIR)/include"
|
||||
$(INSTALL_DIR) "$(RELSYSDIR)/asn1"
|
||||
- $(INSTALL_DATA) $(ASN_ASNS) $(ASN_ERLS) $(ASN_HRLS) $(ASN_CONFIGS) \
|
||||
- $(GEN_ERLS) "$(RELSYSDIR)/asn1"
|
||||
+ $(INSTALL_DATA) $(ASN_ASNS) $(ASN_HRLS) $(ASN_CONFIGS) \
|
||||
+ "$(RELSYSDIR)/asn1"
|
||||
$(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 76bdffe089..fc5e4dfa8e 100644
|
||||
--- a/lib/public_key/src/Makefile
|
||||
+++ b/lib/public_key/src/Makefile
|
||||
@@ -110,8 +110,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 4bddee4664..c714255548 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 76286c5499..d921f9f294 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 16a42caf11..674364281d 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 b/lib/snmp/src/agent/Makefile
|
||||
index 1bde1ca972..acc42385f3 100644
|
||||
--- a/lib/snmp/src/agent/Makefile
|
||||
+++ b/lib/snmp/src/agent/Makefile
|
||||
@@ -140,7 +140,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 6f2b8a4077..bd062a6473 100644
|
||||
--- a/lib/snmp/src/app/Makefile
|
||||
+++ b/lib/snmp/src/app/Makefile
|
||||
@@ -132,7 +132,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 d9678669a5..ff9dff95d9 100644
|
||||
--- a/lib/snmp/src/compile/Makefile
|
||||
+++ b/lib/snmp/src/compile/Makefile
|
||||
@@ -125,7 +125,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 57ff08c160..d51f627ca5 100644
|
||||
--- a/lib/snmp/src/manager/Makefile
|
||||
+++ b/lib/snmp/src/manager/Makefile
|
||||
@@ -123,7 +123,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 adc2c4858f..89ce954e99 100644
|
||||
--- a/lib/snmp/src/misc/Makefile
|
||||
+++ b/lib/snmp/src/misc/Makefile
|
||||
@@ -112,7 +112,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 ab6137e518..bdeabca8c3 100644
|
||||
--- a/lib/ssh/src/Makefile
|
||||
+++ b/lib/ssh/src/Makefile
|
||||
@@ -154,7 +154,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 5edd6cb4b9..39008882ca 100644
|
||||
--- a/lib/ssl/src/Makefile
|
||||
+++ b/lib/ssl/src/Makefile
|
||||
@@ -207,7 +207,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 e3e0c9c03d..ff9bad32ab 100644
|
||||
--- a/lib/stdlib/src/Makefile
|
||||
+++ b/lib/stdlib/src/Makefile
|
||||
@@ -223,7 +223,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 c21d2f49c8..03dbc74ef7 100644
|
||||
--- a/lib/syntax_tools/src/Makefile
|
||||
+++ b/lib/syntax_tools/src/Makefile
|
||||
@@ -100,8 +100,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 029bd731bd..85c633b4f0 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 cc5bee9a8f..7dfa55cb41 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 52f4008e0a..dc297f1d55 100644
|
||||
--- a/lib/wx/src/Makefile
|
||||
+++ b/lib/wx/src/Makefile
|
||||
@@ -122,9 +122,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 51d9190797..1ab65bd2ed 100644
|
||||
--- a/lib/xmerl/src/Makefile
|
||||
+++ b/lib/xmerl/src/Makefile
|
||||
@@ -218,9 +218,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"
|
||||
|
||||
32
otp-0007-Add-extra-search-directory.patch
Normal file
32
otp-0007-Add-extra-search-directory.patch
Normal file
@ -0,0 +1,32 @@
|
||||
From: Peter Lemenkov <lemenkov@gmail.com>
|
||||
Date: Wed, 2 Aug 2017 16:12:19 +0300
|
||||
Subject: [PATCH] Add extra search directory
|
||||
|
||||
Signed-off-by: Peter Lemenkov <lemenkov@gmail.com>
|
||||
|
||||
diff --git a/lib/kernel/src/code_server.erl b/lib/kernel/src/code_server.erl
|
||||
index 4c4823eb38..de0ab149fb 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,
|
||||
31
otp-0008-Avoid-forking-sed-to-get-basename.patch
Normal file
31
otp-0008-Avoid-forking-sed-to-get-basename.patch
Normal file
@ -0,0 +1,31 @@
|
||||
From: Jan Pazdziora <jpazdziora@redhat.com>
|
||||
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 959c099e8f..861b8bcbf1 100644
|
||||
--- a/erts/etc/unix/erl.src.src
|
||||
+++ b/erts/etc/unix/erl.src.src
|
||||
@@ -21,7 +21,7 @@
|
||||
ROOTDIR="%FINAL_ROOTDIR%"
|
||||
BINDIR=$ROOTDIR/erts-%VSN%/bin
|
||||
EMU=%EMULATOR%%EMULATOR_NUMBER%
|
||||
-PROGNAME=`echo $0 | sed 's/.*\///'`
|
||||
+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
|
||||
25
otp-0009-Load-man-pages-from-system-wide-directory.patch
Normal file
25
otp-0009-Load-man-pages-from-system-wide-directory.patch
Normal file
@ -0,0 +1,25 @@
|
||||
From: Francois-Denis Gonthier <neumann@lostwebsite.net>
|
||||
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 9dba684cbb..b4c5a8413f 100644
|
||||
--- a/erts/etc/common/erlexec.c
|
||||
+++ b/erts/etc/common/erlexec.c
|
||||
@@ -727,8 +727,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
|
||||
BIN
otp-OTP-23.3.4.9.tar.gz
Normal file
BIN
otp-OTP-23.3.4.9.tar.gz
Normal file
Binary file not shown.
Loading…
x
Reference in New Issue
Block a user