Skip to content

Commit

Permalink
[eldap] Initial copy of Tobbe's eldap client
Browse files Browse the repository at this point in the history
Copied with Torbjorns permission from https://github.com/etnt/eldap.git
  • Loading branch information
Torbjorn Tornkvist authored and dgud committed Mar 20, 2012
1 parent 725032a commit d8dbf15
Show file tree
Hide file tree
Showing 11 changed files with 2,445 additions and 0 deletions.
4 changes: 4 additions & 0 deletions lib/eldap/.gitignore
@@ -0,0 +1,4 @@
*.beam
*.asn1db
src/ELDAPv3.hrl
src/ELDAPv3.erl
21 changes: 21 additions & 0 deletions lib/eldap/LICENSE
@@ -0,0 +1,21 @@

Copyright (c) 2010, Torbjorn Tornkvist

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.

33 changes: 33 additions & 0 deletions lib/eldap/README
@@ -0,0 +1,33 @@
Hi,

This is 'eldap', the Erlang LDAP library.

It exports an API that can do all possible operations
you may want to do against an LDAP server. The code has
been tested to work at some point, but only the bind
and search operations are running daily in our products,
so there may be bugs lurking in some parts of the code.

To just use eldap for doing authentication, do like in:

{ok,X} = eldap:open(["ldap.mycorp.com"], []).
eldap:simple_bind(X, "uid=tobbe,ou=People,dc=mycorp,dc=com", "passwd").

In the doc/README.example you'll find a trace from a
Erlang shell session as an example on how to setup a
connection, authenticate (bind) and perform a search.
Note that by using the option {ssl, true}, you should
be able to setup an SSL tunnel (LDAPS) if your Erlang
system has been configured with SSL.

In the test directory there are some hints and examples
on how to test the code and how to setup and populate
an OpenLDAP server. The 'eldap' code has been tested
agains OpenLDAP, IPlanet and ActiveDirectory servers.

If you plan to incorporate this code into your system
I suggest that you build a server/supervisor harnesk
that uses 'eldap' (as we have done in our products).

Good luck !
/Tobbe
278 changes: 278 additions & 0 deletions lib/eldap/asn1/ELDAPv3.asn1
@@ -0,0 +1,278 @@
-- Lightweight-Directory-Access-Protocol-V3 {1 3 6 1 1 18}
-- Copyright (C) The Internet Society (2006). This version of
-- this ASN.1 module is part of RFC 4511; see the RFC itself
-- for full legal notices.
ELDAPv3 DEFINITIONS
IMPLICIT TAGS
EXTENSIBILITY IMPLIED ::=

BEGIN

LDAPMessage ::= SEQUENCE {
messageID MessageID,
protocolOp CHOICE {
bindRequest BindRequest,
bindResponse BindResponse,
unbindRequest UnbindRequest,
searchRequest SearchRequest,
searchResEntry SearchResultEntry,
searchResDone SearchResultDone,
searchResRef SearchResultReference,
modifyRequest ModifyRequest,
modifyResponse ModifyResponse,
addRequest AddRequest,
addResponse AddResponse,
delRequest DelRequest,
delResponse DelResponse,
modDNRequest ModifyDNRequest,
modDNResponse ModifyDNResponse,
compareRequest CompareRequest,
compareResponse CompareResponse,
abandonRequest AbandonRequest,
extendedReq ExtendedRequest,
extendedResp ExtendedResponse,
...,
intermediateResponse IntermediateResponse },
controls [0] Controls OPTIONAL }

MessageID ::= INTEGER (0 .. maxInt)

maxInt INTEGER ::= 2147483647 -- (2^^31 - 1) --

LDAPString ::= OCTET STRING -- UTF-8 encoded,
-- [ISO10646] characters

LDAPOID ::= OCTET STRING -- Constrained to <numericoid>
-- [RFC4512]

LDAPDN ::= LDAPString -- Constrained to <distinguishedName>
-- [RFC4514]

RelativeLDAPDN ::= LDAPString -- Constrained to <name-component>
-- [RFC4514]

AttributeDescription ::= LDAPString
-- Constrained to <attributedescription>
-- [RFC4512]

AttributeValue ::= OCTET STRING

