{-# 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.StartCelebrityRecognition
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts asynchronous recognition of celebrities in a stored video.
--
-- Amazon Rekognition Video can detect celebrities in a video must be
-- stored in an Amazon S3 bucket. Use Video to specify the bucket name and
-- the filename of the video. @StartCelebrityRecognition@ returns a job
-- identifier (@JobId@) which you use to get the results of the analysis.
-- When celebrity recognition analysis is finished, Amazon Rekognition
-- Video publishes a completion status to the Amazon Simple Notification
-- Service topic that you specify in @NotificationChannel@. 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 GetCelebrityRecognition and pass the job identifier (@JobId@) from
-- the initial call to @StartCelebrityRecognition@.
--
-- For more information, see Recognizing celebrities in the Amazon
-- Rekognition Developer Guide.
module Amazonka.Rekognition.StartCelebrityRecognition
  ( -- * Creating a Request
    StartCelebrityRecognition (..),
    newStartCelebrityRecognition,

    -- * Request Lenses
    startCelebrityRecognition_clientRequestToken,
    startCelebrityRecognition_jobTag,
    startCelebrityRecognition_notificationChannel,
    startCelebrityRecognition_video,

    -- * Destructuring the Response
    StartCelebrityRecognitionResponse (..),
    newStartCelebrityRecognitionResponse,

    -- * Response Lenses
    startCelebrityRecognitionResponse_jobId,
    startCelebrityRecognitionResponse_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:/ 'newStartCelebrityRecognition' smart constructor.
data StartCelebrityRecognition = StartCelebrityRecognition'
  { -- | Idempotent token used to identify the start request. If you use the same
    -- token with multiple @StartCelebrityRecognition@ requests, the same
    -- @JobId@ is returned. Use @ClientRequestToken@ to prevent the same job
    -- from being accidently started more than once.
    StartCelebrityRecognition -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | An identifier you specify that\'s returned in the completion
    -- notification that\'s published to your Amazon Simple Notification
    -- Service topic. For example, you can use @JobTag@ to group related jobs
    -- and identify them in the completion notification.
    StartCelebrityRecognition -> Maybe Text
jobTag :: Prelude.Maybe Prelude.Text,
    -- | The Amazon SNS topic ARN that you want Amazon Rekognition Video to
    -- publish the completion status of the celebrity recognition analysis to.
    -- The Amazon SNS topic must have a topic name that begins with
    -- /AmazonRekognition/ if you are using the AmazonRekognitionServiceRole
    -- permissions policy.
    StartCelebrityRecognition -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    -- | The video in which you want to recognize celebrities. The video must be
    -- stored in an Amazon S3 bucket.
    StartCelebrityRecognition -> Video
video :: Video
  }
  deriving (StartCelebrityRecognition -> StartCelebrityRecognition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCelebrityRecognition -> StartCelebrityRecognition -> Bool
$c/= :: StartCelebrityRecognition -> StartCelebrityRecognition -> Bool
== :: StartCelebrityRecognition -> StartCelebrityRecognition -> Bool
$c== :: StartCelebrityRecognition -> StartCelebrityRecognition -> Bool
Prelude.Eq, ReadPrec [StartCelebrityRecognition]
ReadPrec StartCelebrityRecognition
Int -> ReadS StartCelebrityRecognition
ReadS [StartCelebrityRecognition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartCelebrityRecognition]
$creadListPrec :: ReadPrec [StartCelebrityRecognition]
readPrec :: ReadPrec StartCelebrityRecognition
$creadPrec :: ReadPrec StartCelebrityRecognition
readList :: ReadS [StartCelebrityRecognition]
$creadList :: ReadS [StartCelebrityRecognition]
readsPrec :: Int -> ReadS StartCelebrityRecognition
$creadsPrec :: Int -> ReadS StartCelebrityRecognition
Prelude.Read, Int -> StartCelebrityRecognition -> ShowS
[StartCelebrityRecognition] -> ShowS
StartCelebrityRecognition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCelebrityRecognition] -> ShowS
$cshowList :: [StartCelebrityRecognition] -> ShowS
show :: StartCelebrityRecognition -> String
$cshow :: StartCelebrityRecognition -> String
showsPrec :: Int -> StartCelebrityRecognition -> ShowS
$cshowsPrec :: Int -> StartCelebrityRecognition -> ShowS
Prelude.Show, forall x.
Rep StartCelebrityRecognition x -> StartCelebrityRecognition
forall x.
StartCelebrityRecognition -> Rep StartCelebrityRecognition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartCelebrityRecognition x -> StartCelebrityRecognition
$cfrom :: forall x.
StartCelebrityRecognition -> Rep StartCelebrityRecognition x
Prelude.Generic)

-- |
-- Create a value of 'StartCelebrityRecognition' 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:
--
-- 'clientRequestToken', 'startCelebrityRecognition_clientRequestToken' - Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartCelebrityRecognition@ requests, the same
-- @JobId@ is returned. Use @ClientRequestToken@ to prevent the same job
-- from being accidently started more than once.
--
-- 'jobTag', 'startCelebrityRecognition_jobTag' - An identifier you specify that\'s returned in the completion
-- notification that\'s published to your Amazon Simple Notification
-- Service topic. For example, you can use @JobTag@ to group related jobs
-- and identify them in the completion notification.
--
-- 'notificationChannel', 'startCelebrityRecognition_notificationChannel' - The Amazon SNS topic ARN that you want Amazon Rekognition Video to
-- publish the completion status of the celebrity recognition analysis to.
-- The Amazon SNS topic must have a topic name that begins with
-- /AmazonRekognition/ if you are using the AmazonRekognitionServiceRole
-- permissions policy.
--
-- 'video', 'startCelebrityRecognition_video' - The video in which you want to recognize celebrities. The video must be
-- stored in an Amazon S3 bucket.
newStartCelebrityRecognition ::
  -- | 'video'
  Video ->
  StartCelebrityRecognition
newStartCelebrityRecognition :: Video -> StartCelebrityRecognition
newStartCelebrityRecognition Video
pVideo_ =
  StartCelebrityRecognition'
    { $sel:clientRequestToken:StartCelebrityRecognition' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartCelebrityRecognition' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartCelebrityRecognition' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:video:StartCelebrityRecognition' :: Video
video = Video
pVideo_
    }

-- | Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartCelebrityRecognition@ requests, the same
-- @JobId@ is returned. Use @ClientRequestToken@ to prevent the same job
-- from being accidently started more than once.
startCelebrityRecognition_clientRequestToken :: Lens.Lens' StartCelebrityRecognition (Prelude.Maybe Prelude.Text)
startCelebrityRecognition_clientRequestToken :: Lens' StartCelebrityRecognition (Maybe Text)
startCelebrityRecognition_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCelebrityRecognition' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: StartCelebrityRecognition
s@StartCelebrityRecognition' {} Maybe Text
a -> StartCelebrityRecognition
s {$sel:clientRequestToken:StartCelebrityRecognition' :: Maybe Text
clientRequestToken = Maybe Text
a} :: StartCelebrityRecognition)

-- | An identifier you specify that\'s returned in the completion
-- notification that\'s published to your Amazon Simple Notification
-- Service topic. For example, you can use @JobTag@ to group related jobs
-- and identify them in the completion notification.
startCelebrityRecognition_jobTag :: Lens.Lens' StartCelebrityRecognition (Prelude.Maybe Prelude.Text)
startCelebrityRecognition_jobTag :: Lens' StartCelebrityRecognition (Maybe Text)
startCelebrityRecognition_jobTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCelebrityRecognition' {Maybe Text
jobTag :: Maybe Text
$sel:jobTag:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
jobTag} -> Maybe Text
jobTag) (\s :: StartCelebrityRecognition
s@StartCelebrityRecognition' {} Maybe Text
a -> StartCelebrityRecognition
s {$sel:jobTag:StartCelebrityRecognition' :: Maybe Text
jobTag = Maybe Text
a} :: StartCelebrityRecognition)

-- | The Amazon SNS topic ARN that you want Amazon Rekognition Video to
-- publish the completion status of the celebrity recognition analysis to.
-- The Amazon SNS topic must have a topic name that begins with
-- /AmazonRekognition/ if you are using the AmazonRekognitionServiceRole
-- permissions policy.
startCelebrityRecognition_notificationChannel :: Lens.Lens' StartCelebrityRecognition (Prelude.Maybe NotificationChannel)
startCelebrityRecognition_notificationChannel :: Lens' StartCelebrityRecognition (Maybe NotificationChannel)
startCelebrityRecognition_notificationChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCelebrityRecognition' {Maybe NotificationChannel
notificationChannel :: Maybe NotificationChannel
$sel:notificationChannel:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe NotificationChannel
notificationChannel} -> Maybe NotificationChannel
notificationChannel) (\s :: StartCelebrityRecognition
s@StartCelebrityRecognition' {} Maybe NotificationChannel
a -> StartCelebrityRecognition
s {$sel:notificationChannel:StartCelebrityRecognition' :: Maybe NotificationChannel
notificationChannel = Maybe NotificationChannel
a} :: StartCelebrityRecognition)

-- | The video in which you want to recognize celebrities. The video must be
-- stored in an Amazon S3 bucket.
startCelebrityRecognition_video :: Lens.Lens' StartCelebrityRecognition Video
startCelebrityRecognition_video :: Lens' StartCelebrityRecognition Video
startCelebrityRecognition_video = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCelebrityRecognition' {Video
video :: Video
$sel:video:StartCelebrityRecognition' :: StartCelebrityRecognition -> Video
video} -> Video
video) (\s :: StartCelebrityRecognition
s@StartCelebrityRecognition' {} Video
a -> StartCelebrityRecognition
s {$sel:video:StartCelebrityRecognition' :: Video
video = Video
a} :: StartCelebrityRecognition)

instance Core.AWSRequest StartCelebrityRecognition where
  type
    AWSResponse StartCelebrityRecognition =
      StartCelebrityRecognitionResponse
  request :: (Service -> Service)
-> StartCelebrityRecognition -> Request StartCelebrityRecognition
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 StartCelebrityRecognition
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartCelebrityRecognition)))
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 Text -> Int -> StartCelebrityRecognitionResponse
StartCelebrityRecognitionResponse'
            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
"JobId")
            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 StartCelebrityRecognition where
  hashWithSalt :: Int -> StartCelebrityRecognition -> Int
hashWithSalt Int
_salt StartCelebrityRecognition' {Maybe Text
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:video:StartCelebrityRecognition' :: StartCelebrityRecognition -> Video
$sel:notificationChannel:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe NotificationChannel
$sel:jobTag:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
$sel:clientRequestToken:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobTag
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationChannel
notificationChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Video
video

instance Prelude.NFData StartCelebrityRecognition where
  rnf :: StartCelebrityRecognition -> ()
rnf StartCelebrityRecognition' {Maybe Text
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:video:StartCelebrityRecognition' :: StartCelebrityRecognition -> Video
$sel:notificationChannel:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe NotificationChannel
$sel:jobTag:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
$sel:clientRequestToken:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NotificationChannel
notificationChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Video
video

instance Data.ToHeaders StartCelebrityRecognition where
  toHeaders :: StartCelebrityRecognition -> 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.StartCelebrityRecognition" ::
                          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 StartCelebrityRecognition where
  toJSON :: StartCelebrityRecognition -> Value
toJSON StartCelebrityRecognition' {Maybe Text
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:video:StartCelebrityRecognition' :: StartCelebrityRecognition -> Video
$sel:notificationChannel:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe NotificationChannel
$sel:jobTag:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
$sel:clientRequestToken:StartCelebrityRecognition' :: StartCelebrityRecognition -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            (Key
"JobTag" 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
jobTag,
            (Key
"NotificationChannel" 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 NotificationChannel
notificationChannel,
            forall a. a -> Maybe a
Prelude.Just (Key
"Video" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Video
video)
          ]
      )

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

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

-- | /See:/ 'newStartCelebrityRecognitionResponse' smart constructor.
data StartCelebrityRecognitionResponse = StartCelebrityRecognitionResponse'
  { -- | The identifier for the celebrity recognition analysis job. Use @JobId@
    -- to identify the job in a subsequent call to @GetCelebrityRecognition@.
    StartCelebrityRecognitionResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartCelebrityRecognitionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartCelebrityRecognitionResponse
-> StartCelebrityRecognitionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCelebrityRecognitionResponse
-> StartCelebrityRecognitionResponse -> Bool
$c/= :: StartCelebrityRecognitionResponse
-> StartCelebrityRecognitionResponse -> Bool
== :: StartCelebrityRecognitionResponse
-> StartCelebrityRecognitionResponse -> Bool
$c== :: StartCelebrityRecognitionResponse
-> StartCelebrityRecognitionResponse -> Bool
Prelude.Eq, ReadPrec [StartCelebrityRecognitionResponse]
ReadPrec StartCelebrityRecognitionResponse
Int -> ReadS StartCelebrityRecognitionResponse
ReadS [StartCelebrityRecognitionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartCelebrityRecognitionResponse]
$creadListPrec :: ReadPrec [StartCelebrityRecognitionResponse]
readPrec :: ReadPrec StartCelebrityRecognitionResponse
$creadPrec :: ReadPrec StartCelebrityRecognitionResponse
readList :: ReadS [StartCelebrityRecognitionResponse]
$creadList :: ReadS [StartCelebrityRecognitionResponse]
readsPrec :: Int -> ReadS StartCelebrityRecognitionResponse
$creadsPrec :: Int -> ReadS StartCelebrityRecognitionResponse
Prelude.Read, Int -> StartCelebrityRecognitionResponse -> ShowS
[StartCelebrityRecognitionResponse] -> ShowS
StartCelebrityRecognitionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCelebrityRecognitionResponse] -> ShowS
$cshowList :: [StartCelebrityRecognitionResponse] -> ShowS
show :: StartCelebrityRecognitionResponse -> String
$cshow :: StartCelebrityRecognitionResponse -> String
showsPrec :: Int -> StartCelebrityRecognitionResponse -> ShowS
$cshowsPrec :: Int -> StartCelebrityRecognitionResponse -> ShowS
Prelude.Show, forall x.
Rep StartCelebrityRecognitionResponse x
-> StartCelebrityRecognitionResponse
forall x.
StartCelebrityRecognitionResponse
-> Rep StartCelebrityRecognitionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartCelebrityRecognitionResponse x
-> StartCelebrityRecognitionResponse
$cfrom :: forall x.
StartCelebrityRecognitionResponse
-> Rep StartCelebrityRecognitionResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartCelebrityRecognitionResponse' 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:
--
-- 'jobId', 'startCelebrityRecognitionResponse_jobId' - The identifier for the celebrity recognition analysis job. Use @JobId@
-- to identify the job in a subsequent call to @GetCelebrityRecognition@.
--
-- 'httpStatus', 'startCelebrityRecognitionResponse_httpStatus' - The response's http status code.
newStartCelebrityRecognitionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartCelebrityRecognitionResponse
newStartCelebrityRecognitionResponse :: Int -> StartCelebrityRecognitionResponse
newStartCelebrityRecognitionResponse Int
pHttpStatus_ =
  StartCelebrityRecognitionResponse'
    { $sel:jobId:StartCelebrityRecognitionResponse' :: Maybe Text
jobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartCelebrityRecognitionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier for the celebrity recognition analysis job. Use @JobId@
-- to identify the job in a subsequent call to @GetCelebrityRecognition@.
startCelebrityRecognitionResponse_jobId :: Lens.Lens' StartCelebrityRecognitionResponse (Prelude.Maybe Prelude.Text)
startCelebrityRecognitionResponse_jobId :: Lens' StartCelebrityRecognitionResponse (Maybe Text)
startCelebrityRecognitionResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCelebrityRecognitionResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:StartCelebrityRecognitionResponse' :: StartCelebrityRecognitionResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: StartCelebrityRecognitionResponse
s@StartCelebrityRecognitionResponse' {} Maybe Text
a -> StartCelebrityRecognitionResponse
s {$sel:jobId:StartCelebrityRecognitionResponse' :: Maybe Text
jobId = Maybe Text
a} :: StartCelebrityRecognitionResponse)

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

instance
  Prelude.NFData
    StartCelebrityRecognitionResponse
  where
  rnf :: StartCelebrityRecognitionResponse -> ()
rnf StartCelebrityRecognitionResponse' {Int
Maybe Text
httpStatus :: Int
jobId :: Maybe Text
$sel:httpStatus:StartCelebrityRecognitionResponse' :: StartCelebrityRecognitionResponse -> Int
$sel:jobId:StartCelebrityRecognitionResponse' :: StartCelebrityRecognitionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus