module Ldap.Client.Bind
( Password(..)
, bind
, bindEither
, bindAsync
, bindAsyncSTM
, Async
, wait
, waitSTM
) where
import Control.Monad.STM (STM, atomically)
import Data.ByteString (ByteString)
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Ldap.Asn1.Type as Type
import Ldap.Client.Internal
newtype Password = Password ByteString
deriving (Show, Eq)
bind :: Ldap -> Dn -> Password -> IO ()
bind l username password =
raise =<< bindEither l username password
bindEither :: Ldap -> Dn -> Password -> IO (Either ResponseError ())
bindEither l username password =
wait =<< bindAsync l username password
bindAsync :: Ldap -> Dn -> Password -> IO (Async ())
bindAsync l username password =
atomically (bindAsyncSTM l username password)
bindAsyncSTM :: Ldap -> Dn -> Password -> STM (Async ())
bindAsyncSTM l username password =
let req = bindRequest username password in sendRequest l (bindResult req) req
bindRequest :: Dn -> Password -> Request
bindRequest (Dn username) (Password password) =
Type.BindRequest ldapVersion
(Type.LdapDn (Type.LdapString username))
(Type.Simple password)
where
ldapVersion = 3
bindResult :: Request -> Response -> Either ResponseError ()
bindResult req (Type.BindResponse (Type.LdapResult code (Type.LdapDn (Type.LdapString dn))
(Type.LdapString msg) _) _ :| [])
| Type.Success <- code = Right ()
| otherwise = Left (ResponseErrorCode req code (Dn dn) msg)
bindResult req res = Left (ResponseInvalid req res)