-- | <https://tools.ietf.org/html/rfc4511#section-4.7 Add> operation.
--
-- This operation comes in four flavours:
--
--   * synchronous, exception throwing ('add')
--
--   * synchronous, returning 'Either' 'ResponseError' @()@ ('addEither')
--
--   * asynchronous, 'IO' based ('addAsync')
--
--   * asynchronous, 'STM' based ('addAsyncSTM')
--
-- Of those, the first one ('add') is probably the most useful for the typical usecase.
module Ldap.Client.Add
  ( add
  , addEither
  , addAsync
  , addAsyncSTM
  , Async
  , wait
  , waitSTM
  ) where

import           Control.Monad.STM (STM, atomically)
import           Data.List.NonEmpty (NonEmpty((:|)))

import qualified Ldap.Asn1.Type as Type
import           Ldap.Client.Internal


-- | Perform the Add operation synchronously. Raises 'ResponseError' on failures.
add :: Ldap -> Dn -> AttrList NonEmpty -> IO ()
add :: Ldap -> Dn -> AttrList NonEmpty -> IO ()
add Ldap
l Dn
dn AttrList NonEmpty
as =
  forall e a. Exception e => Either e a -> IO a
raise forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ldap -> Dn -> AttrList NonEmpty -> IO (Either ResponseError ())
addEither Ldap
l Dn
dn AttrList NonEmpty
as

-- | Perform the Add operation synchronously. Returns @Left e@ where
-- @e@ is a 'ResponseError' on failures.
addEither :: Ldap -> Dn -> AttrList NonEmpty -> IO (Either ResponseError ())
addEither :: Ldap -> Dn -> AttrList NonEmpty -> IO (Either ResponseError ())
addEither Ldap
l Dn
dn AttrList NonEmpty
as =
  forall a. Async a -> IO (Either ResponseError a)
wait forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ldap -> Dn -> AttrList NonEmpty -> IO (Async ())
addAsync Ldap
l Dn
dn AttrList NonEmpty
as

-- | Perform the Add operation asynchronously. Call 'Ldap.Client.wait' to wait
-- for its completion.
addAsync :: Ldap -> Dn -> AttrList NonEmpty -> IO (Async ())
addAsync :: Ldap -> Dn -> AttrList NonEmpty -> IO (Async ())
addAsync Ldap
l Dn
dn AttrList NonEmpty
as =
  forall a. STM a -> IO a
atomically (Ldap -> Dn -> AttrList NonEmpty -> STM (Async ())
addAsyncSTM Ldap
l Dn
dn AttrList NonEmpty
as)

-- | Perform the Add operation asynchronously.
--
-- Don't wait for its completion (with 'Ldap.Client.waitSTM') in the
-- same transaction you've performed it in.
addAsyncSTM :: Ldap -> Dn -> AttrList NonEmpty -> STM (Async ())
addAsyncSTM :: Ldap -> Dn -> AttrList NonEmpty -> STM (Async ())
addAsyncSTM Ldap
l Dn
dn AttrList NonEmpty
as =
  let req :: Request
req = Dn -> AttrList NonEmpty -> Request
addRequest Dn
dn AttrList NonEmpty
as in forall a.
Ldap
-> (Response -> Either ResponseError a) -> Request -> STM (Async a)
sendRequest Ldap
l (Request -> Response -> Either ResponseError ()
addResult Request
req) Request
req

addRequest :: Dn -> AttrList NonEmpty -> Request
addRequest :: Dn -> AttrList NonEmpty -> Request
addRequest (Dn Text
dn) AttrList NonEmpty
as =
  LdapDn -> AttributeList -> Request
Type.AddRequest (LdapString -> LdapDn
Type.LdapDn (Text -> LdapString
Type.LdapString Text
dn))
                  ([Attribute] -> AttributeList
Type.AttributeList (forall a b. (a -> b) -> [a] -> [b]
map (Attr, NonEmpty ByteString) -> Attribute
f AttrList NonEmpty
as))
 where
  f :: (Attr, NonEmpty ByteString) -> Attribute
f (Attr Text
x, NonEmpty ByteString
xs) = AttributeDescription -> NonEmpty AttributeValue -> Attribute
Type.Attribute (LdapString -> AttributeDescription
Type.AttributeDescription (Text -> LdapString
Type.LdapString Text
x))
                                  (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> AttributeValue
Type.AttributeValue NonEmpty ByteString
xs)

addResult :: Request -> Response -> Either ResponseError ()
addResult :: Request -> Response -> Either ResponseError ()
addResult Request
req (Type.AddResponse (Type.LdapResult ResultCode
code (Type.LdapDn (Type.LdapString Text
dn))
                                                      (Type.LdapString Text
msg) Maybe ReferralUris
_) :| [])
  | ResultCode
Type.Success <- ResultCode
code = forall a b. b -> Either a b
Right ()
  | Bool
otherwise = forall a b. a -> Either a b
Left (Request -> ResultCode -> Dn -> Text -> ResponseError
ResponseErrorCode Request
req ResultCode
code (Text -> Dn
Dn Text
dn) Text
msg)
addResult Request
req Response
res = forall a b. a -> Either a b
Left (Request -> Response -> ResponseError
ResponseInvalid Request
req Response
res)