/usr/lib/ocaml/ocamldap/ldap_funclient.mli is in libldap-ocaml-dev 2.1.8-10build7.
This file is owned by root:root, with mode 0o644.
The actual contents of the file can be viewed below.
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 | (* a functional interface to ldap
Copyright (C) 2004 Eric Stokes, and The California State University
at Northridge
This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License, or (at your option) any later version.
This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
Lesser General Public License for more details.
You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
USA
*)
(** a functional ldap client interface *)
open Unix
open Ldap_types
open Lber
type msgid
type conn
type modattr = modify_optype * string * string list
type result = Ldap_types.search_result_entry list
type entry = Ldap_types.search_result_entry
type authmethod = [ `SIMPLE | `SASL ]
type search_result = [ `Entry of entry | `Referral of string list ]
(** Initializes the conn data structure, and opens a connection to the
server. init
[["ldap://rrhost.example.com/";"ldap://backup.example.com:1389"]].
init is round robin dns aware, if dns returns multiple mappings it
will try each one before finially failing. It also takes a list of
hostnames, so you can specify backup servers to try. SSL and TLS are
supported if selected at compile time.
@param version the protocol version to use to
connect, default is version 3. And actually, version 2 will probably
not work correctly without some tweaking.
@raise LDAP_Failure any
failure to connect to the server will result in LDAP_Failure with
the result_code set to `LOCAL_ERROR.
@raise Failure May raise
Failure "int_of_string" if you pass it a malformed url. May also
raise various lexer errors under the same conditions. *)
val init : ?connect_timeout:int -> ?version:int -> string list -> conn
(** close the connection to the server. You may not use the conn
after you have unbound, if you do you will get an exception. *)
val unbind : conn -> unit
(** authenticatite to the server. In this version only simple binds
are supported, however the ldap_protocol.ml module DOES implement
sasl binds. It would be fairly easy to support them here. We
eventually will.
@param who the dn to bind as
@param cred the credentials to authenticate with. For `SIMPLE binds
this is a password, but for `SASL binds it can be nearly
anything. Perhaps a hash of the thumb print of your first born is
sufficent.
@param auth_method either `SIMPLE (the default) or `SASL
@raise LDAP_Failure for bind errors such as `INVALID_CREDENTIALS
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val bind_s :
?who:string -> ?cred:string -> ?auth_method:[> `SIMPLE ] -> conn -> unit
(** Search for the given entry with the specified base node and search
scope, optionally limiting the returned attributes to those listed in
'attrs'. aliasderef sets the server's alias dereferencing policy,
sizelimit is the number of entries to return, timelimit is the number
of seconds to allow the search to run for, attrsonly tells the server
not to return the values. This is the asyncronus version of search
(it does not block) you will need to call the get_search_entry
function below to actually get any data back. This function will
return a msgid which you must use when you call get_search_entry.
@param base The dn of the object in the tree to use as the base
object, the search will only cover children of this object, and will
be further governed by scope.
@param scope The depth in the tree to look for the requested
object. There are three possible values, `BASE, `ONELEVEL, and
`SUBTREE. `BASE means to only search the base object, the search
will return exactly 1 or 0 objects. `ONELEVEL means to search one
level under the base, only immediate children of the base object
will be considered. `SUBTREE means to search the entire tree under
the base object.
@param aliasderef Controls when aliases are dereferenced.
@param sizelimit The maximum number of objects to return
@param timelimit The maximum time, in seconds, that the search will
be allowed to run before terminateing.
@param attrs The list of attribute types (names) to include [[]]
(the default) means all.
@param attrsonly return only attribute types (names), not any of the
values
@raise LDAP_Failure for immediate errors (bad filter, etc)
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val search :
?base:string ->
?scope:Ldap_types.search_scope ->
?aliasderef:Ldap_types.alias_deref ->
?sizelimit:int32 ->
?timelimit:int32 ->
?attrs:string list -> ?attrsonly:bool -> conn -> string -> msgid
(** fetch a search entry from the wire using the given msgid. The
entry could be a search entry, OR it could be a referral structure.
@raise LDAP_Failure for all results other than `SUCCESS (except referrals)
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val get_search_entry :
conn ->
msgid ->
[> `Entry of Ldap_types.search_result_entry | `Referral of string list ]
(** abandon the async request attached to msgid.
@raise Encoding_error for encoder errors (unlikely, probably a bug) *)
val abandon : conn -> msgid -> unit
(** This is the syncronus version of search. It blocks until the
search is complete, and returns a list of objects. It is exactly the
same in all other ways. *)
val search_s :
?base:string ->
?scope:Ldap_types.search_scope ->
?aliasderef:Ldap_types.alias_deref ->
?sizelimit:int32 ->
?timelimit:int32 ->
?attrs:string list ->
?attrsonly:bool ->
conn ->
string ->
[> `Entry of Ldap_types.search_result_entry | `Referral of string list ]
list
(** add entry to the directory
@raise LDAP_Failure for all results other than `SUCCESS
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val add_s : conn -> entry -> unit
(** delete the entry named by dn from the directory
@raise LDAP_Failure for all results other than `SUCCESS
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val delete_s : conn -> dn:string -> unit
(** apply the list of modifications to the named entry
@param dn The dn of the object to modify
@param mods The list of modifications to apply
@raise LDAP_Failure for all results other than `SUCCESS
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val modify_s :
conn ->
dn:string ->
mods:(Ldap_types.modify_optype * string * string list) list -> unit
(** change the rdn, and optionally the superior entry of dn
@param deleteoldrdn Delete the old rdn value, (default true)
@param newsup The new superior dn of the object (default None)
@param dn The dn of the object to modify
@param newrdn The new rdn value (eg. cn=bob)
@raise LDAP_Failure for all results other than `SUCCESS
@raise Decoding_error for decoder errors (unlikely, probably a bug)
@raise Encoding_error for encoder errors (unlikely, probably a bug)
*)
val modrdn_s :
?deleteoldrdn:bool ->
?newsup:'a option -> conn -> dn:string -> newdn:string -> unit
|