Skip to content

Commit 892684d

Browse files
xadhoomMatteo Brancaleoni
authored andcommitted
Fix eldap extensibleMatch dnAttributes option
According to the ldap ASN1 the dnAttributes should be a bool, instead it was generated as a charlist 'TRUE'/'FALSE'. Also add a couple of test to verify the filter behaves correctly.
1 parent 700d189 commit 892684d

File tree

2 files changed

+87
-2
lines changed

2 files changed

+87
-2
lines changed

lib/eldap/src/eldap.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -418,9 +418,9 @@ mra([{matchingRule,Val}|T], Ack) when is_list(Val) ->
418418
mra([{type,Val}|T], Ack) when is_list(Val) ->
419419
mra(T, Ack#'MatchingRuleAssertion'{type=Val});
420420
mra([{dnAttributes,true}|T], Ack) ->
421-
mra(T, Ack#'MatchingRuleAssertion'{dnAttributes="TRUE"});
421+
mra(T, Ack#'MatchingRuleAssertion'{dnAttributes=true});
422422
mra([{dnAttributes,false}|T], Ack) ->
423-
mra(T, Ack#'MatchingRuleAssertion'{dnAttributes="FALSE"});
423+
mra(T, Ack#'MatchingRuleAssertion'{dnAttributes=false});
424424
mra([H|_], _) ->
425425
throw({error,{extensibleMatch_arg,H}});
426426
mra([], Ack) ->

lib/eldap/test/eldap_basic_SUITE.erl

Lines changed: 85 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,8 @@
5959
search_non_existant/1,
6060
search_referral/1,
6161
search_two_hits/1,
62+
search_extensible_match_with_dn/1,
63+
search_extensible_match_without_dn/1,
6264
ssl_connection/1,
6365
start_tls_on_ssl_should_fail/1,
6466
start_tls_twice_should_fail/1,
@@ -129,6 +131,8 @@ groups() ->
129131
search_filter_or,
130132
search_filter_and_not,
131133
search_two_hits,
134+
search_extensible_match_with_dn,
135+
search_extensible_match_without_dn,
132136
search_referral,
133137
search_filter_or_sizelimit_ok,
134138
search_filter_or_sizelimit_exceeded,
@@ -721,6 +725,87 @@ search_two_hits(Config) ->
721725
%% Restore the database:
722726
[ok=eldap:delete(H,DN) || DN <- ExpectedDNs].
723727

728+
%%%----------------------------------------------------------------
729+
search_extensible_match_with_dn(Config) ->
730+
H = proplists:get_value(handle, Config),
731+
BasePath = proplists:get_value(eldap_path, Config),
732+
733+
%% Create intermediate tree
734+
OU1 = "o=Designers," ++ BasePath,
735+
ok = eldap:add(H, OU1, [{"objectclass", ["top", "organization"]}, {"o", ["Designers"]}]),
736+
OU2 = "o=Graphics," ++ BasePath,
737+
ok = eldap:add(H, OU2, [{"objectclass", ["top", "organization"]}, {"o", ["Graphics"]}]),
738+
739+
%% Add objects, they belongs to different trees
740+
DN1 = "cn=Bob Noorda,o=Designers," ++ BasePath,
741+
DN2 = "cn=Bob Noorda,o=Graphics," ++ BasePath,
742+
ok = eldap:add(H, DN1,
743+
[{"objectclass", ["person"]},
744+
{"cn", ["Bob Noorda"]},
745+
{"sn", ["Noorda"]},
746+
{"description", ["Amsterdam"]}]),
747+
ok = eldap:add(H, DN2,
748+
[{"objectclass", ["person"]},
749+
{"cn", ["Bob Noorda"]},
750+
{"sn", ["Noorda"]},
751+
{"description", ["Milan"]}]),
752+
753+
%% Search using extensible filter only in Designers tree
754+
Filter = eldap:'and'([
755+
eldap:extensibleMatch("Designers", [{type, "o"}, {dnAttributes, true}]),
756+
eldap:equalityMatch("sn", "Noorda")
757+
]),
758+
{ok, #eldap_search_result{entries=Es}} =
759+
eldap:search(H, #eldap_search{base = BasePath,
760+
filter = Filter,
761+
scope=eldap:wholeSubtree()}),
762+
763+
%% Check
764+
[DN1] = [D || #eldap_entry{object_name=D} <- Es],
765+
766+
%% Restore the database
767+
[ok=eldap:delete(H,DN) || DN <- [DN1, DN2, OU1, OU2]].
768+
769+
%%%----------------------------------------------------------------
770+
search_extensible_match_without_dn(Config) ->
771+
H = proplists:get_value(handle, Config),
772+
BasePath = proplists:get_value(eldap_path, Config),
773+
774+
%% Create intermediate tree
775+
OU1 = "o=Teachers," ++ BasePath,
776+
ok = eldap:add(H, OU1, [{"objectclass", ["top", "organization"]}, {"o", ["Teachers"]}]),
777+
OU2 = "o=Designers," ++ BasePath,
778+
ok = eldap:add(H, OU2, [{"objectclass", ["top", "organization"]}, {"o", ["Designers"]}]),
779+
780+
%% Add objects, they belongs to different trees
781+
DN1 = "cn=Max Huber,o=Teachers," ++ BasePath,
782+
DN2 = "cn=Max Huber,o=Designers," ++ BasePath,
783+
ok = eldap:add(H, DN1,
784+
[{"objectclass", ["person"]},
785+
{"cn", ["Max Huber"]},
786+
{"sn", ["Huber"]},
787+
{"description", ["Baar"]}]),
788+
ok = eldap:add(H, DN2,
789+
[{"objectclass", ["person"]},
790+
{"cn", ["Max Huber"]},
791+
{"sn", ["Huber"]},
792+
{"description", ["Milan"]}]),
793+
794+
%% Search using extensible filter without dn attribute
795+
Filter = eldap:extensibleMatch("Huber", [{type, "sn"}]),
796+
{ok, #eldap_search_result{entries=Es}} =
797+
eldap:search(H, #eldap_search{base = BasePath,
798+
filter = Filter,
799+
scope = eldap:wholeSubtree()
800+
}),
801+
802+
%% And check that they are the expected ones:
803+
ExpectedDNs = lists:sort([DN1, DN2]),
804+
ExpectedDNs = lists:sort([D || #eldap_entry{object_name=D} <- Es]),
805+
806+
%% Restore the database:
807+
[ok=eldap:delete(H,DN) || DN <- [DN1, DN2, OU1, OU2]].
808+
724809
%%%----------------------------------------------------------------
725810
search_referral(Config) ->
726811
H = proplists:get_value(handle, Config),

0 commit comments

Comments
 (0)