ldap-client-0.1.0: Pure Haskell LDAP Client Library

Safe HaskellNone
LanguageHaskell2010

Ldap.Client

Contents

Description

This module is intended to be imported qualified

import qualified Ldap.Client as Ldap

Synopsis

Documentation

with :: Host -> PortNumber -> (Ldap -> IO a) -> IO (Either LdapError a) Source

The entrypoint into LDAP.

It catches all LDAP-related exceptions.

data Host Source

LDAP host.

Constructors

Plain String

Plain LDAP. Do not use!

Insecure String

LDAP over TLS without the certificate validity check. Only use for testing!

Secure String

LDAP over TLS. Use!

Instances

data Ldap Source

A token. All functions that interact with the Directory require one.

Instances

data LdapError Source

Various failures that can happen when working with LDAP.

Constructors

IOError IOError

Network failure.

ParseError ASN1Error

Invalid ASN.1 data received from the server.

ResponseError ResponseError

An LDAP operation failed.

DisconnectError Disconnect

Notice of Disconnection has been received.

data ResponseError Source

Response indicates a failed operation.

Constructors

ResponseInvalid Request Response

LDAP server did not follow the protocol, so ldap-client couldn't make sense of the response.

ResponseErrorCode Request ResultCode Dn Text

The response contains a result code indicating failure and an error message.

Bind

newtype Password Source

User's password.

Constructors

Password ByteString 

Instances

bind :: Ldap -> Dn -> Password -> IO () Source

Perform the Bind operation synchronously. Raises ResponseError on failures.

Search

search :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO [SearchEntry] Source

Perform the Search operation synchronously. Raises ResponseError on failures.

data SearchEntry Source

Entry found during the Search.

Constructors

SearchEntry !Dn !(AttrList []) 

Search modifiers

data Search Source

Search options. Use Mod to change some of those.

Instances

data Mod a Source

Search modifier. Combine using Semigroup and/or Monoid instance.

Instances

Monoid (Mod a) 
Semigroup (Mod a) 

data Scope Source

Scope of the search to be performed.

Constructors

BaseObject

Constrained to the entry named by baseObject.

SingleLevel

Constrained to the immediate subordinates of the entry named by baseObject.

WholeSubtree

Constrained to the entry named by baseObject and to all its subordinates.

Instances

scope :: Scope -> Mod Search Source

Scope of the search (default: WholeSubtree).

size :: Int32 -> Mod Search Source

Maximum number of entries to be returned as a result of the Search. No limit if the value is 0 (default: 0).

time :: Int32 -> Mod Search Source

Maximum time (in seconds) allowed for the Search. No limit if the value is 0 (default: 0).

typesOnly :: Bool -> Mod Search Source

Whether Search results are to contain just attribute descriptions, or both attribute descriptions and values (default: False).

data DerefAliases Source

An indicator as to whether or not alias entries (as defined in [RFC4512]) are to be dereferenced during stages of the Search operation.

Constructors

NeverDerefAliases

Do not dereference aliases in searching or in locating the base object of the Search.

DerefInSearching

While searching subordinates of the base object, dereference any alias within the search scope.

DerefFindingBaseObject

Dereference aliases in locating the base object of the Search.

DerefAlways

Dereference aliases both in searching and in locating the base object of the Search.

derefAliases :: DerefAliases -> Mod Search Source

Alias dereference policy (default: NeverDerefAliases).

data Filter Source

Conditions that must be fulfilled in order for the Search to match a given entry.

Constructors

Not !Filter

Filter does not match the entry

And !(NonEmpty Filter)

All filters match the entry

Or !(NonEmpty Filter)

Any filter matches the entry

Present !Attr

Attribute is present in the entry

!Attr := !AttrValue

Attribute's value is equal to the assertion

!Attr :>= !AttrValue

Attribute's value is equal to or greater than the assertion

!Attr :<= !AttrValue

Attribute's value is equal to or less than the assertion

!Attr :~= !AttrValue

Attribute's value approximately matches the assertion

!Attr :=* !(Maybe AttrValue, [AttrValue], Maybe AttrValue)

Glob match

(Maybe Attr, Maybe Attr, Bool) ::= AttrValue

Extensible match

Modify

modify :: Ldap -> Dn -> [Operation] -> IO () Source

Perform the Modify operation synchronously. Raises ResponseError on failures.

data Operation Source

Type of modification being performed.

Constructors

Delete Attr [AttrValue]

Delete values from the attribute. Deletes the attribute if the list is empty or all current values are listed.

Add Attr [AttrValue]

Add values to the attribute, creating it if necessary.

Replace Attr [AttrValue]

Replace all existing values of the attribute with the new list. Deletes the attribute if the list is empty.

Add

add :: Ldap -> Dn -> AttrList NonEmpty -> IO () Source

Perform the Add operation synchronously. Raises ResponseError on failures.

Delete

delete :: Ldap -> Dn -> IO () Source

Perform the Delete operation synchronously. Raises ResponseError on failures.

ModifyDn

newtype RelativeDn Source

A component of Dn.

Constructors

RelativeDn Text 

modifyDn :: Ldap -> Dn -> RelativeDn -> Bool -> Maybe Dn -> IO () Source

Perform the Modify DN operation synchronously. Raises ResponseError on failures.

Compare

compare :: Ldap -> Dn -> Attr -> AttrValue -> IO Bool Source

Perform the Compare operation synchronously. Raises ResponseError on failures.

Extended

newtype Oid Source

Globally unique LDAP object identifier.

Constructors

Oid Text 

Instances

extended :: Ldap -> Oid -> Maybe ByteString -> IO () Source

Perform the Extended operation synchronously. Raises ResponseError on failures.

Miscellanous

newtype Dn Source

Unique identifier of an LDAP entry.

Constructors

Dn Text 

Instances

newtype Attr Source

Attribute name.

Constructors

Attr Text 

Instances

type AttrValue = ByteString Source

Attribute value.

type AttrList f = [(Attr, f AttrValue)] Source

List of attributes and their values. f is the structure these values are in, e.g. NonEmpty.

Re-exports

data NonEmpty a :: * -> *

Instances

Monad NonEmpty 
Functor NonEmpty 
MonadFix NonEmpty 
Applicative NonEmpty 
Foldable NonEmpty 
Traversable NonEmpty 
Generic1 NonEmpty 
MonadZip NonEmpty 
IsList (NonEmpty a) 
Eq a => Eq (NonEmpty a) 
Data a => Data (NonEmpty a) 
Ord a => Ord (NonEmpty a) 
Read a => Read (NonEmpty a) 
Show a => Show (NonEmpty a) 
Generic (NonEmpty a) 
NFData a => NFData (NonEmpty a) 
Hashable a => Hashable (NonEmpty a) 
Semigroup (NonEmpty a) 
ToAsn1 a => ToAsn1 (NonEmpty a) 
Typeable (* -> *) NonEmpty 
type Rep1 NonEmpty = D1 D1NonEmpty (C1 C1_0NonEmpty ((:*:) (S1 NoSelector Par1) (S1 NoSelector (Rec1 [])))) 
type Rep (NonEmpty a) = D1 D1NonEmpty (C1 C1_0NonEmpty ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 [a])))) 
type Item (NonEmpty a) = a