Did you know ... Search Documentation:
Pack ldap4pl -- prolog/ldap4pl.pl
PublicShow source

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.

author
- Hongxin Liang <hongxin.liang@ericsson.com>
See also
- http://www.openldap.org/
license
- Apache License Version 2.0
 ldap_initialize(-LDAP, +URI) is semidet
Initialize the LDAP library and open a connection to an LDAP server.

Use ldap_get_ld_errno/1 to get last error.

 ldap_unbind(+LDAP) is semidet
Unbind from the directory, terminate the current association, and free the resources contained in the ld structure.

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.

 ldap_unbind_s(+LDAP) is semidet
Unbind from the directory, terminate the current association, and free the resources contained in the ld structure.

Use ldap_get_ld_errno/1 to get last error.

 ldap_unbind_ext(+LDAP, +SCtrls, +CCtrls) is semidet
Unbind from the directory, terminate the current association, and free the resources contained in the ld structure.

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.

 ldap_unbind_ext_s(+LDAP, +SCtrls, +CCtrls) is semidet
Unbind from the directory, terminate the current association, and free the resources contained in the ld structure.

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.

 ldap_bind(+LDAP, +Who, +Cred, +Method, -MsgID) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.
 ldap_bind_s(+LDAP, +Who, +Cred, +Method) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.

Use ldap_get_ld_errno/1 to get last error.

 ldap_simple_bind(+LDAP, +Who, +Passwd, -MsgID) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.
 ldap_simple_bind_s(+LDAP, +Who, +Passwd) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.

Use ldap_get_ld_errno/1 to get last error.

 ldap_sasl_bind(+LDAP, +DN, +Mechanism, +Cred, +SCtrls, +CCtrls, -MsgID) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_sasl_bind_s(+LDAP, +DN, +Mechanism, +Cred, +SCtrls, +CCtrls, -ServerCred) is semidet
After an association with an LDAP server is made using ldap_initialize/2, an LDAP bind operation should be performed before other operations are attempted over the connection.

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.

 ldap_parse_sasl_bind_result(+LDAP, +Result, -ServerCred, +FreeIt) is semidet
Obtain any server credentials sent from the server.

ServerCred is in the format of:

berval(bv_len(...), bv_val(...))

Use ldap_get_ld_errno/1 to get last error.

 ldap_set_option(+LDAP, +Option, +Value) is semidet
Provide access to options stored either in a LDAP handle or as global options, where applicable.

Use ldap_get_ld_errno/1 to get last error.

To be done
- This API is not fully implemented yet and supported options are:
LDAP_OPT_DEREF
LDAP_OPT_DIAGNOSTIC_MESSAGE
LDAP_OPT_MATCHED_DN
LDAP_OPT_PROTOCOL_VERSION
LDAP_OPT_REFERRAL_URLS
LDAP_OPT_REFERRALS
LDAP_OPT_RESTART
LDAP_OPT_RESULT_CODE
LDAP_OPT_SIZELIMIT
LDAP_OPT_TIMELIMIT
 ldap_get_option(+LDAP, +Option, ?Value) is semidet
Provide access to options stored either in a LDAP handle or as global options, where applicable.

Use ldap_get_ld_errno/1 to get last error.

To be done
- This API is not fully implemented yet and supported options are:
LDAP_OPT_DEREF
LDAP_OPT_DIAGNOSTIC_MESSAGE
LDAP_OPT_MATCHED_DN
LDAP_OPT_PROTOCOL_VERSION
LDAP_OPT_REFERRAL_URLS
LDAP_OPT_REFERRALS
LDAP_OPT_RESTART
LDAP_OPT_RESULT_CODE
LDAP_OPT_SIZELIMIT
LDAP_OPT_TIMELIMIT
 ldap_result(+LDAP, +MsgID, +All, -Result) is semidet
 ldap_result(+LDAP, +MsgID, +All, +Timeout, -Result) is semidet
Wait for and return the result of an operation previously initiated by one of the LDAP asynchronous operation routines.

Use ldap_get_ld_errno/1 to get last error.

 ldap_msgfree(+Msg) is semidet
Free the memory allocated for result(s).
 ldap_msgtype(+Msg, ?Type) is semidet
Return the type of a message.
 ldap_msgid(+Msg, ?ID) is semidet
Return the message id of a message.
 ldap_search_ext(+LDAP, +Query, +SCtrls, +CCtrls, +Timeout, +SizeLimit, -MsgID) is semidet
 ldap_search_ext(+LDAP, +Query, +SCtrls, +CCtrls, +SizeLimit, -MsgID) is semidet
Perform LDAP search operations.

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)
)
 ldap_search_ext_s(+LDAP, +Query, +SCtrls, +CCtrls, +Timeout, +SizeLimit, -Result) is semidet
 ldap_search_ext_s(+LDAP, +Query, +SCtrls, +CCtrls, +SizeLimit, -Result) is semidet
Perform LDAP search operations.

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.

 ldap_search(+LDAP, +Query, -MsgID) is semidet
Perform LDAP search operations.

Query is in the format of:

query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))
 ldap_search_s(+LDAP, +Query, -Result) is semidet
 ldap_search_st(+LDAP, +Query, +Timeout, -Result) is semidet
Perform LDAP search operations.

Query is in the format of:

query(base(...), scope(...), filter(...), attrs([...]), attrsonly(false))

Use ldap_get_ld_errno/1 to get last error.

 ldap_count_entries(+LDAP, +Result, ?Count) is semidet
Obtain a count of the number of entries in the search result.
 ldap_first_entry(+LDAP, +Result, -Entry) is semidet
Retrieve the first entry in a chain of search results.
 ldap_next_entry(+LDAP, +Entry, -NextEntry) is semidet
Retrieve the next entry following Entry.
 ldap_first_attribute(+LDAP, +Entry, -Attribute, -Ber) is semidet
Retrieve the first attribute of the entry.

Ber must be freed by calling ldap_ber_free/2 with second argument as false.

 ldap_next_attribute(+LDAP, +Entry, -Atrribute, +Berval) is semidet
Retrieve the next attribute in the entry. Ber must have been unified by calling ldap_first_attribute/4 prior to this predicate.
 ldap_ber_free(+Ber, +FreeBuf) is det
Frees a BerElement pointed to by Ber.
 ldap_get_values(+LDAP, +Entry, +Attribute, -Values) is semidet
Get values of the attribute.
 ldap_get_dn(+LDAP, +Entry, ?DN) is semidet
Get DN of the entry.
 ldap_parse_result(+LDAP, +Result, ?ErrorCode, -MatchedDN, -ErrorMsg, -Referrals, -SCtrls, +FreeIt) is semidet
Extract information from a result message. 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.

 ldap_err2string(+ErrorMsg, -ErrorString) is semidet
Provides short description of the various codes returned by routines in this library.
 ldap_compare_ext(+LDAP, +DN, +Attribute, +BerVal, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP compare operation.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_compare_ext_s(+LDAP, +DN, +Attribute, +BerVal, +SCtrls, +CCtrls, -Result) is semidet
Perform an LDAP compare operation.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_compare(+LDAP, +DN, +Attribute, +Value, -MsgID) is semidet
Perform an LDAP compare operation.
 ldap_compare_s(+LDAP, +DN, +Attribute, +Value, -Result) is semidet
Perform an LDAP compare operation.
 ldap_abandon_ext(+LDAP, +MsgID, +SCtrls, +CCtrls) is semidet
Send a LDAP Abandon request for an operation in progress.

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.

 ldap_abandon(+LDAP, +MsgID) is semidet
Send a LDAP Abandon request for an operation in progress.

Use ldap_get_ld_errno/1 to get last error.

 ldap_add_ext(+LDAP, +DN, +Attributes, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP add operation.

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)
)
 ldap_add_ext_s(+LDAP, +DN, +Attributes, +SCtrls, +CCtrls) is semidet
Perform an LDAP add operation.

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.

 ldap_add(+LDAP, +DN, +Attributes, -MsgID) is semidet
Perform an LDAP add operation.

Attributes is an array of terms in the format of:

ldapmod(
    mod_op([ldap_mod_add]),
    mod_type(objectClass),
    mod_values([posixGroup, top])
)
 ldap_add_s(+LDAP, +DN, +Attributes) is semidet
Perform an LDAP add operation.

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.

 ldap_modify_ext(+LDAP, +DN, +Attributes, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP modify operation.

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)
)
 ldap_modify_ext_s(+LDAP, +DN, +Attributes, +SCtrls, +CCtrls) is semidet
Perform an LDAP modify operation.

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.

 ldap_modify(+LDAP, +DN, +Attributes, -MsgID) is semidet
Perform an LDAP modify operation.

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.

 ldap_modify_s(+LDAP, +DN, +Attributes) is semidet
Perform an LDAP modify operation.

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.

 ldap_delete_ext(+LDAP, +DN, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP delete operation.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_delete_ext_s(+LDAP, +DN, +SCtrls, +CCtrls) is semidet
Perform an LDAP delete operation.

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.

 ldap_delete(+LDAP, +DN, -MsgID) is semidet
Perform an LDAP delete operation.
 ldap_delete_s(+LDAP, +DN) is semidet
Perform an LDAP delete operation.

Use ldap_get_ld_errno/1 to get last error.

 ldap_modrdn(+LDAP, +DN, +NewRDN, -MsgID) is semidet
Perform an LDAP rename operation.
 ldap_modrdn_s(+LDAP, +DN, +NewRDN) is semidet
Perform an LDAP rename operation.

Use ldap_get_ld_errno/1 to get last error.

 ldap_modrdn2(+LDAP, +DN, +NewRDN, +DeleteOldRDN, -MsgID) is semidet
Perform an LDAP rename operation.
 ldap_modrdn2_s(+LDAP, +DN, +NewRDN, +DeleteOldRDN) is semidet
Perform an LDAP rename operation.

Use ldap_get_ld_errno/1 to get last error.

 ldap_rename(+LDAP, +DN, +NewRDN, +NewSuperior, +DeleteOldRDN, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP rename operation.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_rename_s(+LDAP, +DN, +NewRDN, +NewSuperior, +DeleteOldRDN, +SCtrls, +CCtrls) is semidet
Perform an LDAP rename operation.

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.

 ldap_get_ld_errno(?ErrorCode) is semidet
Get last LDAP operation error.
 ldap_extended_operation(+LDAP, +RequestOID, +RequestData, +SCtrls, +CCtrls, -MsgID) is semidet
Perform an LDAP extended operation.

SCtrls and CCtrls are arrays of terms in the format of:

ldapcontrol(
    ldctl_oid(...),
    ldctl_value(bv_len(...), bv_val(...)),
    ldctl_iscritical(true)
)
 ldap_extended_operation_s(+LDAP, +RequestOID, +RequestData, +SCtrls, +CCtrls, -RetOID, -RetData) is semidet
Perform an LDAP extended operation.

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.

 ldap_is_ldap_url(+URL) is semidet
Check if URL is a valid LDAP URL.
 ldap_url_parse(+URL, -Desc) is semidet
Breaks down an LDAP URL passed in url into its component pieces.

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)
)

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 ldap_result(Arg1, Arg2, Arg3, Arg4, Arg5)
 ldap_search_ext(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 ldap_search_ext_s(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 ldap_search_st(Arg1, Arg2, Arg3, Arg4)