ldap-client-0.4.2: Pure Haskell LDAP Client Library

Safe HaskellNone
LanguageHaskell2010

Ldap.Client.Search

Description

Search operation.

This operation comes in four flavours:

Of those, the first one (search) is probably the most useful for the typical usecase.

Synopsis

Documentation

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

Perform the Search operation synchronously. Raises ResponseError on failures.

searchEither :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO (Either ResponseError [SearchEntry]) Source #

Perform the Search operation synchronously. Returns Left e where e is a ResponseError on failures.

searchAsync :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO (Async [SearchEntry]) Source #

Perform the Search operation asynchronously. Call wait to wait for its completion.

searchAsyncSTM :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> STM (Async [SearchEntry]) Source #

Perform the Search operation asynchronously.

Don't wait for its completion (with waitSTM) in the same transaction you've performed it in.

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

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

data Async a Source #

Asynchronous LDAP operation. Use wait or waitSTM to wait for its completion.

Instances
Functor Async Source # 
Instance details

Defined in Ldap.Client.Internal

Methods

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

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

wait :: Async a -> IO (Either ResponseError a) Source #

Wait for operation completion.

waitSTM :: Async a -> STM (Either ResponseError a) Source #

Wait for operation completion inside STM.

Do not use this inside the same STM transaction the operation was requested in! To give LDAP the chance to respond to it that transaction should commit. After that, applying waitSTM to the corresponding Async starts to make sense.