{-# 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.StartFaceDetection
-- 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 detection of faces in a stored video.
--
-- Amazon Rekognition Video can detect faces in a video stored in an Amazon
-- S3 bucket. Use Video to specify the bucket name and the filename of the
-- video. @StartFaceDetection@ returns a job identifier (@JobId@) that you
-- use to get the results of the operation. When face detection 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 face detection
-- operation, first check that the status value published to the Amazon SNS
-- topic is @SUCCEEDED@. If so, call GetFaceDetection and pass the job
-- identifier (@JobId@) from the initial call to @StartFaceDetection@.
--
-- For more information, see Detecting faces in a stored video in the
-- Amazon Rekognition Developer Guide.
module Amazonka.Rekognition.StartFaceDetection
  ( -- * Creating a Request
    StartFaceDetection (..),
    newStartFaceDetection,

    -- * Request Lenses
    startFaceDetection_clientRequestToken,
    startFaceDetection_faceAttributes,
    startFaceDetection_jobTag,
    startFaceDetection_notificationChannel,
    startFaceDetection_video,

    -- * Destructuring the Response
    StartFaceDetectionResponse (..),
    newStartFaceDetectionResponse,

    -- * Response Lenses
    startFaceDetectionResponse_jobId,
    startFaceDetectionResponse_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:/ 'newStartFaceDetection' smart constructor.
data StartFaceDetection = StartFaceDetection'
  { -- | Idempotent token used to identify the start request. If you use the same
    -- token with multiple @StartFaceDetection@ requests, the same @JobId@ is
    -- returned. Use @ClientRequestToken@ to prevent the same job from being
    -- accidently started more than once.
    StartFaceDetection -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The face attributes you want returned.
    --
    -- @DEFAULT@ - The following subset of facial attributes are returned:
    -- BoundingBox, Confidence, Pose, Quality and Landmarks.
    --
    -- @ALL@ - All facial attributes are returned.
    StartFaceDetection -> Maybe FaceAttributes
faceAttributes :: Prelude.Maybe FaceAttributes,
    -- | 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.
    StartFaceDetection -> Maybe Text
jobTag :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the Amazon SNS topic to which you want Amazon Rekognition
    -- Video to publish the completion status of the face detection operation.
    -- The Amazon SNS topic must have a topic name that begins with
    -- /AmazonRekognition/ if you are using the AmazonRekognitionServiceRole
    -- permissions policy.
    StartFaceDetection -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    -- | The video in which you want to detect faces. The video must be stored in
    -- an Amazon S3 bucket.
    StartFaceDetection -> Video
video :: Video
  }
  deriving (StartFaceDetection -> StartFaceDetection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartFaceDetection -> StartFaceDetection -> Bool
$c/= :: StartFaceDetection -> StartFaceDetection -> Bool
== :: StartFaceDetection -> StartFaceDetection -> Bool
$c== :: StartFaceDetection -> StartFaceDetection -> Bool
Prelude.Eq, ReadPrec [StartFaceDetection]
ReadPrec StartFaceDetection
Int -> ReadS StartFaceDetection
ReadS [StartFaceDetection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartFaceDetection]
$creadListPrec :: ReadPrec [StartFaceDetection]
readPrec :: ReadPrec StartFaceDetection
$creadPrec :: ReadPrec StartFaceDetection
readList :: ReadS [StartFaceDetection]
$creadList :: ReadS [StartFaceDetection]
readsPrec :: Int -> ReadS StartFaceDetection
$creadsPrec :: Int -> ReadS StartFaceDetection
Prelude.Read, Int -> StartFaceDetection -> ShowS
[StartFaceDetection] -> ShowS
StartFaceDetection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartFaceDetection] -> ShowS
$cshowList :: [StartFaceDetection] -> ShowS
show :: StartFaceDetection -> String
$cshow :: StartFaceDetection -> String
showsPrec :: Int -> StartFaceDetection -> ShowS
$cshowsPrec :: Int -> StartFaceDetection -> ShowS
Prelude.Show, forall x. Rep StartFaceDetection x -> StartFaceDetection
forall x. StartFaceDetection -> Rep StartFaceDetection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartFaceDetection x -> StartFaceDetection
$cfrom :: forall x. StartFaceDetection -> Rep StartFaceDetection x
Prelude.Generic)

-- |
-- Create a value of 'StartFaceDetection' 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', 'startFaceDetection_clientRequestToken' - Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartFaceDetection@ requests, the same @JobId@ is
-- returned. Use @ClientRequestToken@ to prevent the same job from being
-- accidently started more than once.
--
-- 'faceAttributes', 'startFaceDetection_faceAttributes' - The face attributes you want returned.
--
-- @DEFAULT@ - The following subset of facial attributes are returned:
-- BoundingBox, Confidence, Pose, Quality and Landmarks.
--
-- @ALL@ - All facial attributes are returned.
--
-- 'jobTag', 'startFaceDetection_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', 'startFaceDetection_notificationChannel' - The ARN of the Amazon SNS topic to which you want Amazon Rekognition
-- Video to publish the completion status of the face detection operation.
-- The Amazon SNS topic must have a topic name that begins with
-- /AmazonRekognition/ if you are using the AmazonRekognitionServiceRole
-- permissions policy.
--
-- 'video', 'startFaceDetection_video' - The video in which you want to detect faces. The video must be stored in
-- an Amazon S3 bucket.
newStartFaceDetection ::
  -- | 'video'
  Video ->
  StartFaceDetection
newStartFaceDetection :: Video -> StartFaceDetection
newStartFaceDetection Video
pVideo_ =
  StartFaceDetection'
    { $sel:clientRequestToken:StartFaceDetection' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:faceAttributes:StartFaceDetection' :: Maybe FaceAttributes
faceAttributes = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartFaceDetection' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartFaceDetection' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:video:StartFaceDetection' :: Video
video = Video
pVideo_
    }

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

-- | The face attributes you want returned.
--
-- @DEFAULT@ - The following subset of facial attributes are returned:
-- BoundingBox, Confidence, Pose, Quality and Landmarks.
--
-- @ALL@ - All facial attributes are returned.
startFaceDetection_faceAttributes :: Lens.Lens' StartFaceDetection (Prelude.Maybe FaceAttributes)
startFaceDetection_faceAttributes :: Lens' StartFaceDetection (Maybe FaceAttributes)
startFaceDetection_faceAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFaceDetection' {Maybe FaceAttributes
faceAttributes :: Maybe FaceAttributes
$sel:faceAttributes:StartFaceDetection' :: StartFaceDetection -> Maybe FaceAttributes
faceAttributes} -> Maybe FaceAttributes
faceAttributes) (\s :: StartFaceDetection
s@StartFaceDetection' {} Maybe FaceAttributes
a -> StartFaceDetection
s {$sel:faceAttributes:StartFaceDetection' :: Maybe FaceAttributes
faceAttributes = Maybe FaceAttributes
a} :: StartFaceDetection)

-- | 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.
startFaceDetection_jobTag :: Lens.Lens' StartFaceDetection (Prelude.Maybe Prelude.Text)
startFaceDetection_jobTag :: Lens' StartFaceDetection (Maybe Text)
startFaceDetection_jobTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFaceDetection' {Maybe Text
jobTag :: Maybe Text
$sel:jobTag:StartFaceDetection' :: StartFaceDetection -> Maybe Text
jobTag} -> Maybe Text
jobTag) (\s :: StartFaceDetection
s@StartFaceDetection' {} Maybe Text
a -> StartFaceDetection
s {$sel:jobTag:StartFaceDetection' :: Maybe Text
jobTag = Maybe Text
a} :: StartFaceDetection)

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

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

instance Core.AWSRequest StartFaceDetection where
  type
    AWSResponse StartFaceDetection =
      StartFaceDetectionResponse
  request :: (Service -> Service)
-> StartFaceDetection -> Request StartFaceDetection
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 StartFaceDetection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartFaceDetection)))
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 -> StartFaceDetectionResponse
StartFaceDetectionResponse'
            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 StartFaceDetection where
  hashWithSalt :: Int -> StartFaceDetection -> Int
hashWithSalt Int
_salt StartFaceDetection' {Maybe Text
Maybe FaceAttributes
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
faceAttributes :: Maybe FaceAttributes
clientRequestToken :: Maybe Text
$sel:video:StartFaceDetection' :: StartFaceDetection -> Video
$sel:notificationChannel:StartFaceDetection' :: StartFaceDetection -> Maybe NotificationChannel
$sel:jobTag:StartFaceDetection' :: StartFaceDetection -> Maybe Text
$sel:faceAttributes:StartFaceDetection' :: StartFaceDetection -> Maybe FaceAttributes
$sel:clientRequestToken:StartFaceDetection' :: StartFaceDetection -> 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 FaceAttributes
faceAttributes
      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 StartFaceDetection where
  rnf :: StartFaceDetection -> ()
rnf StartFaceDetection' {Maybe Text
Maybe FaceAttributes
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
faceAttributes :: Maybe FaceAttributes
clientRequestToken :: Maybe Text
$sel:video:StartFaceDetection' :: StartFaceDetection -> Video
$sel:notificationChannel:StartFaceDetection' :: StartFaceDetection -> Maybe NotificationChannel
$sel:jobTag:StartFaceDetection' :: StartFaceDetection -> Maybe Text
$sel:faceAttributes:StartFaceDetection' :: StartFaceDetection -> Maybe FaceAttributes
$sel:clientRequestToken:StartFaceDetection' :: StartFaceDetection -> 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 FaceAttributes
faceAttributes
      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 StartFaceDetection where
  toHeaders :: StartFaceDetection -> 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.StartFaceDetection" ::
                          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 StartFaceDetection where
  toJSON :: StartFaceDetection -> Value
toJSON StartFaceDetection' {Maybe Text
Maybe FaceAttributes
Maybe NotificationChannel
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
faceAttributes :: Maybe FaceAttributes
clientRequestToken :: Maybe Text
$sel:video:StartFaceDetection' :: StartFaceDetection -> Video
$sel:notificationChannel:StartFaceDetection' :: StartFaceDetection -> Maybe NotificationChannel
$sel:jobTag:StartFaceDetection' :: StartFaceDetection -> Maybe Text
$sel:faceAttributes:StartFaceDetection' :: StartFaceDetection -> Maybe FaceAttributes
$sel:clientRequestToken:StartFaceDetection' :: StartFaceDetection -> 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
"FaceAttributes" 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 FaceAttributes
faceAttributes,
            (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 StartFaceDetection where
  toPath :: StartFaceDetection -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'StartFaceDetectionResponse' 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', 'startFaceDetectionResponse_jobId' - The identifier for the face detection job. Use @JobId@ to identify the
-- job in a subsequent call to @GetFaceDetection@.
--
-- 'httpStatus', 'startFaceDetectionResponse_httpStatus' - The response's http status code.
newStartFaceDetectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartFaceDetectionResponse
newStartFaceDetectionResponse :: Int -> StartFaceDetectionResponse
newStartFaceDetectionResponse Int
pHttpStatus_ =
  StartFaceDetectionResponse'
    { $sel:jobId:StartFaceDetectionResponse' :: Maybe Text
jobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartFaceDetectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier for the face detection job. Use @JobId@ to identify the
-- job in a subsequent call to @GetFaceDetection@.
startFaceDetectionResponse_jobId :: Lens.Lens' StartFaceDetectionResponse (Prelude.Maybe Prelude.Text)
startFaceDetectionResponse_jobId :: Lens' StartFaceDetectionResponse (Maybe Text)
startFaceDetectionResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFaceDetectionResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:StartFaceDetectionResponse' :: StartFaceDetectionResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: StartFaceDetectionResponse
s@StartFaceDetectionResponse' {} Maybe Text
a -> StartFaceDetectionResponse
s {$sel:jobId:StartFaceDetectionResponse' :: Maybe Text
jobId = Maybe Text
a} :: StartFaceDetectionResponse)

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

instance Prelude.NFData StartFaceDetectionResponse where
  rnf :: StartFaceDetectionResponse -> ()
rnf StartFaceDetectionResponse' {Int
Maybe Text
httpStatus :: Int
jobId :: Maybe Text
$sel:httpStatus:StartFaceDetectionResponse' :: StartFaceDetectionResponse -> Int
$sel:jobId:StartFaceDetectionResponse' :: StartFaceDetectionResponse -> 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