1/* Copyright 2015 Ericsson 2 3Licensed under the Apache License, Version 2.0 (the "License"); 4you may not use this file except in compliance with the License. 5You may obtain a copy of the License at 6 7 http://www.apache.org/licenses/LICENSE-2.0 8 9Unless required by applicable law or agreed to in writing, software 10distributed under the License is distributed on an "AS IS" BASIS, 11WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. 12See the License for the specific language governing permissions and 13limitations under the License. 14*/ 15 16:- module(ldap4pl, [ 17 ldap_initialize/2, % -LDAP, +URI 18 ldap_unbind/1, % +LDAP 19 ldap_unbind_s/1, % +LDAP 20 ldap_unbind_ext/3, % +LDAP, +SCtrls, +CCtrls 21 ldap_unbind_ext_s/3, % +LDAP, +SCtrls, +CCtrls 22 ldap_bind/5, % +LDAP, +Who, +Cred, +Method, -MsgID 23 ldap_bind_s/4, % +LDAP, +Who, +Cred, +Method 24 ldap_simple_bind/4, % +LDAP, +Who, +Passwd, -MsgID 25 ldap_simple_bind_s/3, % +LDAP, +Who, +Passwd 26 ldap_sasl_bind/7, % +LDAP, +DN, +Mechanism, +Cred, +SCtrls, +CCtrls, -MsgID 27 ldap_sasl_bind_s/7, % +LDAP, +DN, +Mechanism, +Cred, +SCtrls, +CCtrls, -ServerCred 28 ldap_parse_sasl_bind_result/4, % +LDAP, +Result, -ServerCred, +FreeIt 29 ldap_set_option/3, % +LDAP, +Option, +Value 30 ldap_get_option/3, % +LDAP, +Option, ?Value 31 ldap_result/4, % +LDAP, +MsgID, +All, -Result 32 ldap_result/5, % +LDAP, +MsgID, +All, +Timeout, -Result 33 ldap_msgfree/1, % +Msg 34 ldap_msgtype/2, % +Msg, ?Type 35 ldap_msgid/2, % +Msg, ?ID 36 ldap_search_ext/7, % +LDAP, +Query, +SCtrls, +CCtrls, +Timeout, +SizeLimit, -MsgID 37 ldap_search_ext/6, % +LDAP, +Query, +SCtrls, +CCtrls, +SizeLimit, -MsgID 38 ldap_search_ext_s/7, % +LDAP, +Query, +SCtrls, +CCtrls, +Timeout, +SizeLimit, -Result 39 ldap_search_ext_s/6, % +LDAP, +Query, +SCtrls, +CCtrls, +SizeLimit, -Result 40 ldap_search/3, % +LDAP, +Query, -MsgID 41 ldap_search_s/3, % +LDAP, +Query, -Result 42 ldap_search_st/4, % +LDAP, +Query, +Timeout, -Result 43 ldap_count_entries/3, % +LDAP, +Result, ?Count 44 ldap_first_entry/3, % +LDAP, +Result, -Entry 45 ldap_next_entry/3, % +LDAP, +Entry, -NextEntry 46 ldap_first_attribute/4, % +LDAP, +Entry, -Attribute, -Ber 47 ldap_next_attribute/4, % +LDAP, +Entry, -Attribute, +Ber 48 ldap_ber_free/2, % +Ber, +FreeBuf 49 ldap_get_values/4, % +LDAP, +Entry, +Attribute, -Values 50 ldap_get_dn/3, % +LDAP, +Entry, ?DN 51 ldap_parse_result/8, % +LDAP, +Result, ?ErrorCode, -MatchedDN, -ErrorMsg, -Referrals, -ServerCred, +FreeIt 52 ldap_err2string/2, % +ErrorCode, -ErrorString 53 ldap_compare_ext/7, % +LDAP, +DN, +Attribute, +BerVal, +SCtrls, +CCtrls, -MsgID 54 ldap_compare_ext_s/7, % +LDAP, +DN, +Attribute, +BerVal, +SCtrls, +CCtrls, -Result 55 ldap_compare/5, % +LDAP, +DN, +Attribute, +Value, -MsgID 56 ldap_compare_s/5, % +LDAP, +DN, +Attribute, +Value, -Result 57 ldap_abandon_ext/4, % +LDAP, +MsgID, +SCtrls, +CCtrls 58 ldap_abandon/2, % +LDAP, +MsgID 59 ldap_add_ext/6, % +LDAP, +DN, +Attributes, +SCtrls, +CCtrls, -MsgID 60 ldap_add_ext_s/5, % +LDAP, +DN, +Attributes, +SCtrls, +CCtrls 61 ldap_add/4, % +LDAP, +DN, +Attributes, -MsgID 62 ldap_add_s/3, % +LDAP, +DN, +Attributes 63 ldap_modify_ext/6, % +LDAP, +DN, +Attributes, +SCtrls, +CCtrls, -MsgID 64 ldap_modify_ext_s/5, % +LDAP, +DN, +Attributes, +SCtrls, +CCtrls 65 ldap_modify/4, % +LDAP, +DN, +Attributes, -MsgID 66 ldap_modify_s/3, % +LDAP, +DN, +Attributes 67 ldap_delete_ext/5, % +LDAP, +DN, +SCtrls, +CCtrls, -MsgID 68 ldap_delete_ext_s/4, % +LDAP, +DN, +SCtrls, +CCtrls 69 ldap_delete/3, % +LDAP, +DN, -MsgID 70 ldap_delete_s/2, % +LDAP, +DN 71 ldap_modrdn/4, % +LDAP, +DN, +NewRDN, -MsgID 72 ldap_modrdn_s/3, % +LDAP, +DN, +NewRDN 73 ldap_modrdn2/5, % +LDAP, +DN, +NewRDN, +DeleteOldRDN, -MsgID 74 ldap_modrdn2_s/4, % +LDAP, +DN, +NewRDN, +DeleteOldRDN 75 ldap_rename/8, % +LDAP, +DN, +NewRDN, +NewSuperior, +DeleteOldRDN, +SCtrls, +CCtrls, -MsgID 76 ldap_rename_s/7, % +LDAP, +DN, +NewRDN, +NewSuperior, +DeleteOldRDN, +SCtrls, +CCtrls 77 ldap_get_ld_errno/1, % ?ErrorCode 78 ldap_extended_operation/6, % +LDAP, +RequestOID, +RequestData, +SCtrls, +CCtrls, -MsgID 79 ldap_extended_operation_s/7, % +LDAP, +RequestOID, +RequestData, +SCtrls, +CCtrls, -RetOID, -RetData 80 ldap_is_ldap_url/1, % +URL 81 ldap_url_parse/2 % +URL, -Desc 82]).
95:- use_foreign_library(foreign(ldap4pl)).
Use ldap_get_ld_errno/1 to get last error.
104ldap_initialize(LDAP, URI) :-
105 ldap4pl_initialize(LDAP, URI).
By nature there is no asynchrous version of unbind and the underlying implementation is the same as ldap_unbind_s/1.
Use ldap_get_ld_errno/1 to get last error.
119ldap_unbind(LDAP) :-
120 ldap4pl_unbind(LDAP).
Use ldap_get_ld_errno/1 to get last error.
130ldap_unbind_s(LDAP) :-
131 ldap4pl_unbind(LDAP).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
By nature there is no asynchrous version of unbind and the underlying implementation is the same as ldap_unbind_ext_s/3.
Use ldap_get_ld_errno/1 to get last error.
155ldap_unbind_ext(LDAP, SCtrls, CCtrls) :-
156 ldap4pl_unbind_ext(LDAP, SCtrls, CCtrls).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
176ldap_unbind_ext_s(LDAP, SCtrls, CCtrls) :-
177 ldap4pl_unbind_ext(LDAP, SCtrls, CCtrls).
185ldap_bind(LDAP, Who, Cred, Method, MsgID) :-
186 ldap4pl_bind(LDAP, Who, Cred, Method, MsgID).
Use ldap_get_ld_errno/1 to get last error.
196ldap_bind_s(LDAP, Who, Cred, Method) :-
197 ldap4pl_bind_s(LDAP, Who, Cred, Method).
205ldap_simple_bind(LDAP, Who, Passwd, MsgID) :-
206 ldap4pl_simple_bind(LDAP, Who, Passwd, MsgID).
Use ldap_get_ld_errno/1 to get last error.
216ldap_simple_bind_s(LDAP, Who, Passwd) :-
217 ldap4pl_simple_bind_s(LDAP, Who, Passwd).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
235ldap_sasl_bind(LDAP, DN, Mechanism, Cred, SCtrls, CCtrls, MsgID) :-
236 ldap4pl_sasl_bind(LDAP, DN, Mechanism, Cred, SCtrls, CCtrls, MsgID).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
ServerCred
is in the format of:
berval(bv_len(...), bv_val(...))
Use ldap_get_ld_errno/1 to get last error.
261ldap_sasl_bind_s(LDAP, DN, Mechanism, Cred, SCtrls, CCtrls, ServerCred) :-
262 ldap4pl_sasl_bind_s(LDAP, DN, Mechanism, Cred, SCtrls, CCtrls, ServerCred).
ServerCred
is in the format of:
berval(bv_len(...), bv_val(...))
Use ldap_get_ld_errno/1 to get last error.
275ldap_parse_sasl_bind_result(LDAP, Result, ServerCred, FreeIt) :-
276 ldap4pl_parse_sasl_bind_result(LDAP, Result, ServerCred, FreeIt).
Use ldap_get_ld_errno/1 to get last error.
299ldap_set_option(LDAP, Option, Value) :-
300 ldap4pl_set_option(LDAP, Option, Value).
Use ldap_get_ld_errno/1 to get last error.
323ldap_get_option(LDAP, Option, Value) :-
324 ldap4pl_get_option(LDAP, Option, Value).
Use ldap_get_ld_errno/1 to get last error.
335ldap_result(LDAP, MsgID, All, Result) :- 336 ldap4pl_result(LDAP, MsgID, All, _, Result). 337 338ldap_result(LDAP, MsgID, All, Timeout, Result) :- 339 ldap4pl_result(LDAP, MsgID, All, Timeout, Result).
result(s)
.
345ldap_msgfree(Msg) :-
346 ldap4pl_msgfree(Msg).
352ldap_msgtype(Msg, Type) :-
353 ldap4pl_msgtype(Msg, Type).
359ldap_msgid(Msg, ID) :-
360 ldap4pl_msgid(Msg, ID).
Query
is in the format of:
query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
382ldap_search_ext(LDAP, Query, SCtrls, CCtrls, Timeout, SizeLimit, MsgID) :- 383 ldap4pl_search_ext(LDAP, Query, SCtrls, CCtrls, Timeout, SizeLimit, MsgID). 384 385ldap_search_ext(LDAP, Query, SCtrls, CCtrls, SizeLimit, MsgID) :- 386 ldap4pl_search_ext(LDAP, Query, SCtrls, CCtrls, _, SizeLimit, MsgID).
Query
is in the format of:
query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
410ldap_search_ext_s(LDAP, Query, SCtrls, CCtrls, Timeout, SizeLimit, Result) :- 411 ldap4pl_search_ext_s(LDAP, Query, SCtrls, CCtrls, Timeout, SizeLimit, Result). 412 413ldap_search_ext_s(LDAP, Query, SCtrls, CCtrls, SizeLimit, Result) :- 414 ldap4pl_search_ext_s(LDAP, Query, SCtrls, CCtrls, _, SizeLimit, Result).
Query
is in the format of:
query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))
425ldap_search(LDAP, Query, MsgID) :-
426 ldap4pl_search(LDAP, Query, _, MsgID).
Query
is in the format of:
query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))
Use ldap_get_ld_errno/1 to get last error.
440ldap_search_s(LDAP, Query, Result) :- 441 ldap4pl_search_s(LDAP, Query, _, Result). 442 443ldap_search_st(LDAP, Query, Timeout, Result) :- 444 ldap4pl_search_s(LDAP, Query, Timeout, Result).
450ldap_count_entries(LDAP, Result, Count) :-
451 ldap4pl_count_entries(LDAP, Result, Count).
457ldap_first_entry(LDAP, Result, Entry) :-
458 ldap4pl_first_entry(LDAP, Result, Entry).
Entry
.
464ldap_next_entry(LDAP, Entry, NextEntry) :-
465 ldap4pl_next_entry(LDAP, Entry, NextEntry).
Ber
must be freed by calling ldap_ber_free/2 with second
argument as false
.
474ldap_first_attribute(LDAP, Entry, Attribute, Ber) :-
475 ldap4pl_first_attribute(LDAP, Entry, Attribute, Ber).
Ber
must have been
unified by calling ldap_first_attribute/4 prior to this predicate.
482ldap_next_attribute(LDAP, Entry, Attribute, Ber) :-
483 ldap4pl_next_attribute(LDAP, Entry, Attribute, Ber).
Ber
.
489ldap_ber_free(Ber, FreeBuf) :-
490 ldap4pl_ber_free(Ber, FreeBuf).
496ldap_get_values(LDAP, Entry, Attribute, Values) :-
497 ldap4pl_get_values(LDAP, Entry, Attribute, Values).
503ldap_get_dn(LDAP, Entry, DN) :-
504 ldap4pl_get_dn(LDAP, Entry, DN).
SCtrls
is an array of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
521ldap_parse_result(LDAP, Result, ErrorCode, MatchedDN, ErrorMsg,
522 Referrals, SCtrls, FreeIt) :-
523 ldap4pl_parse_result(LDAP, Result, ErrorCode, MatchedDN, ErrorMsg,
524 Referrals, SCtrls, FreeIt).
531ldap_err2string(ErrorCode, ErrorString) :-
532 ldap4pl_err2string(ErrorCode, ErrorString).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
548ldap_compare_ext(LDAP, DN, Attribute, BerVal, SCtrls, CCtrls, MsgID) :-
549 ldap4pl_compare_ext(LDAP, DN, Attribute, BerVal, SCtrls, CCtrls, MsgID).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
565ldap_compare_ext_s(LDAP, DN, Attribute, BerVal, SCtrls, CCtrls, Result) :-
566 ldap4pl_compare_ext_s(LDAP, DN, Attribute, BerVal, SCtrls, CCtrls, Result).
572ldap_compare(LDAP, DN, Attribute, Value, MsgID) :-
573 ldap4pl_compare(LDAP, DN, Attribute, Value, MsgID).
579ldap_compare_s(LDAP, DN, Attribute, Value, Result) :-
580 ldap4pl_compare_s(LDAP, DN, Attribute, Value, Result).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
598ldap_abandon_ext(LDAP, MsgID, SCtrls, CCtrls) :-
599 ldap4pl_abandon_ext(LDAP, MsgID, SCtrls, CCtrls).
Use ldap_get_ld_errno/1 to get last error.
607ldap_abandon(LDAP, MsgID) :-
608 ldap4pl_abandon_ext(LDAP, MsgID, [], []).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
633ldap_add_ext(LDAP, DN, Attributes, SCtrls, CCtrls, MsgID) :-
634 ldap4pl_add_ext(LDAP, DN, Attributes, SCtrls, CCtrls, MsgID).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
661ldap_add_ext_s(LDAP, DN, Attributes, SCtrls, CCtrls) :-
662 ldap4pl_add_ext_s(LDAP, DN, Attributes, SCtrls, CCtrls).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
677ldap_add(LDAP, DN, Attributes, MsgID) :-
678 ldap4pl_add_ext(LDAP, DN, Attributes, [], [], MsgID).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
Use ldap_get_ld_errno/1 to get last error.
695ldap_add_s(LDAP, DN, Attributes) :-
696 ldap4pl_add_ext_s(LDAP, DN, Attributes, [], []).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
To delete an attribute completely, simply skip mod_values
.
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
722ldap_modify_ext(LDAP, DN, Attributes, SCtrls, CCtrls, MsgID) :-
723 ldap4pl_modify_ext(LDAP, DN, Attributes, SCtrls, CCtrls, MsgID).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
To delete an attribute completely, simply skip mod_values
.
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
751ldap_modify_ext_s(LDAP, DN, Attributes, SCtrls, CCtrls) :-
752 ldap4pl_modify_ext_s(LDAP, DN, Attributes, SCtrls, CCtrls).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
To delete an attribute completely, simply skip mod_values
.
768ldap_modify(LDAP, DN, Attributes, MsgID) :-
769 ldap4pl_modify_ext(LDAP, DN, Attributes, [], [], MsgID).
Attributes
is an array of terms in the format of:
ldapmod( mod_op([ldap_mod_add]), mod_type(objectClass), mod_values([posixGroup, top]) )
To delete an attribute completely, simply skip mod_values
.
Use ldap_get_ld_errno/1 to get last error.
787ldap_modify_s(LDAP, DN, Attributes) :-
788 ldap4pl_modify_ext_s(LDAP, DN, Attributes, [], []).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
804ldap_delete_ext(LDAP, DN, SCtrls, CCtrls, MsgID) :-
805 ldap4pl_delete_ext(LDAP, DN, SCtrls, CCtrls, MsgID).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
823ldap_delete_ext_s(LDAP, DN, SCtrls, CCtrls) :-
824 ldap4pl_delete_ext_s(LDAP, DN, SCtrls, CCtrls).
830ldap_delete(LDAP, DN, MsgID) :-
831 ldap4pl_delete_ext(LDAP, DN, [], [], MsgID).
Use ldap_get_ld_errno/1 to get last error.
839ldap_delete_s(LDAP, DN) :-
840 ldap4pl_delete_ext_s(LDAP, DN, [], []).
846ldap_modrdn(LDAP, DN, NewRDN, MsgID) :-
847 ldap4pl_modrdn(LDAP, DN, NewRDN, MsgID).
Use ldap_get_ld_errno/1 to get last error.
855ldap_modrdn_s(LDAP, DN, NewRDN) :-
856 ldap4pl_modrdn_s(LDAP, DN, NewRDN).
862ldap_modrdn2(LDAP, DN, NewRDN, DeleteOldRDN, MsgID) :-
863 ldap4pl_modrdn2(LDAP, DN, NewRDN, DeleteOldRDN, MsgID).
Use ldap_get_ld_errno/1 to get last error.
871ldap_modrdn2_s(LDAP, DN, NewRDN, DeleteOldRDN) :-
872 ldap4pl_modrdn2_s(LDAP, DN, NewRDN, DeleteOldRDN).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
888ldap_rename(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, SCtrls, CCtrls, MsgID) :-
889 ldap4pl_rename(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, SCtrls, CCtrls, MsgID).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
907ldap_rename_s(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, SCtrls, CCtrls) :-
908 ldap4pl_rename_s(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, SCtrls, CCtrls).
914ldap_rename2(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, MsgID) :-
915 ldap4pl_rename(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, [], [], MsgID).
Use ldap_get_ld_errno/1 to get last error.
923ldap_rename2_s(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN) :-
924 ldap4pl_rename_s(LDAP, DN, NewRDN, NewSuperior, DeleteOldRDN, [], []).
930ldap_get_ld_errno(ErrorCode) :-
931 ldap4pl_get_ld_errno(ErrorCode).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
947ldap_extended_operation(LDAP, RequestOID, RequestData, SCtrls, CCtrls, MsgID) :-
948 ldap4pl_extended_operation(LDAP, RequestOID, RequestData, SCtrls, CCtrls, MsgID).
SCtrls
and CCtrls
are arrays of terms in the format
of:
ldapcontrol( ldctl_oid(...), ldctl_value(bv_len(...), bv_val(...)), ldctl_iscritical(true) )
Use ldap_get_ld_errno/1 to get last error.
966ldap_extended_operation_s(LDAP, RequestOID, RequestData, SCtrls, CCtrls, RetOID, RetData) :-
967 ldap4pl_extended_operation_s(LDAP, RequestOID, RequestData, SCtrls, CCtrls, RetOID, RetData).
URL
is a valid LDAP URL.
973ldap_is_ldap_url(URL) :-
974 ldap4pl_is_ldap_url(URL).
Desc
is in the format of:
lud( lud_scheme(ldap), lud_host(''), lud_port(389), lud_dn(''), lud_attrs([]), lud_scope(0), lud_filter(''), lud_exts([]), lud_crit_exts(0) )
995ldap_url_parse(URL, Desc) :-
996 ldap4pl_url_parse(URL, Desc)
Prolog bindings to OpenLDAP
This module provides bindings to OpenLDAP API. Most APIs have been implemented and the names are aligned with OpenLDAP API, so for detailed description please check here.