Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Host
- data PortNumber
- data Ldap = Ldap {
- reqQ :: !(TQueue ClientMessage)
- workers :: !(Async Void)
- conn :: !Connection
- data ClientMessage = New !Request !(TMVar (NonEmpty ProtocolServerOp))
- 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
- data Async a
- type AttrList f = [(Attr, f AttrValue)]
- wait :: Async a -> IO (Either ResponseError a)
- waitSTM :: Async a -> STM (Either ResponseError a)
- type Response = NonEmpty InMessage
- data ResponseError
- type Request = ProtocolClientOp
- eitherToIO :: Exception e => Either e a -> IO a
- sendRequest :: Ldap -> (Response -> Either ResponseError a) -> Request -> STM (Async a)
- newtype Dn = Dn Text
- newtype Attr = Attr Text
- type AttrValue = ByteString
- unAttr :: Attr -> Text
- unbindAsync :: Ldap -> IO ()
- unbindAsyncSTM :: Ldap -> STM ()
Documentation
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
An LDAP connection handle
Ldap | |
|
data ClientMessage Source #
New !Request !(TMVar (NonEmpty ProtocolServerOp)) |
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 # |
type AttrList f = [(Attr, f AttrValue)] Source #
List of attributes and their values. f
is the structure these
values are in, e.g. NonEmpty
.
Waiting for Request Completion
Misc
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 |
type Request = ProtocolClientOp Source #
sendRequest :: Ldap -> (Response -> Either ResponseError a) -> Request -> STM (Async a) Source #
Unique identifier of an LDAP entry.
Attribute name.
type AttrValue = ByteString Source #
Attribute value.
Unbind operation
unbindAsync :: Ldap -> IO () Source #
Terminate the connection to the Directory.
Note that unbindAsync
does not return an Async
,
because LDAP server never responds to UnbindRequest
s, hence
a call to wait
on a hypothetical Async
would have resulted
in an exception anyway.
unbindAsyncSTM :: Ldap -> STM () Source #
Terminate the connection to the Directory.
Note that unbindAsyncSTM
does not return an Async
,
because LDAP server never responds to UnbindRequest
s, hence
a call to wait
on a hypothetical Async
would have resulted
in an exception anyway.