Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is intended to be imported qualified
import qualified Ldap.Client as Ldap
Synopsis
- with :: Host -> PortNumber -> (Ldap -> IO a) -> IO (Either LdapError a)
- with' :: Host -> PortNumber -> (Ldap -> IO a) -> IO a
- runsIn :: (Ldap -> IO a) -> LdapH -> IO a
- runsInEither :: (Ldap -> IO a) -> LdapH -> IO (Either LdapError a)
- open :: Host -> PortNumber -> IO LdapH
- close :: LdapH -> IO ()
- data Host
- defaultTlsSettings :: TLSSettings
- insecureTlsSettings :: TLSSettings
- data PortNumber
- data Ldap
- data LdapH
- data LdapError
- = IOError !IOError
- | ParseError !ASN1Error
- | ResponseError !ResponseError
- | DisconnectError !Disconnect
- data ResponseError
- data ResultCode
- = Success
- | OperationError
- | ProtocolError
- | TimeLimitExceeded
- | SizeLimitExceeded
- | CompareFalse
- | CompareTrue
- | AuthMethodNotSupported
- | StrongerAuthRequired
- | Referral
- | AdminLimitExceeded
- | UnavailableCriticalExtension
- | ConfidentialityRequired
- | SaslBindInProgress
- | NoSuchAttribute
- | UndefinedAttributeType
- | InappropriateMatching
- | ConstraintViolation
- | AttributeOrValueExists
- | InvalidAttributeSyntax
- | NoSuchObject
- | AliasProblem
- | InvalidDNSyntax
- | AliasDereferencingProblem
- | InappropriateAuthentication
- | InvalidCredentials
- | InsufficientAccessRights
- | Busy
- | Unavailable
- | UnwillingToPerform
- | LoopDetect
- | NamingViolation
- | ObjectClassViolation
- | NotAllowedOnNonLeaf
- | NotAllowedOnRDN
- | EntryAlreadyExists
- | ObjectClassModsProhibited
- | AffectsMultipleDSAs
- | Other
- newtype Password = Password ByteString
- bind :: Ldap -> Dn -> Password -> IO ()
- externalBind :: Ldap -> Dn -> Maybe Text -> IO ()
- search :: Ldap -> Dn -> Mod Search -> Filter -> [Attr] -> IO [SearchEntry]
- data SearchEntry = SearchEntry !Dn !(AttrList [])
- 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
- modify :: Ldap -> Dn -> [Operation] -> IO ()
- data Operation
- add :: Ldap -> Dn -> AttrList NonEmpty -> IO ()
- delete :: Ldap -> Dn -> IO ()
- newtype RelativeDn = RelativeDn Text
- modifyDn :: Ldap -> Dn -> RelativeDn -> Bool -> Maybe Dn -> IO ()
- compare :: Ldap -> Dn -> Attr -> AttrValue -> IO Bool
- newtype Oid = Oid Text
- extended :: Ldap -> Oid -> Maybe ByteString -> IO ()
- newtype Dn = Dn Text
- newtype Attr = Attr Text
- type AttrValue = ByteString
- type AttrList f = [(Attr, f AttrValue)]
- data NonEmpty a
Documentation
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
.
LDAP host.
Plain String | Plain LDAP. |
Tls String TLSSettings | LDAP over TLS. |
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
Various failures that can happen when working with LDAP.
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 # | |
Show LdapError Source # | |
Exception LdapError Source # | |
Defined in Ldap.Client toException :: LdapError -> SomeException # fromException :: SomeException -> Maybe LdapError # displayException :: LdapError -> String # |
data ResponseError Source #
Response indicates a failed operation.
ResponseInvalid !Request !Response | LDAP server did not follow the protocol, so |
ResponseErrorCode !Request !ResultCode !Dn !Text | The response contains a result code indicating failure and an error message. |
Instances
Eq ResponseError Source # | |
Defined in Ldap.Client.Internal (==) :: ResponseError -> ResponseError -> Bool # (/=) :: ResponseError -> ResponseError -> Bool # | |
Show ResponseError Source # | |
Defined in Ldap.Client.Internal showsPrec :: Int -> ResponseError -> ShowS # show :: ResponseError -> String # showList :: [ResponseError] -> ShowS # | |
Exception ResponseError Source # | |
Defined in Ldap.Client.Internal |
data ResultCode Source #
LDAP operation's result.
Instances
Eq ResultCode Source # | |
Defined in Ldap.Asn1.Type (==) :: ResultCode -> ResultCode -> Bool # (/=) :: ResultCode -> ResultCode -> Bool # | |
Show ResultCode Source # | |
Defined in Ldap.Asn1.Type showsPrec :: Int -> ResultCode -> ShowS # show :: ResultCode -> String # showList :: [ResultCode] -> ShowS # |
Bind
User's password.
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.
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 # |
Search modifiers
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 |
Modify
modify :: Ldap -> Dn -> [Operation] -> IO () Source #
Perform the Modify operation synchronously. Raises ResponseError
on failures.
Type of modification being performed.
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
.
Instances
Eq RelativeDn Source # | |
Defined in Ldap.Client.Modify (==) :: RelativeDn -> RelativeDn -> Bool # (/=) :: RelativeDn -> RelativeDn -> Bool # | |
Show RelativeDn Source # | |
Defined in Ldap.Client.Modify showsPrec :: Int -> RelativeDn -> ShowS # show :: RelativeDn -> String # showList :: [RelativeDn] -> ShowS # |
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
Globally unique LDAP object identifier.
extended :: Ldap -> Oid -> Maybe ByteString -> IO () Source #
Perform the Extended operation synchronously. Raises ResponseError
on failures.
Miscellanous
Unique identifier of an LDAP entry.
Attribute name.
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
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Instances
Monad NonEmpty | Since: base-4.9.0.0 |
Functor NonEmpty | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Traversable NonEmpty | Since: base-4.9.0.0 |
Eq1 NonEmpty | Since: base-4.10.0.0 |
Ord1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Read1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Show1 NonEmpty | Since: base-4.10.0.0 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Data a => Data (NonEmpty a) | Since: base-4.9.0.0 |
Defined in Data.Data 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 |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
Show a => Show (NonEmpty a) | Since: base-4.11.0.0 |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
ToAsn1 a => ToAsn1 (NonEmpty a) Source # | |