Safe Haskell | None |
---|---|
Language | Haskell2010 |
Search operation.
This operation comes in four flavours:
- synchronous, exception throwing (
search
) - synchronous, returning
Either
ResponseError
()
(searchEither
) - asynchronous,
IO
based (searchAsync
) - asynchronous,
STM
based (searchAsyncSTM
)
Of those, the first one (search
) is probably the most useful for the typical usecase.
Synopsis
- search :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO [SearchEntry]
- searchEither :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO (Either ResponseError [SearchEntry])
- searchAsync :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO (Async [SearchEntry])
- searchAsyncSTM :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> STM (Async [SearchEntry])
- data Search
- data Mod a
- data Scope
- scope :: Scope -> Mod Search
- size :: Int32 -> Mod Search
- time :: Int32 -> Mod Search
- typesOnly :: Bool -> Mod Search
- data DerefAliases
- derefAliases :: DerefAliases -> Mod Search
- data Filter
- data SearchEntry = SearchEntry !Dn !(AttrList [])
- data Async a
- wait :: Async a -> IO (Either ResponseError a)
- waitSTM :: Async a -> STM (Either ResponseError a)
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.
Search options. Use Mod
to change some of those.
Scope of the search to be performed.
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. |
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.
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 # | |
Defined in Ldap.Asn1.Type (==) :: DerefAliases -> DerefAliases -> Bool # (/=) :: DerefAliases -> DerefAliases -> Bool # | |
Show DerefAliases Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> DerefAliases -> ShowS # show :: DerefAliases -> String # showList :: [DerefAliases] -> ShowS # |
derefAliases :: DerefAliases -> Mod Search Source #
Alias dereference policy (default: NeverDerefAliases
).
Conditions that must be fulfilled in order for the Search to match a given entry.
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.
SearchEntry !Dn !(AttrList []) |
Instances
Eq SearchEntry Source # | |
Defined in Ldap.Client.Search (==) :: SearchEntry -> SearchEntry -> Bool # (/=) :: SearchEntry -> SearchEntry -> Bool # | |
Show SearchEntry Source # | |
Defined in Ldap.Client.Search showsPrec :: Int -> SearchEntry -> ShowS # show :: SearchEntry -> String # showList :: [SearchEntry] -> ShowS # |