AttributeValueAssertion ::= SEQUENCE {
attributeDesc AttributeDescription,
assertionValue AssertionValue }

AssertionValue ::= OCTET STRING

PartialAttribute ::= SEQUENCE {
type AttributeDescription,
vals SET OF value AttributeValue }

Attribute ::= PartialAttribute(WITH COMPONENTS {
...,
vals (SIZE(1..MAX))})

MatchingRuleId ::= LDAPString

LDAPResult ::= SEQUENCE {
resultCode ENUMERATED {
success (0),
operationsError (1),
protocolError (2),
timeLimitExceeded (3),
sizeLimitExceeded (4),
compareFalse (5),
compareTrue (6),
authMethodNotSupported (7),
strongerAuthRequired (8),
-- 9 reserved --
referral (10),
adminLimitExceeded (11),
unavailableCriticalExtension (12),
confidentialityRequired (13),
saslBindInProgress (14),

noSuchAttribute (16),
undefinedAttributeType (17),
inappropriateMatching (18),
constraintViolation (19),
attributeOrValueExists (20),
invalidAttributeSyntax (21),
-- 22-31 unused --
noSuchObject (32),
aliasProblem (33),
invalidDNSyntax (34),
-- 35 reserved for undefined isLeaf --
aliasDereferencingProblem (36),
-- 37-47 unused --
inappropriateAuthentication (48),
invalidCredentials (49),
insufficientAccessRights (50),
busy (51),
unavailable (52),
unwillingToPerform (53),
loopDetect (54),
-- 55-63 unused --
namingViolation (64),
objectClassViolation (65),
notAllowedOnNonLeaf (66),
notAllowedOnRDN (67),
entryAlreadyExists (68),
objectClassModsProhibited (69),
-- 70 reserved for CLDAP --
affectsMultipleDSAs (71),
-- 72-79 unused --
other (80),
... },
matchedDN LDAPDN,
diagnosticMessage LDAPString,
referral [3] Referral OPTIONAL }

Referral ::= SEQUENCE SIZE (1..MAX) OF uri URI

URI ::= LDAPString -- limited to characters permitted in
-- URIs

Controls ::= SEQUENCE OF control Control

Control ::= SEQUENCE {
controlType LDAPOID,
criticality BOOLEAN DEFAULT FALSE,
controlValue OCTET STRING OPTIONAL }

BindRequest ::= [APPLICATION 0] SEQUENCE {
version INTEGER (1 .. 127),
name LDAPDN,
authentication AuthenticationChoice }

AuthenticationChoice ::= CHOICE {
simple [0] OCTET STRING,
-- 1 and 2 reserved
sasl [3] SaslCredentials,
... }

SaslCredentials ::= SEQUENCE {
mechanism LDAPString,
credentials OCTET STRING OPTIONAL }

BindResponse ::= [APPLICATION 1] SEQUENCE {
COMPONENTS OF LDAPResult,
serverSaslCreds [7] OCTET STRING OPTIONAL }

UnbindRequest ::= [APPLICATION 2] NULL

SearchRequest ::= [APPLICATION 3] SEQUENCE {
baseObject LDAPDN,
scope ENUMERATED {
baseObject (0),
singleLevel (1),
wholeSubtree (2),
... },
derefAliases ENUMERATED {
neverDerefAliases (0),
derefInSearching (1),
derefFindingBaseObj (2),
derefAlways (3) },
sizeLimit INTEGER (0 .. maxInt),
timeLimit INTEGER (0 .. maxInt),
typesOnly BOOLEAN,
filter Filter,
attributes AttributeSelection }

AttributeSelection ::= SEQUENCE OF selector LDAPString
-- The LDAPString is constrained to
-- <attributeSelector> in Section 4.5.1.8

Filter ::= CHOICE {
and [0] SET SIZE (1..MAX) OF filter Filter,
or [1] SET SIZE (1..MAX) OF filter Filter,
not [2] Filter,
equalityMatch [3] AttributeValueAssertion,
substrings [4] SubstringFilter,
greaterOrEqual [5] AttributeValueAssertion,
lessOrEqual [6] AttributeValueAssertion,
present [7] AttributeDescription,
approxMatch [8] AttributeValueAssertion,
extensibleMatch [9] MatchingRuleAssertion,
... }

SubstringFilter ::= SEQUENCE {
type AttributeDescription,
substrings SEQUENCE SIZE (1..MAX) OF substring CHOICE {
initial [0] AssertionValue, -- can occur at most once
any [1] AssertionValue,
final [2] AssertionValue } -- can occur at most once
}

MatchingRuleAssertion ::= SEQUENCE {
matchingRule [1] MatchingRuleId OPTIONAL,
type [2] AttributeDescription OPTIONAL,
matchValue [3] AssertionValue,
dnAttributes [4] BOOLEAN DEFAULT FALSE }

SearchResultEntry ::= [APPLICATION 4] SEQUENCE {
objectName LDAPDN,
attributes PartialAttributeList }

PartialAttributeList ::= SEQUENCE OF
partialAttribute PartialAttribute

SearchResultReference ::= [APPLICATION 19] SEQUENCE
SIZE (1..MAX) OF uri URI

SearchResultDone ::= [APPLICATION 5] LDAPResult

ModifyRequest ::= [APPLICATION 6] SEQUENCE {
object LDAPDN,
changes SEQUENCE OF change SEQUENCE {
operation ENUMERATED {
add (0),
delete (1),
replace (2),
... },
modification PartialAttribute } }

ModifyResponse ::= [APPLICATION 7] LDAPResult

AddRequest ::= [APPLICATION 8] SEQUENCE {
entry LDAPDN,
attributes AttributeList }

AttributeList ::= SEQUENCE OF attribute Attribute

AddResponse ::= [APPLICATION 9] LDAPResult

DelRequest ::= [APPLICATION 10] LDAPDN

DelResponse ::= [APPLICATION 11] LDAPResult

ModifyDNRequest ::= [APPLICATION 12] SEQUENCE {
entry LDAPDN,
newrdn RelativeLDAPDN,
deleteoldrdn BOOLEAN,
newSuperior [0] LDAPDN OPTIONAL }

ModifyDNResponse ::= [APPLICATION 13] LDAPResult

CompareRequest ::= [APPLICATION 14] SEQUENCE {
entry LDAPDN,
ava AttributeValueAssertion }

CompareResponse ::= [APPLICATION 15] LDAPResult

AbandonRequest ::= [APPLICATION 16] MessageID

ExtendedRequest ::= [APPLICATION 23] SEQUENCE {
requestName [0] LDAPOID,
requestValue [1] OCTET STRING OPTIONAL }

ExtendedResponse ::= [APPLICATION 24] SEQUENCE {
COMPONENTS OF LDAPResult,
responseName [10] LDAPOID OPTIONAL,
responseValue [11] OCTET STRING OPTIONAL }

IntermediateResponse ::= [APPLICATION 25] SEQUENCE {
responseName [0] LDAPOID OPTIONAL,
responseValue [1] OCTET STRING OPTIONAL }

END

Empty file added lib/eldap/ebin/.gitignore
Empty file.
32 changes: 32 additions & 0 deletions lib/eldap/include/eldap.hrl
@@ -0,0 +1,32 @@
-ifndef( _ELDAP_HRL ).
-define( _ELDAP_HRL , 1 ).

%%%
%%% Search input parameters
%%%
-record(eldap_search, {
base = [], % Baseobject
filter = [], % Search conditions
scope, % Search scope
attributes = [], % Attributes to be returned
types_only = false, % Return types+values or types
timeout = 0 % Timelimit for search
}).

%%%
%%% Returned search result
%%%
-record(eldap_search_result, {
entries = [], % List of #eldap_entry{} records
referrals = [] % List of referrals
}).

%%%
%%% LDAP entry
%%%
-record(eldap_entry, {
object_name = "", % The DN for the entry
attributes = [] % List of {Attribute, Value} pairs
}).

-endif.
9 changes: 9 additions & 0 deletions lib/eldap/src/eldap.app.src
@@ -0,0 +1,9 @@
{application, eldap,
[{description, "Ldap api"},
{vsn, "%VSN%"},
{modules, []},
{registered, []},
{applications, [kernel, stdlib]},
{mod, { eldap_app, []}},
{env, []}
]}.

0 comments on commit d8dbf15

Please sign in to comment.