File 1364-Fix-eldap-extensibleMatch-dnAttributes-option.patch of Package erlang
From 4e7b1f7de78f8e971df1d02583b143642be2df55 Mon Sep 17 00:00:00 2001
From: Matteo Brancaleoni <mbrancaleoni@gmail.com>
Date: Mon, 17 Jan 2022 16:52:45 +0100
Subject: [PATCH] Fix eldap extensibleMatch dnAttributes option
According to the ldap ASN1 the dnAttributes should be a bool,
instead it was generated as a string.
Also add a couple of test to verify the filter behaves correctly.
---
lib/eldap/src/eldap.erl | 4 +-
lib/eldap/test/eldap_basic_SUITE.erl | 85 ++++++++++++++++++++++++++++
2 files changed, 87 insertions(+), 2 deletions(-)
diff --git a/lib/eldap/src/eldap.erl b/lib/eldap/src/eldap.erl
index 24562eb790..dfdcfccf55 100644
--- a/lib/eldap/src/eldap.erl
+++ b/lib/eldap/src/eldap.erl
@@ -418,9 +418,9 @@ mra([{matchingRule,Val}|T], Ack) when is_list(Val) ->
mra([{type,Val}|T], Ack) when is_list(Val) ->
mra(T, Ack#'MatchingRuleAssertion'{type=Val});
mra([{dnAttributes,true}|T], Ack) ->
- mra(T, Ack#'MatchingRuleAssertion'{dnAttributes="TRUE"});
+ mra(T, Ack#'MatchingRuleAssertion'{dnAttributes=true});
mra([{dnAttributes,false}|T], Ack) ->
- mra(T, Ack#'MatchingRuleAssertion'{dnAttributes="FALSE"});
+ mra(T, Ack#'MatchingRuleAssertion'{dnAttributes=false});
mra([H|_], _) ->
throw({error,{extensibleMatch_arg,H}});
mra([], Ack) ->
diff --git a/lib/eldap/test/eldap_basic_SUITE.erl b/lib/eldap/test/eldap_basic_SUITE.erl
index 15cf6a9039..6d90158050 100644
--- a/lib/eldap/test/eldap_basic_SUITE.erl
+++ b/lib/eldap/test/eldap_basic_SUITE.erl
@@ -129,6 +131,8 @@ groups() ->
search_filter_or,
search_filter_and_not,
search_two_hits,
+ search_extensible_match_with_dn,
+ search_extensible_match_without_dn,
search_referral,
modify,
modify_referral,
@@ -721,6 +725,87 @@ search_two_hits(Config) ->
%% Restore the database:
[ok=eldap:delete(H,DN) || DN <- ExpectedDNs].
+%%%----------------------------------------------------------------
+search_extensible_match_with_dn(Config) ->
+ H = proplists:get_value(handle, Config),
+ BasePath = proplists:get_value(eldap_path, Config),
+
+ %% Create intermediate tree
+ OU1 = "o=Designers," ++ BasePath,
+ ok = eldap:add(H, OU1, [{"objectclass", ["top", "organization"]}, {"o", ["Designers"]}]),
+ OU2 = "o=Graphics," ++ BasePath,
+ ok = eldap:add(H, OU2, [{"objectclass", ["top", "organization"]}, {"o", ["Graphics"]}]),
+
+ %% Add objects, they belongs to different trees
+ DN1 = "cn=Bob Noorda,o=Designers," ++ BasePath,
+ DN2 = "cn=Bob Noorda,o=Graphics," ++ BasePath,
+ ok = eldap:add(H, DN1,
+ [{"objectclass", ["person"]},
+ {"cn", ["Bob Noorda"]},
+ {"sn", ["Noorda"]},
+ {"description", ["Amsterdam"]}]),
+ ok = eldap:add(H, DN2,
+ [{"objectclass", ["person"]},
+ {"cn", ["Bob Noorda"]},
+ {"sn", ["Noorda"]},
+ {"description", ["Milan"]}]),
+
+ %% Search using extensible filter only in Designers tree
+ Filter = eldap:'and'([
+ eldap:extensibleMatch("Designers", [{type, "o"}, {dnAttributes, true}]),
+ eldap:equalityMatch("sn", "Noorda")
+ ]),
+ {ok, #eldap_search_result{entries=Es}} =
+ eldap:search(H, #eldap_search{base = BasePath,
+ filter = Filter,
+ scope=eldap:wholeSubtree()}),
+
+ %% Check
+ [DN1] = [D || #eldap_entry{object_name=D} <- Es],
+
+ %% Restore the database
+ [ok=eldap:delete(H,DN) || DN <- [DN1, DN2, OU1, OU2]].
+
+%%%----------------------------------------------------------------
+search_extensible_match_without_dn(Config) ->
+ H = proplists:get_value(handle, Config),
+ BasePath = proplists:get_value(eldap_path, Config),
+
+ %% Create intermediate tree
+ OU1 = "o=Teachers," ++ BasePath,
+ ok = eldap:add(H, OU1, [{"objectclass", ["top", "organization"]}, {"o", ["Teachers"]}]),
+ OU2 = "o=Designers," ++ BasePath,
+ ok = eldap:add(H, OU2, [{"objectclass", ["top", "organization"]}, {"o", ["Designers"]}]),
+
+ %% Add objects, they belongs to different trees
+ DN1 = "cn=Max Huber,o=Teachers," ++ BasePath,
+ DN2 = "cn=Max Huber,o=Designers," ++ BasePath,
+ ok = eldap:add(H, DN1,
+ [{"objectclass", ["person"]},
+ {"cn", ["Max Huber"]},
+ {"sn", ["Huber"]},
+ {"description", ["Baar"]}]),
+ ok = eldap:add(H, DN2,
+ [{"objectclass", ["person"]},
+ {"cn", ["Max Huber"]},
+ {"sn", ["Huber"]},
+ {"description", ["Milan"]}]),
+
+ %% Search using extensible filter without dn attribute
+ Filter = eldap:extensibleMatch("Huber", [{type, "sn"}]),
+ {ok, #eldap_search_result{entries=Es}} =
+ eldap:search(H, #eldap_search{base = BasePath,
+ filter = Filter,
+ scope = eldap:wholeSubtree()
+ }),
+
+ %% And check that they are the expected ones:
+ ExpectedDNs = lists:sort([DN1, DN2]),
+ ExpectedDNs = lists:sort([D || #eldap_entry{object_name=D} <- Es]),
+
+ %% Restore the database:
+ [ok=eldap:delete(H,DN) || DN <- [DN1, DN2, OU1, OU2]].
+
%%%----------------------------------------------------------------
search_referral(Config) ->
H = proplists:get_value(handle, Config),
--
2.31.1