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_util, [
   17    ldap_parse_search_result/3,    % +LDAP, +Result, -List
   18    ldap_simple_auth/3,            % +URL, +Who, +Passwd
   19    ldap_add_s2/3,                 % +LDAP, +DN, +Entry
   20    ldap_modify_s2/3               % +LDAP, +DN, +Operations
   21]).

Utilities to make life easier.

This module provides utilities for OpenLDAP API Prolog bindings.

author
- Hongxin Liang <hongxin.liang@ericsson.com>
See also
- http://www.openldap.org/ */
license
- Apache License Version 2.0
   33:- use_module(ldap4pl).
 ldap_parse_search_result(+LDAP, +Result, -List) is det
Walk through LDAP search results chain and build up a complete list in the format of:
[
    _{dn:..., attributes:_{a1:[], a2:[]}}
    _{dn:..., attributes:_{a1:[], a2:[]}}
]
   47ldap_parse_search_result(LDAP, Result, List) :-
   48    iterate_entries(LDAP, Result, List).
   49
   50iterate_entries(LDAP, Result, List) :-
   51    (   ldap_first_entry(LDAP, Result, Entry)
   52    ->  iterate_entries0(LDAP, Entry, List0),
   53        parse_entry(LDAP, Entry, Dict),
   54        List = [Dict|List0]
   55    ;   List = []
   56    ).
   57
   58iterate_entries0(LDAP, Entry, List) :-
   59    (   ldap_next_entry(LDAP, Entry, NextEntry)
   60    ->  iterate_entries0(LDAP, NextEntry, List0),
   61        parse_entry(LDAP, NextEntry, Dict),
   62        List = [Dict|List0]
   63    ;   List = []
   64    ).
   65
   66parse_entry(LDAP, Entry, Dict) :-
   67    iterate_attributes(LDAP, Entry, Attributes),
   68    ldap_get_dn(LDAP, Entry, DN),
   69    Dict = _{dn:DN, attributes:Attributes}.
   70
   71iterate_attributes(LDAP, Entry, Attributes) :-
   72    (   ldap_first_attribute(LDAP, Entry, Attribute, Ber)
   73    ->  iterate_attributes0(LDAP, Entry, Ber, Attributes0),
   74        ldap_get_values(LDAP, Entry, Attribute, Values),
   75        Attributes = Attributes0.put(Attribute, Values)
   76    ;   Attributes = _{}
   77    ).
   78
   79iterate_attributes0(LDAP, Entry, Ber, Attributes) :-
   80    (   ldap_next_attribute(LDAP, Entry, Attribute, Ber)
   81    ->  iterate_attributes0(LDAP, Entry, Ber, Attributes0),
   82        ldap_get_values(LDAP, Entry, Attribute, Values),
   83        Attributes = Attributes0.put(Attribute, Values)
   84    ;   ldap_ber_free(Ber, false),
   85        Attributes = _{}
   86    ).
 ldap_simple_auth(+URI, +Who, +Passwd) is semidet
Do an LDAP simple authentication in a simple way.
   92ldap_simple_auth(URI, Who, Passwd) :-
   93    setup_call_cleanup(
   94        (ldap_initialize(LDAP, URI), ldap_set_option(LDAP, ldap_opt_protocol_version, 3)),
   95        ldap_simple_bind_s(LDAP, Who, Passwd),
   96        ldap_unbind(LDAP)
   97    ).
 ldap_add_s2(+LDAP, +DN, +Entry) is semidet
The same as ldap_add_s/3 while with simplified entry format:
_{objectClass:[posixGroup, top], cn:..., gidNumber:..., description:...}
  108ldap_add_s2(LDAP, DN, Entry) :-
  109    dict_pairs(Entry, _, Pairs),
  110    build_ldapmod_add_list(Pairs, List),
  111    ldap_add_s(LDAP, DN, List).
  112
  113build_ldapmod_add_list([], []) :- !.
  114build_ldapmod_add_list([Attribute-V|T], List) :-
  115    build_ldapmod_add_list(T, List0),
  116    (   is_list(V)
  117    ->  Values = V
  118    ;   Values = [V]
  119    ),
  120    LDAPMod = ldapmod(mod_op([ldap_mod_add]), mod_type(Attribute), mod_values(Values)),
  121    List = [LDAPMod|List0].
 ldap_modify_s2(+LDAP, +DN, +Operations) is semidet
The same as ldap_modify_s/3 while with simplified operation format:
[
    add-street:..,
    delete-street:...,
    add-street:[...],
    replace-street:[...],
    delete-street
]
  138ldap_modify_s2(LDAP, DN, Operations) :-
  139    build_ldapmod_modify_list(Operations, List),
  140    ldap_modify_s(LDAP, DN, List).
  141
  142build_ldapmod_modify_list([], []) :- !.
  143build_ldapmod_modify_list([Op-Attribute:V|T], List) :- !,
  144    build_ldapmod_modify_list(T, List0),
  145    (   is_list(V)
  146    ->  Values = V
  147    ;   Values = [V]
  148    ),
  149    atom_concat(ldap_mod_, Op, Operation),
  150    LDAPMod = ldapmod(mod_op([Operation]), mod_type(Attribute), mod_values(Values)),
  151    List = [LDAPMod|List0].
  152build_ldapmod_modify_list([delete-Attribute|T], List) :- !,
  153    build_ldapmod_modify_list(T, List0),
  154    LDAPMod = ldapmod(mod_op([ldap_mod_delete]), mod_type(Attribute)),
  155    List = [LDAPMod|List0]