ldap-client-0.4.2: 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 #

with' :: Host -> PortNumber -> (Ldap -> IO a) -> IO a Source #

The entrypoint into LDAP.

runsIn :: (Ldap -> IO a) -> LdapH -> IO a Source #

Provide a LdapH to a function needing an Ldap handle.

runsInEither :: (Ldap -> IO a) -> LdapH -> IO (Either LdapError a) Source #

Provide a LdapH to a function needing an Ldap handle

open :: Host -> PortNumber -> IO LdapH Source #

Creates an LDAP handle. This action is useful for creating your own resource management, such as with 'resource-pool'. The handle must be manually closed with close.

close :: LdapH -> IO () Source #

Closes an LDAP connection. This is to be used in together with open.

data Host Source #

LDAP host.

Constructors

Plain String

Plain LDAP.

Tls String TLSSettings

LDAP over TLS.

Instances
Show Host Source # 
Instance details

Defined in Ldap.Client.Internal

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

data PortNumber #

Port number. Use the Num instance (i.e. use a literal) to create a PortNumber value.

>>> 1 :: PortNumber
1
>>> read "1" :: PortNumber
1
>>> show (12345 :: PortNumber)
"12345"
>>> 50000 < (51000 :: PortNumber)
True
>>> 50000 < (52000 :: PortNumber)
True
>>> 50000 + (10000 :: PortNumber)
60000
Instances
Bounded PortNumber 
Instance details

Defined in Network.Socket.Types

Enum PortNumber 
Instance details

Defined in Network.Socket.Types

Eq PortNumber 
Instance details

Defined in Network.Socket.Types

Integral PortNumber 
Instance details

Defined in Network.Socket.Types

Num PortNumber 
Instance details

Defined in Network.Socket.Types

Ord PortNumber 
Instance details

Defined in Network.Socket.Types

Read PortNumber 
Instance details

Defined in Network.Socket.Types

Real PortNumber 
Instance details

Defined in Network.Socket.Types

Show PortNumber 
Instance details

Defined in Network.Socket.Types

Storable PortNumber 
Instance details

Defined in Network.Socket.Types

data Ldap Source #

An LDAP connection handle

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.

Instances
Eq LdapError Source # 
Instance details

Defined in Ldap.Client

Show LdapError Source # 
Instance details

Defined in Ldap.Client

Exception LdapError Source # 
Instance details

Defined in Ldap.Client

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
Eq Password Source # 
Instance details

Defined in Ldap.Client.Bind

Show Password Source # 
Instance details

Defined in Ldap.Client.Bind

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 []) 
Instances
Eq SearchEntry Source # 
Instance details

Defined in Ldap.Client.Search

Show SearchEntry Source # 
Instance details

Defined in Ldap.Client.Search

Search modifiers

data Search Source #

Search options. Use Mod to change some of those.

Instances
Eq Search Source # 
Instance details

Defined in Ldap.Client.Search

Methods

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

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

Show Search Source # 
Instance details

Defined in Ldap.Client.Search

data Mod a Source #

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

Instances
Semigroup (Mod a) Source # 
Instance details

Defined in Ldap.Client.Search

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 # 
Instance details

Defined in Ldap.Client.Search

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 # 
Instance details

Defined in Ldap.Asn1.Type

Methods

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

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

Show Scope Source # 
Instance details

Defined in Ldap.Asn1.Type

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.

Instances
Eq DerefAliases Source # 
Instance details

Defined in Ldap.Asn1.Type

Show DerefAliases Source # 
Instance details

Defined in Ldap.Asn1.Type

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.

Instances
Eq Operation Source # 
Instance details

Defined in Ldap.Client.Modify

Show Operation Source # 
Instance details

Defined in Ldap.Client.Modify

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 
Instances
Eq RelativeDn Source # 
Instance details

Defined in Ldap.Client.Modify

Show RelativeDn Source # 
Instance details

Defined in Ldap.Client.Modify

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 # 
Instance details

Defined in Ldap.Client.Extended

Methods

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

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

Show Oid Source # 
Instance details

Defined in Ldap.Client.Extended

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

IsString Oid Source # 
Instance details

Defined in Ldap.Client.Extended

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 # 
Instance details

Defined in Ldap.Client.Internal

Methods

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

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

Show Dn Source # 
Instance details

Defined in Ldap.Client.Internal

Methods

showsPrec :: Int -> Dn -> ShowS #

show :: Dn -> String #

showList :: [Dn] -> ShowS #

newtype Attr Source #

Attribute name.

Constructors

Attr Text 
Instances
Eq Attr Source # 
Instance details

Defined in Ldap.Client.Internal

Methods

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

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

Show Attr Source # 
Instance details

Defined in Ldap.Client.Internal

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: base-4.9.0.0

Instances
Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

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

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

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

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

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

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

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

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) #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Data a => Data (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in Data.Data

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)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

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)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

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 # 
Instance details

Defined in Ldap.Asn1.ToAsn1

Methods

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