{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CloudSearchDomains.UploadDocuments
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Posts a batch of documents to a search domain for indexing. A document
-- batch is a collection of add and delete operations that represent the
-- documents you want to add, update, or delete from your domain. Batches
-- can be described in either JSON or XML. Each item that you want Amazon
-- CloudSearch to return as a search result (such as a product) is
-- represented as a document. Every document has a unique ID and one or
-- more fields that contain the data that you want to search and return in
-- results. Individual documents cannot contain more than 1 MB of data. The
-- entire batch cannot exceed 5 MB. To get the best possible upload
-- performance, group add and delete operations in batches that are close
-- the 5 MB limit. Submitting a large volume of single-document batches can
-- overload a domain\'s document service.
--
-- The endpoint for submitting @UploadDocuments@ requests is
-- domain-specific. To get the document endpoint for your domain, use the
-- Amazon CloudSearch configuration service @DescribeDomains@ action. A
-- domain\'s endpoints are also displayed on the domain dashboard in the
-- Amazon CloudSearch console.
--
-- For more information about formatting your data for Amazon CloudSearch,
-- see
-- <http://docs.aws.amazon.com/cloudsearch/latest/developerguide/preparing-data.html Preparing Your Data>
-- in the /Amazon CloudSearch Developer Guide/. For more information about
-- uploading data for indexing, see
-- <http://docs.aws.amazon.com/cloudsearch/latest/developerguide/uploading-data.html Uploading Data>
-- in the /Amazon CloudSearch Developer Guide/.
module Amazonka.CloudSearchDomains.UploadDocuments
  ( -- * Creating a Request
    UploadDocuments (..),
    newUploadDocuments,

    -- * Request Lenses
    uploadDocuments_contentType,
    uploadDocuments_documents,

    -- * Destructuring the Response
    UploadDocumentsResponse (..),
    newUploadDocumentsResponse,

    -- * Response Lenses
    uploadDocumentsResponse_adds,
    uploadDocumentsResponse_deletes,
    uploadDocumentsResponse_status,
    uploadDocumentsResponse_warnings,
    uploadDocumentsResponse_httpStatus,
  )
where

import Amazonka.CloudSearchDomains.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Container for the parameters to the @UploadDocuments@ request.
--
-- /See:/ 'newUploadDocuments' smart constructor.
data UploadDocuments = UploadDocuments'
  { -- | The format of the batch you are uploading. Amazon CloudSearch supports
    -- two document batch formats:
    --
    -- -   application\/json
    -- -   application\/xml
    UploadDocuments -> ContentType
contentType :: ContentType,
    -- | A batch of documents formatted in JSON or HTML.
    UploadDocuments -> HashedBody
documents :: Data.HashedBody
  }
  deriving (Int -> UploadDocuments -> ShowS
[UploadDocuments] -> ShowS
UploadDocuments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadDocuments] -> ShowS
$cshowList :: [UploadDocuments] -> ShowS
show :: UploadDocuments -> String
$cshow :: UploadDocuments -> String
showsPrec :: Int -> UploadDocuments -> ShowS
$cshowsPrec :: Int -> UploadDocuments -> ShowS
Prelude.Show, forall x. Rep UploadDocuments x -> UploadDocuments
forall x. UploadDocuments -> Rep UploadDocuments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadDocuments x -> UploadDocuments
$cfrom :: forall x. UploadDocuments -> Rep UploadDocuments x
Prelude.Generic)

-- |
-- Create a value of 'UploadDocuments' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'contentType', 'uploadDocuments_contentType' - The format of the batch you are uploading. Amazon CloudSearch supports
-- two document batch formats:
--
-- -   application\/json
-- -   application\/xml
--
-- 'documents', 'uploadDocuments_documents' - A batch of documents formatted in JSON or HTML.
newUploadDocuments ::
  -- | 'contentType'
  ContentType ->
  -- | 'documents'
  Data.HashedBody ->
  UploadDocuments
newUploadDocuments :: ContentType -> HashedBody -> UploadDocuments
newUploadDocuments ContentType
pContentType_ HashedBody
pDocuments_ =
  UploadDocuments'
    { $sel:contentType:UploadDocuments' :: ContentType
contentType = ContentType
pContentType_,
      $sel:documents:UploadDocuments' :: HashedBody
documents = HashedBody
pDocuments_
    }

-- | The format of the batch you are uploading. Amazon CloudSearch supports
-- two document batch formats:
--
-- -   application\/json
-- -   application\/xml
uploadDocuments_contentType :: Lens.Lens' UploadDocuments ContentType
uploadDocuments_contentType :: Lens' UploadDocuments ContentType
uploadDocuments_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocuments' {ContentType
contentType :: ContentType
$sel:contentType:UploadDocuments' :: UploadDocuments -> ContentType
contentType} -> ContentType
contentType) (\s :: UploadDocuments
s@UploadDocuments' {} ContentType
a -> UploadDocuments
s {$sel:contentType:UploadDocuments' :: ContentType
contentType = ContentType
a} :: UploadDocuments)

-- | A batch of documents formatted in JSON or HTML.
uploadDocuments_documents :: Lens.Lens' UploadDocuments Data.HashedBody
uploadDocuments_documents :: Lens' UploadDocuments HashedBody
uploadDocuments_documents = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocuments' {HashedBody
documents :: HashedBody
$sel:documents:UploadDocuments' :: UploadDocuments -> HashedBody
documents} -> HashedBody
documents) (\s :: UploadDocuments
s@UploadDocuments' {} HashedBody
a -> UploadDocuments
s {$sel:documents:UploadDocuments' :: HashedBody
documents = HashedBody
a} :: UploadDocuments)

instance Core.AWSRequest UploadDocuments where
  type
    AWSResponse UploadDocuments =
      UploadDocumentsResponse
  request :: (Service -> Service) -> UploadDocuments -> Request UploadDocuments
request Service -> Service
overrides =
    forall a. (ToRequest a, ToBody a) => Service -> a -> Request a
Request.postBody (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UploadDocuments
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UploadDocuments)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Integer
-> Maybe Integer
-> Maybe Text
-> Maybe [DocumentServiceWarning]
-> Int
-> UploadDocumentsResponse
UploadDocumentsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"adds")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"deletes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"warnings" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Data.ToBody UploadDocuments where
  toBody :: UploadDocuments -> RequestBody
toBody UploadDocuments' {HashedBody
ContentType
documents :: HashedBody
contentType :: ContentType
$sel:documents:UploadDocuments' :: UploadDocuments -> HashedBody
$sel:contentType:UploadDocuments' :: UploadDocuments -> ContentType
..} = forall a. ToBody a => a -> RequestBody
Data.toBody HashedBody
documents

instance Data.ToHeaders UploadDocuments where
  toHeaders :: UploadDocuments -> ResponseHeaders
toHeaders UploadDocuments' {HashedBody
ContentType
documents :: HashedBody
contentType :: ContentType
$sel:documents:UploadDocuments' :: UploadDocuments -> HashedBody
$sel:contentType:UploadDocuments' :: UploadDocuments -> ContentType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"Content-Type" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ContentType
contentType]

instance Data.ToPath UploadDocuments where
  toPath :: UploadDocuments -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2013-01-01/documents/batch"

instance Data.ToQuery UploadDocuments where
  toQuery :: UploadDocuments -> QueryString
toQuery =
    forall a b. a -> b -> a
Prelude.const (forall a. Monoid a => [a] -> a
Prelude.mconcat [QueryString
"format=sdk"])

-- | Contains the response to an @UploadDocuments@ request.
--
-- /See:/ 'newUploadDocumentsResponse' smart constructor.
data UploadDocumentsResponse = UploadDocumentsResponse'
  { -- | The number of documents that were added to the search domain.
    UploadDocumentsResponse -> Maybe Integer
adds :: Prelude.Maybe Prelude.Integer,
    -- | The number of documents that were deleted from the search domain.
    UploadDocumentsResponse -> Maybe Integer
deletes :: Prelude.Maybe Prelude.Integer,
    -- | The status of an @UploadDocumentsRequest@.
    UploadDocumentsResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | Any warnings returned by the document service about the documents being
    -- uploaded.
    UploadDocumentsResponse -> Maybe [DocumentServiceWarning]
warnings :: Prelude.Maybe [DocumentServiceWarning],
    -- | The response's http status code.
    UploadDocumentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UploadDocumentsResponse -> UploadDocumentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadDocumentsResponse -> UploadDocumentsResponse -> Bool
$c/= :: UploadDocumentsResponse -> UploadDocumentsResponse -> Bool
== :: UploadDocumentsResponse -> UploadDocumentsResponse -> Bool
$c== :: UploadDocumentsResponse -> UploadDocumentsResponse -> Bool
Prelude.Eq, ReadPrec [UploadDocumentsResponse]
ReadPrec UploadDocumentsResponse
Int -> ReadS UploadDocumentsResponse
ReadS [UploadDocumentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UploadDocumentsResponse]
$creadListPrec :: ReadPrec [UploadDocumentsResponse]
readPrec :: ReadPrec UploadDocumentsResponse
$creadPrec :: ReadPrec UploadDocumentsResponse
readList :: ReadS [UploadDocumentsResponse]
$creadList :: ReadS [UploadDocumentsResponse]
readsPrec :: Int -> ReadS UploadDocumentsResponse
$creadsPrec :: Int -> ReadS UploadDocumentsResponse
Prelude.Read, Int -> UploadDocumentsResponse -> ShowS
[UploadDocumentsResponse] -> ShowS
UploadDocumentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadDocumentsResponse] -> ShowS
$cshowList :: [UploadDocumentsResponse] -> ShowS
show :: UploadDocumentsResponse -> String
$cshow :: UploadDocumentsResponse -> String
showsPrec :: Int -> UploadDocumentsResponse -> ShowS
$cshowsPrec :: Int -> UploadDocumentsResponse -> ShowS
Prelude.Show, forall x. Rep UploadDocumentsResponse x -> UploadDocumentsResponse
forall x. UploadDocumentsResponse -> Rep UploadDocumentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadDocumentsResponse x -> UploadDocumentsResponse
$cfrom :: forall x. UploadDocumentsResponse -> Rep UploadDocumentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'UploadDocumentsResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'adds', 'uploadDocumentsResponse_adds' - The number of documents that were added to the search domain.
--
-- 'deletes', 'uploadDocumentsResponse_deletes' - The number of documents that were deleted from the search domain.
--
-- 'status', 'uploadDocumentsResponse_status' - The status of an @UploadDocumentsRequest@.
--
-- 'warnings', 'uploadDocumentsResponse_warnings' - Any warnings returned by the document service about the documents being
-- uploaded.
--
-- 'httpStatus', 'uploadDocumentsResponse_httpStatus' - The response's http status code.
newUploadDocumentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UploadDocumentsResponse
newUploadDocumentsResponse :: Int -> UploadDocumentsResponse
newUploadDocumentsResponse Int
pHttpStatus_ =
  UploadDocumentsResponse'
    { $sel:adds:UploadDocumentsResponse' :: Maybe Integer
adds = forall a. Maybe a
Prelude.Nothing,
      $sel:deletes:UploadDocumentsResponse' :: Maybe Integer
deletes = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UploadDocumentsResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:UploadDocumentsResponse' :: Maybe [DocumentServiceWarning]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UploadDocumentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The number of documents that were added to the search domain.
uploadDocumentsResponse_adds :: Lens.Lens' UploadDocumentsResponse (Prelude.Maybe Prelude.Integer)
uploadDocumentsResponse_adds :: Lens' UploadDocumentsResponse (Maybe Integer)
uploadDocumentsResponse_adds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocumentsResponse' {Maybe Integer
adds :: Maybe Integer
$sel:adds:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Integer
adds} -> Maybe Integer
adds) (\s :: UploadDocumentsResponse
s@UploadDocumentsResponse' {} Maybe Integer
a -> UploadDocumentsResponse
s {$sel:adds:UploadDocumentsResponse' :: Maybe Integer
adds = Maybe Integer
a} :: UploadDocumentsResponse)

