ldap-client-0.2.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.

Tls String TLSSettings

LDAP over TLS.

Instances

data PortNumber :: * #

Use the Num instance (i.e. use a literal) to create a PortNumber value with the correct network-byte-ordering. You should not use the PortNum constructor. It will be removed in the next release.

>>> 1 :: PortNumber
1
>>> read "1" :: PortNumber
1

Instances

Enum PortNumber 
Eq PortNumber 
Integral PortNumber 
Num PortNumber 
Ord PortNumber 
Read PortNumber 
Real PortNumber 
Show PortNumber 
Storable PortNumber 

data Ldap Source #

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

Instances

Eq Ldap Source # 

Methods

(==) :: Ldap -> Ldap -> Bool #

(/=) :: Ldap -> Ldap -> Bool #

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 

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

Perform the Bind operation synchronously. Raises ResponseError on failures.

externalBind :: Ldap -> Dn -> Maybe Text -> IO () Source #

Perform a SASL EXTERNAL 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

Semigroup (Mod a) Source # 

Methods

(<>) :: Mod a -> Mod a -> Mod a #

sconcat :: NonEmpty (Mod a) -> Mod a #

stimes :: Integral b => b -> Mod a -> Mod a #

Monoid (Mod a) Source # 

Methods

mempty :: Mod a #

mappend :: Mod a -> Mod a -> Mod a #

mconcat :: [Mod a] -> 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

Eq Scope Source # 

Methods

(==) :: Scope -> Scope -> Bool #

(/=) :: Scope -> Scope -> Bool #

Show Scope Source # 

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

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

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

Eq Oid Source # 

Methods

(==) :: Oid -> Oid -> Bool #

(/=) :: Oid -> Oid -> Bool #

Show Oid Source # 

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

IsString Oid Source # 

Methods

fromString :: String -> Oid #

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

Eq Dn Source # 

Methods

(==) :: Dn -> Dn -> Bool #

(/=) :: Dn -> Dn -> Bool #

Show Dn Source # 

Methods

showsPrec :: Int -> Dn -> ShowS #

show :: Dn -> String #

showList :: [Dn] -> ShowS #

newtype Attr Source #

Attribute name.

Constructors

Attr Text 

Instances

Eq Attr Source # 

Methods

(==) :: Attr -> Attr -> Bool #

(/=) :: Attr -> Attr -> Bool #

Show Attr Source # 

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

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 :: * -> * #

Non-empty (and non-strict) list type.

Since: 4.9.0.0

Instances

Monad NonEmpty 

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty 

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

MonadFix NonEmpty 

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty 

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Generic1 NonEmpty 

Associated Types

type Rep1 (NonEmpty :: * -> *) :: * -> * #

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

MonadZip NonEmpty 

Methods

mzip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

mzipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

munzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) #

IsList (NonEmpty a) 

Associated Types

type Item (NonEmpty a) :: * #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Eq a => Eq (NonEmpty a) 

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Data a => Data (NonEmpty a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) #

toConstr :: NonEmpty a -> Constr #

dataTypeOf :: NonEmpty a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) #

gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

Ord a => Ord (NonEmpty a) 

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Read a => Read (NonEmpty a) 
Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Semigroup (NonEmpty a) 

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

ToAsn1 a => ToAsn1 (NonEmpty a) Source # 

Methods

toAsn1 :: NonEmpty a -> Endo [ASN1] Source #

type Rep1 NonEmpty 
type Rep (NonEmpty a) 
type Item (NonEmpty a) 
type Item (NonEmpty a) = a