{-# 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.Comprehend.BatchDetectTargetedSentiment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Inspects a batch of documents and returns a sentiment analysis for each
-- entity identified in the documents.
--
-- For more information about targeted sentiment, see
-- <https://docs.aws.amazon.com/comprehend/latest/dg/how-targeted-sentiment.html Targeted sentiment>.
module Amazonka.Comprehend.BatchDetectTargetedSentiment
  ( -- * Creating a Request
    BatchDetectTargetedSentiment (..),
    newBatchDetectTargetedSentiment,

    -- * Request Lenses
    batchDetectTargetedSentiment_textList,
    batchDetectTargetedSentiment_languageCode,

    -- * Destructuring the Response
    BatchDetectTargetedSentimentResponse (..),
    newBatchDetectTargetedSentimentResponse,

    -- * Response Lenses
    batchDetectTargetedSentimentResponse_httpStatus,
    batchDetectTargetedSentimentResponse_resultList,
    batchDetectTargetedSentimentResponse_errorList,
  )
where

import Amazonka.Comprehend.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

-- | /See:/ 'newBatchDetectTargetedSentiment' smart constructor.
data BatchDetectTargetedSentiment = BatchDetectTargetedSentiment'
  { -- | A list containing the UTF-8 encoded text of the input documents. The
    -- list can contain a maximum of 25 documents. The maximum size of each
    -- document is 5 KB.
    BatchDetectTargetedSentiment
-> Sensitive (NonEmpty (Sensitive Text))
textList :: Data.Sensitive (Prelude.NonEmpty (Data.Sensitive Prelude.Text)),
    -- | The language of the input documents. Currently, English is the only
    -- supported language.
    BatchDetectTargetedSentiment -> LanguageCode
languageCode :: LanguageCode
  }
  deriving (BatchDetectTargetedSentiment
-> BatchDetectTargetedSentiment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDetectTargetedSentiment
-> BatchDetectTargetedSentiment -> Bool
$c/= :: BatchDetectTargetedSentiment
-> BatchDetectTargetedSentiment -> Bool
== :: BatchDetectTargetedSentiment
-> BatchDetectTargetedSentiment -> Bool
$c== :: BatchDetectTargetedSentiment
-> BatchDetectTargetedSentiment -> Bool
Prelude.Eq, Int -> BatchDetectTargetedSentiment -> ShowS
[BatchDetectTargetedSentiment] -> ShowS
BatchDetectTargetedSentiment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDetectTargetedSentiment] -> ShowS
$cshowList :: [BatchDetectTargetedSentiment] -> ShowS
show :: BatchDetectTargetedSentiment -> String
$cshow :: BatchDetectTargetedSentiment -> String
showsPrec :: Int -> BatchDetectTargetedSentiment -> ShowS
$cshowsPrec :: Int -> BatchDetectTargetedSentiment -> ShowS
Prelude.Show, forall x.
Rep BatchDetectTargetedSentiment x -> BatchDetectTargetedSentiment
forall x.
BatchDetectTargetedSentiment -> Rep BatchDetectTargetedSentiment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDetectTargetedSentiment x -> BatchDetectTargetedSentiment
$cfrom :: forall x.
BatchDetectTargetedSentiment -> Rep BatchDetectTargetedSentiment x
Prelude.Generic)

-- |
-- Create a value of 'BatchDetectTargetedSentiment' 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:
--
-- 'textList', 'batchDetectTargetedSentiment_textList' - A list containing the UTF-8 encoded text of the input documents. The
-- list can contain a maximum of 25 documents. The maximum size of each
-- document is 5 KB.
--
-- 'languageCode', 'batchDetectTargetedSentiment_languageCode' - The language of the input documents. Currently, English is the only
-- supported language.
newBatchDetectTargetedSentiment ::
  -- | 'textList'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'languageCode'
  LanguageCode ->
  BatchDetectTargetedSentiment
newBatchDetectTargetedSentiment :: NonEmpty Text -> LanguageCode -> BatchDetectTargetedSentiment
newBatchDetectTargetedSentiment
  NonEmpty Text
pTextList_
  LanguageCode
pLanguageCode_ =
    BatchDetectTargetedSentiment'
      { $sel:textList:BatchDetectTargetedSentiment' :: Sensitive (NonEmpty (Sensitive Text))
textList =
          forall a. Iso' (Sensitive a) a
Data._Sensitive
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
            forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pTextList_,
        $sel:languageCode:BatchDetectTargetedSentiment' :: LanguageCode
languageCode = LanguageCode
pLanguageCode_
      }

-- | A list containing the UTF-8 encoded text of the input documents. The
-- list can contain a maximum of 25 documents. The maximum size of each
-- document is 5 KB.
batchDetectTargetedSentiment_textList :: Lens.Lens' BatchDetectTargetedSentiment (Prelude.NonEmpty Prelude.Text)
batchDetectTargetedSentiment_textList :: Lens' BatchDetectTargetedSentiment (NonEmpty Text)
batchDetectTargetedSentiment_textList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectTargetedSentiment' {Sensitive (NonEmpty (Sensitive Text))
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:textList:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment
-> Sensitive (NonEmpty (Sensitive Text))
textList} -> Sensitive (NonEmpty (Sensitive Text))
textList) (\s :: BatchDetectTargetedSentiment
s@BatchDetectTargetedSentiment' {} Sensitive (NonEmpty (Sensitive Text))
a -> BatchDetectTargetedSentiment
s {$sel:textList:BatchDetectTargetedSentiment' :: Sensitive (NonEmpty (Sensitive Text))
textList = Sensitive (NonEmpty (Sensitive Text))
a} :: BatchDetectTargetedSentiment) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The language of the input documents. Currently, English is the only
-- supported language.
batchDetectTargetedSentiment_languageCode :: Lens.Lens' BatchDetectTargetedSentiment LanguageCode
batchDetectTargetedSentiment_languageCode :: Lens' BatchDetectTargetedSentiment LanguageCode
batchDetectTargetedSentiment_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectTargetedSentiment' {LanguageCode
languageCode :: LanguageCode
$sel:languageCode:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment -> LanguageCode
languageCode} -> LanguageCode
languageCode) (\s :: BatchDetectTargetedSentiment
s@BatchDetectTargetedSentiment' {} LanguageCode
a -> BatchDetectTargetedSentiment
s {$sel:languageCode:BatchDetectTargetedSentiment' :: LanguageCode
languageCode = LanguageCode
a} :: BatchDetectTargetedSentiment)

instance Core.AWSRequest BatchDetectTargetedSentiment where
  type
    AWSResponse BatchDetectTargetedSentiment =
      BatchDetectTargetedSentimentResponse
  request :: (Service -> Service)
-> BatchDetectTargetedSentiment
-> Request BatchDetectTargetedSentiment
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy BatchDetectTargetedSentiment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchDetectTargetedSentiment)))
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 ->
          Int
-> [BatchDetectTargetedSentimentItemResult]
-> [BatchItemError]
-> BatchDetectTargetedSentimentResponse
BatchDetectTargetedSentimentResponse'
            forall (f :: * -> *) a b. Functor 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))
            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
"ResultList" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ErrorList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance
  Prelude.Hashable
    BatchDetectTargetedSentiment
  where
  hashWithSalt :: Int -> BatchDetectTargetedSentiment -> Int
hashWithSalt Int
_salt BatchDetectTargetedSentiment' {Sensitive (NonEmpty (Sensitive Text))
LanguageCode
languageCode :: LanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment -> LanguageCode
$sel:textList:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment
-> Sensitive (NonEmpty (Sensitive Text))
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive (NonEmpty (Sensitive Text))
textList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LanguageCode
languageCode

instance Prelude.NFData BatchDetectTargetedSentiment where
  rnf :: BatchDetectTargetedSentiment -> ()
rnf BatchDetectTargetedSentiment' {Sensitive (NonEmpty (Sensitive Text))
LanguageCode
languageCode :: LanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment -> LanguageCode
$sel:textList:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment
-> Sensitive (NonEmpty (Sensitive Text))
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Sensitive (NonEmpty (Sensitive Text))
textList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf LanguageCode
languageCode

instance Data.ToHeaders BatchDetectTargetedSentiment where
  toHeaders :: BatchDetectTargetedSentiment -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Comprehend_20171127.BatchDetectTargetedSentiment" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON BatchDetectTargetedSentiment where
  toJSON :: BatchDetectTargetedSentiment -> Value
toJSON BatchDetectTargetedSentiment' {Sensitive (NonEmpty (Sensitive Text))
LanguageCode
languageCode :: LanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment -> LanguageCode
$sel:textList:BatchDetectTargetedSentiment' :: BatchDetectTargetedSentiment
-> Sensitive (NonEmpty (Sensitive Text))
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"TextList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive (NonEmpty (Sensitive Text))
textList),
            forall a. a -> Maybe a
Prelude.Just (Key
"LanguageCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= LanguageCode
languageCode)
          ]
      )

instance Data.ToPath BatchDetectTargetedSentiment where
  toPath :: BatchDetectTargetedSentiment -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery BatchDetectTargetedSentiment where
  toQuery :: BatchDetectTargetedSentiment -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newBatchDetectTargetedSentimentResponse' smart constructor.
data BatchDetectTargetedSentimentResponse = BatchDetectTargetedSentimentResponse'
  { -- | The response's http status code.
    BatchDetectTargetedSentimentResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of objects containing the results of the operation. The results
    -- are sorted in ascending order by the @Index@ field and match the order
    -- of the documents in the input list. If all of the documents contain an
    -- error, the @ResultList@ is empty.
    BatchDetectTargetedSentimentResponse
-> [BatchDetectTargetedSentimentItemResult]
resultList :: [BatchDetectTargetedSentimentItemResult],
    -- | List of errors that the operation can return.
    BatchDetectTargetedSentimentResponse -> [BatchItemError]
errorList :: [BatchItemError]
  }
  deriving (BatchDetectTargetedSentimentResponse
-> BatchDetectTargetedSentimentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDetectTargetedSentimentResponse
-> BatchDetectTargetedSentimentResponse -> Bool
$c/= :: BatchDetectTargetedSentimentResponse
-> BatchDetectTargetedSentimentResponse -> Bool
== :: BatchDetectTargetedSentimentResponse
-> BatchDetectTargetedSentimentResponse -> Bool
$c== :: BatchDetectTargetedSentimentResponse
-> BatchDetectTargetedSentimentResponse -> Bool
Prelude.Eq, Int -> BatchDetectTargetedSentimentResponse -> ShowS
[BatchDetectTargetedSentimentResponse] -> ShowS
BatchDetectTargetedSentimentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDetectTargetedSentimentResponse] -> ShowS
$cshowList :: [BatchDetectTargetedSentimentResponse] -> ShowS
show :: BatchDetectTargetedSentimentResponse -> String
$cshow :: BatchDetectTargetedSentimentResponse -> String
showsPrec :: Int -> BatchDetectTargetedSentimentResponse -> ShowS
$cshowsPrec :: Int -> BatchDetectTargetedSentimentResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDetectTargetedSentimentResponse x
-> BatchDetectTargetedSentimentResponse
forall x.
BatchDetectTargetedSentimentResponse
-> Rep BatchDetectTargetedSentimentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDetectTargetedSentimentResponse x
-> BatchDetectTargetedSentimentResponse
$cfrom :: forall x.
BatchDetectTargetedSentimentResponse
-> Rep BatchDetectTargetedSentimentResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchDetectTargetedSentimentResponse' 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:
--
-- 'httpStatus', 'batchDetectTargetedSentimentResponse_httpStatus' - The response's http status code.
--
-- 'resultList', 'batchDetectTargetedSentimentResponse_resultList' - A list of objects containing the results of the operation. The results
-- are sorted in ascending order by the @Index@ field and match the order
-- of the documents in the input list. If all of the documents contain an
-- error, the @ResultList@ is empty.
--
-- 'errorList', 'batchDetectTargetedSentimentResponse_errorList' - List of errors that the operation can return.
newBatchDetectTargetedSentimentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchDetectTargetedSentimentResponse
newBatchDetectTargetedSentimentResponse :: Int -> BatchDetectTargetedSentimentResponse
newBatchDetectTargetedSentimentResponse Int
pHttpStatus_ =
  BatchDetectTargetedSentimentResponse'
    { $sel:httpStatus:BatchDetectTargetedSentimentResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:resultList:BatchDetectTargetedSentimentResponse' :: [BatchDetectTargetedSentimentItemResult]
resultList = forall a. Monoid a => a
Prelude.mempty,
      $sel:errorList:BatchDetectTargetedSentimentResponse' :: [BatchItemError]
errorList = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A list of objects containing the results of the operation. The results
-- are sorted in ascending order by the @Index@ field and match the order
-- of the documents in the input list. If all of the documents contain an
-- error, the @ResultList@ is empty.
batchDetectTargetedSentimentResponse_resultList :: Lens.Lens' BatchDetectTargetedSentimentResponse [BatchDetectTargetedSentimentItemResult]
batchDetectTargetedSentimentResponse_resultList :: Lens'
  BatchDetectTargetedSentimentResponse
  [BatchDetectTargetedSentimentItemResult]
batchDetectTargetedSentimentResponse_resultList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectTargetedSentimentResponse' {[BatchDetectTargetedSentimentItemResult]
resultList :: [BatchDetectTargetedSentimentItemResult]
$sel:resultList:BatchDetectTargetedSentimentResponse' :: BatchDetectTargetedSentimentResponse
-> [BatchDetectTargetedSentimentItemResult]
resultList} -> [BatchDetectTargetedSentimentItemResult]
resultList) (\s :: BatchDetectTargetedSentimentResponse
s@BatchDetectTargetedSentimentResponse' {} [BatchDetectTargetedSentimentItemResult]
a -> BatchDetectTargetedSentimentResponse
s {$sel:resultList:BatchDetectTargetedSentimentResponse' :: [BatchDetectTargetedSentimentItemResult]
resultList = [BatchDetectTargetedSentimentItemResult]
a} :: BatchDetectTargetedSentimentResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | List of errors that the operation can return.
batchDetectTargetedSentimentResponse_errorList :: Lens.Lens' BatchDetectTargetedSentimentResponse [BatchItemError]
batchDetectTargetedSentimentResponse_errorList :: Lens' BatchDetectTargetedSentimentResponse [BatchItemError]
batchDetectTargetedSentimentResponse_errorList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectTargetedSentimentResponse' {[BatchItemError]
errorList :: [BatchItemError]
$sel:errorList:BatchDetectTargetedSentimentResponse' :: BatchDetectTargetedSentimentResponse -> [BatchItemError]
errorList} -> [BatchItemError]
errorList) (\s :: BatchDetectTargetedSentimentResponse
s@BatchDetectTargetedSentimentResponse' {} [BatchItemError]
a -> BatchDetectTargetedSentimentResponse
s {$sel:errorList:BatchDetectTargetedSentimentResponse' :: [BatchItemError]
errorList = [BatchItemError]
a} :: BatchDetectTargetedSentimentResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    BatchDetectTargetedSentimentResponse
  where
  rnf :: BatchDetectTargetedSentimentResponse -> ()
rnf BatchDetectTargetedSentimentResponse' {Int
[BatchItemError]
[BatchDetectTargetedSentimentItemResult]
errorList :: [BatchItemError]
resultList :: [BatchDetectTargetedSentimentItemResult]
httpStatus :: Int
$sel:errorList:BatchDetectTargetedSentimentResponse' :: BatchDetectTargetedSentimentResponse -> [BatchItemError]
$sel:resultList:BatchDetectTargetedSentimentResponse' :: BatchDetectTargetedSentimentResponse
-> [BatchDetectTargetedSentimentItemResult]
$sel:httpStatus:BatchDetectTargetedSentimentResponse' :: BatchDetectTargetedSentimentResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BatchDetectTargetedSentimentItemResult]
resultList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BatchItemError]
errorList