-- | The number of documents that were deleted from the search domain.
uploadDocumentsResponse_deletes :: Lens.Lens' UploadDocumentsResponse (Prelude.Maybe Prelude.Integer)
uploadDocumentsResponse_deletes :: Lens' UploadDocumentsResponse (Maybe Integer)
uploadDocumentsResponse_deletes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocumentsResponse' {Maybe Integer
deletes :: Maybe Integer
$sel:deletes:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Integer
deletes} -> Maybe Integer
deletes) (\s :: UploadDocumentsResponse
s@UploadDocumentsResponse' {} Maybe Integer
a -> UploadDocumentsResponse
s {$sel:deletes:UploadDocumentsResponse' :: Maybe Integer
deletes = Maybe Integer
a} :: UploadDocumentsResponse)

-- | The status of an @UploadDocumentsRequest@.
uploadDocumentsResponse_status :: Lens.Lens' UploadDocumentsResponse (Prelude.Maybe Prelude.Text)
uploadDocumentsResponse_status :: Lens' UploadDocumentsResponse (Maybe Text)
uploadDocumentsResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocumentsResponse' {Maybe Text
status :: Maybe Text
$sel:status:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: UploadDocumentsResponse
s@UploadDocumentsResponse' {} Maybe Text
a -> UploadDocumentsResponse
s {$sel:status:UploadDocumentsResponse' :: Maybe Text
status = Maybe Text
a} :: UploadDocumentsResponse)

-- | Any warnings returned by the document service about the documents being
-- uploaded.
uploadDocumentsResponse_warnings :: Lens.Lens' UploadDocumentsResponse (Prelude.Maybe [DocumentServiceWarning])
uploadDocumentsResponse_warnings :: Lens' UploadDocumentsResponse (Maybe [DocumentServiceWarning])
uploadDocumentsResponse_warnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocumentsResponse' {Maybe [DocumentServiceWarning]
warnings :: Maybe [DocumentServiceWarning]
$sel:warnings:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe [DocumentServiceWarning]
warnings} -> Maybe [DocumentServiceWarning]
warnings) (\s :: UploadDocumentsResponse
s@UploadDocumentsResponse' {} Maybe [DocumentServiceWarning]
a -> UploadDocumentsResponse
s {$sel:warnings:UploadDocumentsResponse' :: Maybe [DocumentServiceWarning]
warnings = Maybe [DocumentServiceWarning]
a} :: UploadDocumentsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
uploadDocumentsResponse_httpStatus :: Lens.Lens' UploadDocumentsResponse Prelude.Int
uploadDocumentsResponse_httpStatus :: Lens' UploadDocumentsResponse Int
uploadDocumentsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadDocumentsResponse' {Int
httpStatus :: Int
$sel:httpStatus:UploadDocumentsResponse' :: UploadDocumentsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UploadDocumentsResponse
s@UploadDocumentsResponse' {} Int
a -> UploadDocumentsResponse
s {$sel:httpStatus:UploadDocumentsResponse' :: Int
httpStatus = Int
a} :: UploadDocumentsResponse)

instance Prelude.NFData UploadDocumentsResponse where
  rnf :: UploadDocumentsResponse -> ()
rnf UploadDocumentsResponse' {Int
Maybe Integer
Maybe [DocumentServiceWarning]
Maybe Text
httpStatus :: Int
warnings :: Maybe [DocumentServiceWarning]
status :: Maybe Text
deletes :: Maybe Integer
adds :: Maybe Integer
$sel:httpStatus:UploadDocumentsResponse' :: UploadDocumentsResponse -> Int
$sel:warnings:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe [DocumentServiceWarning]
$sel:status:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Text
$sel:deletes:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Integer
$sel:adds:UploadDocumentsResponse' :: UploadDocumentsResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
adds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
deletes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DocumentServiceWarning]
warnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus