File 6901-Add-new-api-conn_info-for-SSL-connections-to-LDAP-se.patch of Package erlang

From a537e48be916d5225b16e020da0def71ed928d89 Mon Sep 17 00:00:00 2001
From: anupamasingh10 <anupamasingh31@gmail.com>
Date: Thu, 23 Feb 2023 11:11:06 +0100
Subject: [PATCH 1/8] Add new api conn_info for SSL connections to LDAP server

---
 lib/eldap/doc/src/eldap.xml          | 26 +++++++++++++
 lib/eldap/src/eldap.erl              | 29 +++++++++++++-
 lib/eldap/test/eldap_basic_SUITE.erl | 56 ++++++++++++++++++++++++++--
 3 files changed, 107 insertions(+), 4 deletions(-)

diff --git a/lib/eldap/doc/src/eldap.xml b/lib/eldap/doc/src/eldap.xml
index 4d9ec96a70..8f08514886 100644
--- a/lib/eldap/doc/src/eldap.xml
+++ b/lib/eldap/doc/src/eldap.xml
@@ -548,6 +548,32 @@ Control2 = eldap:paged_result_control(PageSize, Cookie1),
         the series.</p>
       </desc>
     </func>
+    <func>
+      <name since="OTP 26.0">conn_info(Handle) -> {ok, Data} | {error, Reason}</name>
+      <fsummary>Returns all the connection information.
+      </fsummary>
+      <type>
+	<v>Handle = handle()</v>
+	<v>Data = ssl:connection_info()</v>
+      </type>
+      <desc><p>Returns the most relevant information for SSL connection to an LDAP server, ssl options 
+      that are undefined will be filtered out. Note that values that affect the security of the
+      connection will only be returned if explicitly requested by conn_info/2.</p>
+      </desc>
+    </func>
+    <func>
+      <name since="OTP 26.0">conn_info(Handle, Items) -> {ok, Data} | {error, Reason}</name>
+      <fsummary>Returns the requested connection information.
+      </fsummary>
+      <type>
+	<v>Handle = handle()</v>
+	<v>Items = ssl:connection_info_items()</v>
+	<v>Data = ssl:connection_info()</v>
+      </type>
+      <desc><p>Returns the requested information items about the SSL connection to LDAP server,
+      if they are defined.</p>
+      </desc>
+    </func>
 
   </funcs>
 
diff --git a/lib/eldap/src/eldap.erl b/lib/eldap/src/eldap.erl
index 22d816c8c8..cc27a31966 100644
--- a/lib/eldap/src/eldap.erl
+++ b/lib/eldap/src/eldap.erl
@@ -30,7 +30,9 @@
 	 parse_ldap_url/1,
 	 paged_result_control/1,
 	 paged_result_control/2,
-	 paged_result_cookie/1]).
+	 paged_result_cookie/1,
+         conn_info/1,
+         conn_info/2]).
 
 -export([neverDerefAliases/0, derefInSearching/0,
          derefFindingBaseObj/0, derefAlways/0]).
@@ -154,6 +156,16 @@ controlling_process(Handle, Pid) when is_pid(Handle), is_pid(Pid)  ->
     send(Handle, {cnt_proc, Pid}),
     recv(Handle).
 
+%%% --------------------------------------------------------------------
+%%% Return LDAP connection information
+%%% --------------------------------------------------------------------
+conn_info(Handle) when is_pid(Handle) ->
+    conn_info(Handle, []).
+
+conn_info(Handle, Items) when is_pid(Handle) ->
+    send(Handle, {conn_info, Items}),
+    recv(Handle).
+
 %%% --------------------------------------------------------------------
 %%% Authenticate ourselves to the Directory
 %%% using simple authentication.
@@ -608,6 +620,17 @@ loop(Cpid, Data) ->
 	    send(From, Result),
 	    ?MODULE:loop(Cpid, Data);
 
+        {From, {conn_info, Items}} ->
+            Res =
+                case Data#eldap.ldaps of
+                    true ->
+                        get_ssl_conn_info(Data#eldap.fd, Items);
+                    false ->
+                        {error, "Not an SSL connection"} 
+                end,
+            send(From, Res),
+            ?MODULE:loop(Cpid, Data);
+
 	{Cpid, 'EXIT', Reason} ->
 	    ?PRINT("Got EXIT from Cpid, reason=~p~n",[Reason]),
 	    exit(Reason);
@@ -618,6 +641,10 @@ loop(Cpid, Data) ->
 
     end.
 
+get_ssl_conn_info(SockFd, []) ->
+    ssl:connection_information(SockFd);
+get_ssl_conn_info(SockFd, Items) ->
+    ssl:connection_information(SockFd, Items).
 
 %%% --------------------------------------------------------------------
 %%% startTLS Request
diff --git a/lib/eldap/test/eldap_basic_SUITE.erl b/lib/eldap/test/eldap_basic_SUITE.erl
index 5fa6d4ca69..1c283a1f82 100644
--- a/lib/eldap/test/eldap_basic_SUITE.erl
+++ b/lib/eldap/test/eldap_basic_SUITE.erl
@@ -46,6 +46,7 @@
          more_add/1,
          open_ret_val_error/1,
          open_ret_val_success/1,
+         plain_ldap_conn_info_error/1,
          search_filter_and/1,
          search_filter_and_not/1,
          search_filter_equalityMatch/1,
@@ -63,6 +64,8 @@
          search_extensible_match_without_dn/1,
          search_paged_results/1,
          ssl_connection/1,
+         ssl_conn_info/1,
+         ssl_conn_info_items/1,
          start_tls_on_ssl_should_fail/1,
          start_tls_twice_should_fail/1,
          tcp_connection/1,
@@ -81,8 +84,8 @@
          suite/0
         ]).
 
-%%-include_lib("common_test/include/ct.hrl").
 -include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
 -include_lib("eldap/include/eldap.hrl").
 -include_lib("eldap/ebin/ELDAPv3.hrl").
 
@@ -159,7 +162,10 @@ connection_tests() ->
      client_side_bind_timeout,
      client_side_add_timeout,
      client_side_search_timeout,
-     close_after_tcp_error
+     close_after_tcp_error,
+     ssl_conn_info,
+     ssl_conn_info_items,
+     plain_ldap_conn_info_error
     ].
 
 
@@ -259,7 +265,7 @@ end_per_group(start_tls_api, Config) -> clear_db(Config);
 end_per_group(_Group, Config) -> Config.
 
 
-init_per_testcase(ssl_connection, Config) ->
+init_per_testcase(TC, Config) when TC == ssl_connection; TC == ssl_conn_info; TC == ssl_conn_info_items ->
     case proplists:get_value(ssl_available,Config) of
 	true ->
 	    SSL_Port = 9999,
@@ -422,6 +428,50 @@ ssl_connection(Config) ->
 	Other -> ct:fail("eldap:open failed: ~p",[Other])
     end.
 
+%%%----------------------------------------------------------------
+ssl_conn_info(Config) ->
+    Host = proplists:get_value(listen_host, Config),
+    Port = proplists:get_value(ssl_listen_port, Config),
+    Opts = proplists:get_value(tcp_connect_opts, Config),
+    SSLOpts = proplists:get_value(ssl_connect_opts, Config),
+    case eldap:open([Host], [{port,Port},
+			     {ssl,true},
+			     {timeout,5000},
+			     {sslopts,SSLOpts}|Opts]) of
+	{ok,H} ->
+            ?assertMatch({ok, _Data}, eldap:conn_info(H));
+	Other -> ct:fail("eldap:open failed: ~p",[Other])
+    end.
+
+%%%----------------------------------------------------------------
+ssl_conn_info_items(Config) ->
+    Host = proplists:get_value(listen_host, Config),
+    Port = proplists:get_value(ssl_listen_port, Config),
+    Opts = proplists:get_value(tcp_connect_opts, Config),
+    SSLOpts = proplists:get_value(ssl_connect_opts, Config),
+    case eldap:open([Host], [{port,Port},
+			     {ssl,true},
+			     {timeout,5000},
+			     {sslopts,SSLOpts}|Opts]) of
+	{ok,H} ->
+            ?assertEqual({ok, [{protocol, 'tlsv1.3'}, {session_resumption, false}]},
+                          eldap:conn_info(H, [protocol, session_resumption]));
+	Other -> ct:fail("eldap:open failed: ~p",[Other])
+    end.
+
+%%%----------------------------------------------------------------
+plain_ldap_conn_info_error(Config) ->
+    Host = proplists:get_value(listen_host, Config),
+    Port = proplists:get_value(listen_port, Config),
+    Opts = proplists:get_value(tcp_connect_opts, Config),
+    T = 1000,
+    case eldap:open([Host], [{timeout,T},{port,Port}|Opts]) of
+        {ok,H} ->
+            ?assertMatch({error, "Not an SSL connection"},
+                          eldap:conn_info(H));
+        Other -> ct:fail("eldap:open failed: ~p",[Other])
+    end.
+
 %%%----------------------------------------------------------------
 client_side_add_timeout(Config) ->
     client_timeout(
-- 
2.35.3

openSUSE Build Service is sponsored by