{-# 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.Rekognition.GetCelebrityRecognition
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the celebrity recognition results for a Amazon Rekognition Video
-- analysis started by StartCelebrityRecognition.
--
-- Celebrity recognition in a video is an asynchronous operation. Analysis
-- is started by a call to StartCelebrityRecognition which returns a job
-- identifier (@JobId@).
--
-- When the celebrity recognition operation finishes, Amazon Rekognition
-- Video publishes a completion status to the Amazon Simple Notification
-- Service topic registered in the initial call to
-- @StartCelebrityRecognition@. To get the results of the celebrity
-- recognition analysis, first check that the status value published to the
-- Amazon SNS topic is @SUCCEEDED@. If so, call @GetCelebrityDetection@ and
-- pass the job identifier (@JobId@) from the initial call to
-- @StartCelebrityDetection@.
--
-- For more information, see Working With Stored Videos in the Amazon
-- Rekognition Developer Guide.
--
-- @GetCelebrityRecognition@ returns detected celebrities and the time(s)
-- they are detected in an array (@Celebrities@) of CelebrityRecognition
-- objects. Each @CelebrityRecognition@ contains information about the
-- celebrity in a CelebrityDetail object and the time, @Timestamp@, the
-- celebrity was detected. This CelebrityDetail object stores information
-- about the detected celebrity\'s face attributes, a face bounding box,
-- known gender, the celebrity\'s name, and a confidence estimate.
--
-- @GetCelebrityRecognition@ only returns the default facial attributes
-- (@BoundingBox@, @Confidence@, @Landmarks@, @Pose@, and @Quality@). The
-- @BoundingBox@ field only applies to the detected face instance. The
-- other facial attributes listed in the @Face@ object of the following
-- response syntax are not returned. For more information, see FaceDetail
-- in the Amazon Rekognition Developer Guide.
--
-- By default, the @Celebrities@ array is sorted by time (milliseconds from
-- the start of the video). You can also sort the array by celebrity by
-- specifying the value @ID@ in the @SortBy@ input parameter.
--
-- The @CelebrityDetail@ object includes the celebrity identifer and
-- additional information urls. If you don\'t store the additional
-- information urls, you can get them later by calling GetCelebrityInfo
-- with the celebrity identifer.
--
-- No information is returned for faces not recognized as celebrities.
--
-- Use MaxResults parameter to limit the number of labels returned. If
-- there are more results than specified in @MaxResults@, the value of
-- @NextToken@ in the operation response contains a pagination token for
-- getting the next set of results. To get the next page of results, call
-- @GetCelebrityDetection@ and populate the @NextToken@ request parameter
-- with the token value returned from the previous call to
-- @GetCelebrityRecognition@.
module Amazonka.Rekognition.GetCelebrityRecognition
  ( -- * Creating a Request
    GetCelebrityRecognition (..),
    newGetCelebrityRecognition,

    -- * Request Lenses
    getCelebrityRecognition_maxResults,
    getCelebrityRecognition_nextToken,
    getCelebrityRecognition_sortBy,
    getCelebrityRecognition_jobId,

    -- * Destructuring the Response
    GetCelebrityRecognitionResponse (..),
    newGetCelebrityRecognitionResponse,

    -- * Response Lenses
    getCelebrityRecognitionResponse_celebrities,
    getCelebrityRecognitionResponse_jobStatus,
    getCelebrityRecognitionResponse_nextToken,
    getCelebrityRecognitionResponse_statusMessage,
    getCelebrityRecognitionResponse_videoMetadata,
    getCelebrityRecognitionResponse_httpStatus,
  )
where

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 Amazonka.Rekognition.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetCelebrityRecognition' smart constructor.
data GetCelebrityRecognition = GetCelebrityRecognition'
  { -- | Maximum number of results to return per paginated call. The largest
    -- value you can specify is 1000. If you specify a value greater than 1000,
    -- a maximum of 1000 results is returned. The default value is 1000.
    GetCelebrityRecognition -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there is more
    -- recognized celebrities to retrieve), Amazon Rekognition Video returns a
    -- pagination token in the response. You can use this pagination token to
    -- retrieve the next set of celebrities.
    GetCelebrityRecognition -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Sort to use for celebrities returned in @Celebrities@ field. Specify
    -- @ID@ to sort by the celebrity identifier, specify @TIMESTAMP@ to sort by
    -- the time the celebrity was recognized.
    GetCelebrityRecognition -> Maybe CelebrityRecognitionSortBy
sortBy :: Prelude.Maybe CelebrityRecognitionSortBy,
    -- | Job identifier for the required celebrity recognition analysis. You can
    -- get the job identifer from a call to @StartCelebrityRecognition@.
    GetCelebrityRecognition -> Text
jobId :: Prelude.Text
  }
  deriving (GetCelebrityRecognition -> GetCelebrityRecognition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCelebrityRecognition -> GetCelebrityRecognition -> Bool
$c/= :: GetCelebrityRecognition -> GetCelebrityRecognition -> Bool
== :: GetCelebrityRecognition -> GetCelebrityRecognition -> Bool
$c== :: GetCelebrityRecognition -> GetCelebrityRecognition -> Bool
Prelude.Eq, ReadPrec [GetCelebrityRecognition]
ReadPrec GetCelebrityRecognition
Int -> ReadS GetCelebrityRecognition
ReadS [GetCelebrityRecognition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCelebrityRecognition]
$creadListPrec :: ReadPrec [GetCelebrityRecognition]
readPrec :: ReadPrec GetCelebrityRecognition
$creadPrec :: ReadPrec GetCelebrityRecognition
readList :: ReadS [GetCelebrityRecognition]
$creadList :: ReadS [GetCelebrityRecognition]
readsPrec :: Int -> ReadS GetCelebrityRecognition
$creadsPrec :: Int -> ReadS GetCelebrityRecognition
Prelude.Read, Int -> GetCelebrityRecognition -> ShowS
[GetCelebrityRecognition] -> ShowS
GetCelebrityRecognition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCelebrityRecognition] -> ShowS
$cshowList :: [GetCelebrityRecognition] -> ShowS
show :: GetCelebrityRecognition -> String
$cshow :: GetCelebrityRecognition -> String
showsPrec :: Int -> GetCelebrityRecognition -> ShowS
$cshowsPrec :: Int -> GetCelebrityRecognition -> ShowS
Prelude.Show, forall x. Rep GetCelebrityRecognition x -> GetCelebrityRecognition
forall x. GetCelebrityRecognition -> Rep GetCelebrityRecognition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCelebrityRecognition x -> GetCelebrityRecognition
$cfrom :: forall x. GetCelebrityRecognition -> Rep GetCelebrityRecognition x
Prelude.Generic)

-- |
-- Create a value of 'GetCelebrityRecognition' 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:
--
-- 'maxResults', 'getCelebrityRecognition_maxResults' - Maximum number of results to return per paginated call. The largest
-- value you can specify is 1000. If you specify a value greater than 1000,
-- a maximum of 1000 results is returned. The default value is 1000.
--
-- 'nextToken', 'getCelebrityRecognition_nextToken' - If the previous response was incomplete (because there is more
-- recognized celebrities to retrieve), Amazon Rekognition Video returns a
-- pagination token in the response. You can use this pagination token to
-- retrieve the next set of celebrities.
--
-- 'sortBy', 'getCelebrityRecognition_sortBy' - Sort to use for celebrities returned in @Celebrities@ field. Specify
-- @ID@ to sort by the celebrity identifier, specify @TIMESTAMP@ to sort by
-- the time the celebrity was recognized.
--
-- 'jobId', 'getCelebrityRecognition_jobId' - Job identifier for the required celebrity recognition analysis. You can
-- get the job identifer from a call to @StartCelebrityRecognition@.
newGetCelebrityRecognition ::
  -- | 'jobId'
  Prelude.Text ->
  GetCelebrityRecognition
newGetCelebrityRecognition :: Text -> GetCelebrityRecognition
newGetCelebrityRecognition Text
pJobId_ =
  GetCelebrityRecognition'
    { $sel:maxResults:GetCelebrityRecognition' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetCelebrityRecognition' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:GetCelebrityRecognition' :: Maybe CelebrityRecognitionSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:GetCelebrityRecognition' :: Text
jobId = Text
pJobId_
    }

-- | Maximum number of results to return per paginated call. The largest
-- value you can specify is 1000. If you specify a value greater than 1000,
-- a maximum of 1000 results is returned. The default value is 1000.
getCelebrityRecognition_maxResults :: Lens.Lens' GetCelebrityRecognition (Prelude.Maybe Prelude.Natural)
getCelebrityRecognition_maxResults :: Lens' GetCelebrityRecognition (Maybe Natural)
getCelebrityRecognition_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognition' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetCelebrityRecognition
s@GetCelebrityRecognition' {} Maybe Natural
a -> GetCelebrityRecognition
s {$sel:maxResults:GetCelebrityRecognition' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetCelebrityRecognition)

-- | If the previous response was incomplete (because there is more
-- recognized celebrities to retrieve), Amazon Rekognition Video returns a
-- pagination token in the response. You can use this pagination token to
-- retrieve the next set of celebrities.
getCelebrityRecognition_nextToken :: Lens.Lens' GetCelebrityRecognition (Prelude.Maybe Prelude.Text)
getCelebrityRecognition_nextToken :: Lens' GetCelebrityRecognition (Maybe Text)
getCelebrityRecognition_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognition' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetCelebrityRecognition
s@GetCelebrityRecognition' {} Maybe Text
a -> GetCelebrityRecognition
s {$sel:nextToken:GetCelebrityRecognition' :: Maybe Text
nextToken = Maybe Text
a} :: GetCelebrityRecognition)

-- | Sort to use for celebrities returned in @Celebrities@ field. Specify
-- @ID@ to sort by the celebrity identifier, specify @TIMESTAMP@ to sort by
-- the time the celebrity was recognized.
getCelebrityRecognition_sortBy :: Lens.Lens' GetCelebrityRecognition (Prelude.Maybe CelebrityRecognitionSortBy)
getCelebrityRecognition_sortBy :: Lens' GetCelebrityRecognition (Maybe CelebrityRecognitionSortBy)
getCelebrityRecognition_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognition' {Maybe CelebrityRecognitionSortBy
sortBy :: Maybe CelebrityRecognitionSortBy
$sel:sortBy:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe CelebrityRecognitionSortBy
sortBy} -> Maybe CelebrityRecognitionSortBy
sortBy) (\s :: GetCelebrityRecognition
s@GetCelebrityRecognition' {} Maybe CelebrityRecognitionSortBy
a -> GetCelebrityRecognition
s {$sel:sortBy:GetCelebrityRecognition' :: Maybe CelebrityRecognitionSortBy
sortBy = Maybe CelebrityRecognitionSortBy
a} :: GetCelebrityRecognition)

-- | Job identifier for the required celebrity recognition analysis. You can
-- get the job identifer from a call to @StartCelebrityRecognition@.
getCelebrityRecognition_jobId :: Lens.Lens' GetCelebrityRecognition Prelude.Text
getCelebrityRecognition_jobId :: Lens' GetCelebrityRecognition Text
getCelebrityRecognition_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognition' {Text
jobId :: Text
$sel:jobId:GetCelebrityRecognition' :: GetCelebrityRecognition -> Text
jobId} -> Text
jobId) (\s :: GetCelebrityRecognition
s@GetCelebrityRecognition' {} Text
a -> GetCelebrityRecognition
s {$sel:jobId:GetCelebrityRecognition' :: Text
jobId = Text
a} :: GetCelebrityRecognition)

instance Core.AWSRequest GetCelebrityRecognition where
  type
    AWSResponse GetCelebrityRecognition =
      GetCelebrityRecognitionResponse
  request :: (Service -> Service)
-> GetCelebrityRecognition -> Request GetCelebrityRecognition
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 GetCelebrityRecognition
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCelebrityRecognition)))
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 [CelebrityRecognition]
-> Maybe VideoJobStatus
-> Maybe Text
-> Maybe Text
-> Maybe VideoMetadata
-> Int
-> GetCelebrityRecognitionResponse
GetCelebrityRecognitionResponse'
            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
"Celebrities" 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
"JobStatus")
            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
"NextToken")
            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
"StatusMessage")
            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
"VideoMetadata")
            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 Prelude.Hashable GetCelebrityRecognition where
  hashWithSalt :: Int -> GetCelebrityRecognition -> Int
hashWithSalt Int
_salt GetCelebrityRecognition' {Maybe Natural
Maybe Text
Maybe CelebrityRecognitionSortBy
Text
jobId :: Text
sortBy :: Maybe CelebrityRecognitionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetCelebrityRecognition' :: GetCelebrityRecognition -> Text
$sel:sortBy:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe CelebrityRecognitionSortBy
$sel:nextToken:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Text
$sel:maxResults:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CelebrityRecognitionSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData GetCelebrityRecognition where
  rnf :: GetCelebrityRecognition -> ()
rnf GetCelebrityRecognition' {Maybe Natural
Maybe Text
Maybe CelebrityRecognitionSortBy
Text
jobId :: Text
sortBy :: Maybe CelebrityRecognitionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetCelebrityRecognition' :: GetCelebrityRecognition -> Text
$sel:sortBy:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe CelebrityRecognitionSortBy
$sel:nextToken:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Text
$sel:maxResults:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CelebrityRecognitionSortBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

instance Data.ToHeaders GetCelebrityRecognition where
  toHeaders :: GetCelebrityRecognition -> 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
"RekognitionService.GetCelebrityRecognition" ::
                          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 GetCelebrityRecognition where
  toJSON :: GetCelebrityRecognition -> Value
toJSON GetCelebrityRecognition' {Maybe Natural
Maybe Text
Maybe CelebrityRecognitionSortBy
Text
jobId :: Text
sortBy :: Maybe CelebrityRecognitionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetCelebrityRecognition' :: GetCelebrityRecognition -> Text
$sel:sortBy:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe CelebrityRecognitionSortBy
$sel:nextToken:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Text
$sel:maxResults:GetCelebrityRecognition' :: GetCelebrityRecognition -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"SortBy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CelebrityRecognitionSortBy
sortBy,
            forall a. a -> Maybe a
Prelude.Just (Key
"JobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)
          ]
      )

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

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

-- | /See:/ 'newGetCelebrityRecognitionResponse' smart constructor.
data GetCelebrityRecognitionResponse = GetCelebrityRecognitionResponse'
  { -- | Array of celebrities recognized in the video.
    GetCelebrityRecognitionResponse -> Maybe [CelebrityRecognition]
celebrities :: Prelude.Maybe [CelebrityRecognition],
    -- | The current status of the celebrity recognition job.
    GetCelebrityRecognitionResponse -> Maybe VideoJobStatus
jobStatus :: Prelude.Maybe VideoJobStatus,
    -- | If the response is truncated, Amazon Rekognition Video returns this
    -- token that you can use in the subsequent request to retrieve the next
    -- set of celebrities.
    GetCelebrityRecognitionResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | If the job fails, @StatusMessage@ provides a descriptive error message.
    GetCelebrityRecognitionResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | Information about a video that Amazon Rekognition Video analyzed.
    -- @Videometadata@ is returned in every page of paginated responses from a
    -- Amazon Rekognition Video operation.
    GetCelebrityRecognitionResponse -> Maybe VideoMetadata
videoMetadata :: Prelude.Maybe VideoMetadata,
    -- | The response's http status code.
    GetCelebrityRecognitionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCelebrityRecognitionResponse
-> GetCelebrityRecognitionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCelebrityRecognitionResponse
-> GetCelebrityRecognitionResponse -> Bool
$c/= :: GetCelebrityRecognitionResponse
-> GetCelebrityRecognitionResponse -> Bool
== :: GetCelebrityRecognitionResponse
-> GetCelebrityRecognitionResponse -> Bool
$c== :: GetCelebrityRecognitionResponse
-> GetCelebrityRecognitionResponse -> Bool
Prelude.Eq, ReadPrec [GetCelebrityRecognitionResponse]
ReadPrec GetCelebrityRecognitionResponse
Int -> ReadS GetCelebrityRecognitionResponse
ReadS [GetCelebrityRecognitionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCelebrityRecognitionResponse]
$creadListPrec :: ReadPrec [GetCelebrityRecognitionResponse]
readPrec :: ReadPrec GetCelebrityRecognitionResponse
$creadPrec :: ReadPrec GetCelebrityRecognitionResponse
readList :: ReadS [GetCelebrityRecognitionResponse]
$creadList :: ReadS [GetCelebrityRecognitionResponse]
readsPrec :: Int -> ReadS GetCelebrityRecognitionResponse
$creadsPrec :: Int -> ReadS GetCelebrityRecognitionResponse
Prelude.Read, Int -> GetCelebrityRecognitionResponse -> ShowS
[GetCelebrityRecognitionResponse] -> ShowS
GetCelebrityRecognitionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCelebrityRecognitionResponse] -> ShowS
$cshowList :: [GetCelebrityRecognitionResponse] -> ShowS
show :: GetCelebrityRecognitionResponse -> String
$cshow :: GetCelebrityRecognitionResponse -> String
showsPrec :: Int -> GetCelebrityRecognitionResponse -> ShowS
$cshowsPrec :: Int -> GetCelebrityRecognitionResponse -> ShowS
Prelude.Show, forall x.
Rep GetCelebrityRecognitionResponse x
-> GetCelebrityRecognitionResponse
forall x.
GetCelebrityRecognitionResponse
-> Rep GetCelebrityRecognitionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCelebrityRecognitionResponse x
-> GetCelebrityRecognitionResponse
$cfrom :: forall x.
GetCelebrityRecognitionResponse
-> Rep GetCelebrityRecognitionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCelebrityRecognitionResponse' 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:
--
-- 'celebrities', 'getCelebrityRecognitionResponse_celebrities' - Array of celebrities recognized in the video.
--
-- 'jobStatus', 'getCelebrityRecognitionResponse_jobStatus' - The current status of the celebrity recognition job.
--
-- 'nextToken', 'getCelebrityRecognitionResponse_nextToken' - If the response is truncated, Amazon Rekognition Video returns this
-- token that you can use in the subsequent request to retrieve the next
-- set of celebrities.
--
-- 'statusMessage', 'getCelebrityRecognitionResponse_statusMessage' - If the job fails, @StatusMessage@ provides a descriptive error message.
--
-- 'videoMetadata', 'getCelebrityRecognitionResponse_videoMetadata' - Information about a video that Amazon Rekognition Video analyzed.
-- @Videometadata@ is returned in every page of paginated responses from a
-- Amazon Rekognition Video operation.
--
-- 'httpStatus', 'getCelebrityRecognitionResponse_httpStatus' - The response's http status code.
newGetCelebrityRecognitionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCelebrityRecognitionResponse
newGetCelebrityRecognitionResponse :: Int -> GetCelebrityRecognitionResponse
newGetCelebrityRecognitionResponse Int
pHttpStatus_ =
  GetCelebrityRecognitionResponse'
    { $sel:celebrities:GetCelebrityRecognitionResponse' :: Maybe [CelebrityRecognition]
celebrities =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobStatus:GetCelebrityRecognitionResponse' :: Maybe VideoJobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetCelebrityRecognitionResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetCelebrityRecognitionResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:videoMetadata:GetCelebrityRecognitionResponse' :: Maybe VideoMetadata
videoMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCelebrityRecognitionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Array of celebrities recognized in the video.
getCelebrityRecognitionResponse_celebrities :: Lens.Lens' GetCelebrityRecognitionResponse (Prelude.Maybe [CelebrityRecognition])
getCelebrityRecognitionResponse_celebrities :: Lens'
  GetCelebrityRecognitionResponse (Maybe [CelebrityRecognition])
getCelebrityRecognitionResponse_celebrities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognitionResponse' {Maybe [CelebrityRecognition]
celebrities :: Maybe [CelebrityRecognition]
$sel:celebrities:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe [CelebrityRecognition]
celebrities} -> Maybe [CelebrityRecognition]
celebrities) (\s :: GetCelebrityRecognitionResponse
s@GetCelebrityRecognitionResponse' {} Maybe [CelebrityRecognition]
a -> GetCelebrityRecognitionResponse
s {$sel:celebrities:GetCelebrityRecognitionResponse' :: Maybe [CelebrityRecognition]
celebrities = Maybe [CelebrityRecognition]
a} :: GetCelebrityRecognitionResponse) 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 current status of the celebrity recognition job.
getCelebrityRecognitionResponse_jobStatus :: Lens.Lens' GetCelebrityRecognitionResponse (Prelude.Maybe VideoJobStatus)
getCelebrityRecognitionResponse_jobStatus :: Lens' GetCelebrityRecognitionResponse (Maybe VideoJobStatus)
getCelebrityRecognitionResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognitionResponse' {Maybe VideoJobStatus
jobStatus :: Maybe VideoJobStatus
$sel:jobStatus:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe VideoJobStatus
jobStatus} -> Maybe VideoJobStatus
jobStatus) (\s :: GetCelebrityRecognitionResponse
s@GetCelebrityRecognitionResponse' {} Maybe VideoJobStatus
a -> GetCelebrityRecognitionResponse
s {$sel:jobStatus:GetCelebrityRecognitionResponse' :: Maybe VideoJobStatus
jobStatus = Maybe VideoJobStatus
a} :: GetCelebrityRecognitionResponse)

-- | If the response is truncated, Amazon Rekognition Video returns this
-- token that you can use in the subsequent request to retrieve the next
-- set of celebrities.
getCelebrityRecognitionResponse_nextToken :: Lens.Lens' GetCelebrityRecognitionResponse (Prelude.Maybe Prelude.Text)
getCelebrityRecognitionResponse_nextToken :: Lens' GetCelebrityRecognitionResponse (Maybe Text)
getCelebrityRecognitionResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognitionResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetCelebrityRecognitionResponse
s@GetCelebrityRecognitionResponse' {} Maybe Text
a -> GetCelebrityRecognitionResponse
s {$sel:nextToken:GetCelebrityRecognitionResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetCelebrityRecognitionResponse)

-- | If the job fails, @StatusMessage@ provides a descriptive error message.
getCelebrityRecognitionResponse_statusMessage :: Lens.Lens' GetCelebrityRecognitionResponse (Prelude.Maybe Prelude.Text)
getCelebrityRecognitionResponse_statusMessage :: Lens' GetCelebrityRecognitionResponse (Maybe Text)
getCelebrityRecognitionResponse_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognitionResponse' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: GetCelebrityRecognitionResponse
s@GetCelebrityRecognitionResponse' {} Maybe Text
a -> GetCelebrityRecognitionResponse
s {$sel:statusMessage:GetCelebrityRecognitionResponse' :: Maybe Text
statusMessage = Maybe Text
a} :: GetCelebrityRecognitionResponse)

-- | Information about a video that Amazon Rekognition Video analyzed.
-- @Videometadata@ is returned in every page of paginated responses from a
-- Amazon Rekognition Video operation.
getCelebrityRecognitionResponse_videoMetadata :: Lens.Lens' GetCelebrityRecognitionResponse (Prelude.Maybe VideoMetadata)
getCelebrityRecognitionResponse_videoMetadata :: Lens' GetCelebrityRecognitionResponse (Maybe VideoMetadata)
getCelebrityRecognitionResponse_videoMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCelebrityRecognitionResponse' {Maybe VideoMetadata
videoMetadata :: Maybe VideoMetadata
$sel:videoMetadata:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe VideoMetadata
videoMetadata} -> Maybe VideoMetadata
videoMetadata) (\s :: GetCelebrityRecognitionResponse
s@GetCelebrityRecognitionResponse' {} Maybe VideoMetadata
a -> GetCelebrityRecognitionResponse
s {$sel:videoMetadata:GetCelebrityRecognitionResponse' :: Maybe VideoMetadata
videoMetadata = Maybe VideoMetadata
a} :: GetCelebrityRecognitionResponse)

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

instance
  Prelude.NFData
    GetCelebrityRecognitionResponse
  where
  rnf :: GetCelebrityRecognitionResponse -> ()
rnf GetCelebrityRecognitionResponse' {Int
Maybe [CelebrityRecognition]
Maybe Text
Maybe VideoJobStatus
Maybe VideoMetadata
httpStatus :: Int
videoMetadata :: Maybe VideoMetadata
statusMessage :: Maybe Text
nextToken :: Maybe Text
jobStatus :: Maybe VideoJobStatus
celebrities :: Maybe [CelebrityRecognition]
$sel:httpStatus:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Int
$sel:videoMetadata:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe VideoMetadata
$sel:statusMessage:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe Text
$sel:nextToken:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe Text
$sel:jobStatus:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe VideoJobStatus
$sel:celebrities:GetCelebrityRecognitionResponse' :: GetCelebrityRecognitionResponse -> Maybe [CelebrityRecognition]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CelebrityRecognition]
celebrities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VideoJobStatus
jobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VideoMetadata
videoMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus