{-# 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.StartFaceSearch
-- 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 the asynchronous search for faces in a collection that match the
-- faces of persons detected in a stored video.
--
-- The video must be stored in an Amazon S3 bucket. Use Video to specify
-- the bucket name and the filename of the video. @StartFaceSearch@ returns
-- a job identifier (@JobId@) which you use to get the search results once
-- the search has completed. When searching is finished, Amazon Rekognition
-- Video publishes a completion status to the Amazon Simple Notification
-- Service topic that you specify in @NotificationChannel@. To get the
-- search results, first check that the status value published to the
-- Amazon SNS topic is @SUCCEEDED@. If so, call GetFaceSearch and pass the
-- job identifier (@JobId@) from the initial call to @StartFaceSearch@. For
-- more information, see
-- <https://docs.aws.amazon.com/rekognition/latest/dg/procedure-person-search-videos.html Searching stored videos for faces>.
module Amazonka.Rekognition.StartFaceSearch
  ( -- * Creating a Request
    StartFaceSearch (..),
    newStartFaceSearch,

    -- * Request Lenses
    startFaceSearch_clientRequestToken,
    startFaceSearch_faceMatchThreshold,
    startFaceSearch_jobTag,
    startFaceSearch_notificationChannel,
    startFaceSearch_video,
    startFaceSearch_collectionId,

    -- * Destructuring the Response
    StartFaceSearchResponse (..),
    newStartFaceSearchResponse,

    -- * Response Lenses
    startFaceSearchResponse_jobId,
    startFaceSearchResponse_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:/ 'newStartFaceSearch' smart constructor.
data StartFaceSearch = StartFaceSearch'
  { -- | Idempotent token used to identify the start request. If you use the same
    -- token with multiple @StartFaceSearch@ requests, the same @JobId@ is
    -- returned. Use @ClientRequestToken@ to prevent the same job from being
    -- accidently started more than once.
    StartFaceSearch -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The minimum confidence in the person match to return. For example,
    -- don\'t return any matches where confidence in matches is less than 70%.
    -- The default value is 80%.
    StartFaceSearch -> Maybe Double
faceMatchThreshold :: Prelude.Maybe Prelude.Double,
    -- | 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.
    StartFaceSearch -> 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 search. The Amazon SNS
    -- topic must have a topic name that begins with /AmazonRekognition/ if you
    -- are using the AmazonRekognitionServiceRole permissions policy to access
    -- the topic.
    StartFaceSearch -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    -- | The video you want to search. The video must be stored in an Amazon S3
    -- bucket.
    StartFaceSearch -> Video
video :: Video,
    -- | ID of the collection that contains the faces you want to search for.
    StartFaceSearch -> Text
collectionId :: Prelude.Text
  }
  deriving (StartFaceSearch -> StartFaceSearch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartFaceSearch -> StartFaceSearch -> Bool
$c/= :: StartFaceSearch -> StartFaceSearch -> Bool
== :: StartFaceSearch -> StartFaceSearch -> Bool
$c== :: StartFaceSearch -> StartFaceSearch -> Bool
Prelude.Eq, ReadPrec [StartFaceSearch]
ReadPrec StartFaceSearch
Int -> ReadS StartFaceSearch
ReadS [StartFaceSearch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartFaceSearch]
$creadListPrec :: ReadPrec [StartFaceSearch]
readPrec :: ReadPrec StartFaceSearch
$creadPrec :: ReadPrec StartFaceSearch
readList :: ReadS [StartFaceSearch]
$creadList :: ReadS [StartFaceSearch]
readsPrec :: Int -> ReadS StartFaceSearch
$creadsPrec :: Int -> ReadS StartFaceSearch
Prelude.Read, Int -> StartFaceSearch -> ShowS
[StartFaceSearch] -> ShowS
StartFaceSearch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartFaceSearch] -> ShowS
$cshowList :: [StartFaceSearch] -> ShowS
show :: StartFaceSearch -> String
$cshow :: StartFaceSearch -> String
showsPrec :: Int -> StartFaceSearch -> ShowS
$cshowsPrec :: Int -> StartFaceSearch -> ShowS
Prelude.Show, forall x. Rep StartFaceSearch x -> StartFaceSearch
forall x. StartFaceSearch -> Rep StartFaceSearch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartFaceSearch x -> StartFaceSearch
$cfrom :: forall x. StartFaceSearch -> Rep StartFaceSearch x
Prelude.Generic)

-- |
-- Create a value of 'StartFaceSearch' 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', 'startFaceSearch_clientRequestToken' - Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartFaceSearch@ requests, the same @JobId@ is
-- returned. Use @ClientRequestToken@ to prevent the same job from being
-- accidently started more than once.
--
-- 'faceMatchThreshold', 'startFaceSearch_faceMatchThreshold' - The minimum confidence in the person match to return. For example,
-- don\'t return any matches where confidence in matches is less than 70%.
-- The default value is 80%.
--
-- 'jobTag', 'startFaceSearch_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', 'startFaceSearch_notificationChannel' - The ARN of the Amazon SNS topic to which you want Amazon Rekognition
-- Video to publish the completion status of the search. The Amazon SNS
-- topic must have a topic name that begins with /AmazonRekognition/ if you
-- are using the AmazonRekognitionServiceRole permissions policy to access
-- the topic.
--
-- 'video', 'startFaceSearch_video' - The video you want to search. The video must be stored in an Amazon S3
-- bucket.
--
-- 'collectionId', 'startFaceSearch_collectionId' - ID of the collection that contains the faces you want to search for.
newStartFaceSearch ::
  -- | 'video'
  Video ->
  -- | 'collectionId'
  Prelude.Text ->
  StartFaceSearch
newStartFaceSearch :: Video -> Text -> StartFaceSearch
newStartFaceSearch Video
pVideo_ Text
pCollectionId_ =
  StartFaceSearch'
    { $sel:clientRequestToken:StartFaceSearch' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:faceMatchThreshold:StartFaceSearch' :: Maybe Double
faceMatchThreshold = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartFaceSearch' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartFaceSearch' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:video:StartFaceSearch' :: Video
video = Video
pVideo_,
      $sel:collectionId:StartFaceSearch' :: Text
collectionId = Text
pCollectionId_
    }

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

-- | The minimum confidence in the person match to return. For example,
-- don\'t return any matches where confidence in matches is less than 70%.
-- The default value is 80%.
startFaceSearch_faceMatchThreshold :: Lens.Lens' StartFaceSearch (Prelude.Maybe Prelude.Double)
startFaceSearch_faceMatchThreshold :: Lens' StartFaceSearch (Maybe Double)
startFaceSearch_faceMatchThreshold = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFaceSearch' {Maybe Double
faceMatchThreshold :: Maybe Double
$sel:faceMatchThreshold:StartFaceSearch' :: StartFaceSearch -> Maybe Double
faceMatchThreshold} -> Maybe Double
faceMatchThreshold) (\s :: StartFaceSearch
s@StartFaceSearch' {} Maybe Double
a -> StartFaceSearch
s {$sel:faceMatchThreshold:StartFaceSearch' :: Maybe Double
faceMatchThreshold = Maybe Double
a} :: StartFaceSearch)

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

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

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

-- | ID of the collection that contains the faces you want to search for.
startFaceSearch_collectionId :: Lens.Lens' StartFaceSearch Prelude.Text
startFaceSearch_collectionId :: Lens' StartFaceSearch Text
startFaceSearch_collectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFaceSearch' {Text
collectionId :: Text
$sel:collectionId:StartFaceSearch' :: StartFaceSearch -> Text
collectionId} -> Text
collectionId) (\s :: StartFaceSearch
s@StartFaceSearch' {} Text
a -> StartFaceSearch
s {$sel:collectionId:StartFaceSearch' :: Text
collectionId = Text
a} :: StartFaceSearch)

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

instance Prelude.NFData StartFaceSearch where
  rnf :: StartFaceSearch -> ()
rnf StartFaceSearch' {Maybe Double
Maybe Text
Maybe NotificationChannel
Text
Video
collectionId :: Text
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
faceMatchThreshold :: Maybe Double
clientRequestToken :: Maybe Text
$sel:collectionId:StartFaceSearch' :: StartFaceSearch -> Text
$sel:video:StartFaceSearch' :: StartFaceSearch -> Video
$sel:notificationChannel:StartFaceSearch' :: StartFaceSearch -> Maybe NotificationChannel
$sel:jobTag:StartFaceSearch' :: StartFaceSearch -> Maybe Text
$sel:faceMatchThreshold:StartFaceSearch' :: StartFaceSearch -> Maybe Double
$sel:clientRequestToken:StartFaceSearch' :: StartFaceSearch -> 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 Double
faceMatchThreshold
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
collectionId

instance Data.ToHeaders StartFaceSearch where
  toHeaders :: StartFaceSearch -> 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.StartFaceSearch" ::
                          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 StartFaceSearch where
  toJSON :: StartFaceSearch -> Value
toJSON StartFaceSearch' {Maybe Double
Maybe Text
Maybe NotificationChannel
Text
Video
collectionId :: Text
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
faceMatchThreshold :: Maybe Double
clientRequestToken :: Maybe Text
$sel:collectionId:StartFaceSearch' :: StartFaceSearch -> Text
$sel:video:StartFaceSearch' :: StartFaceSearch -> Video
$sel:notificationChannel:StartFaceSearch' :: StartFaceSearch -> Maybe NotificationChannel
$sel:jobTag:StartFaceSearch' :: StartFaceSearch -> Maybe Text
$sel:faceMatchThreshold:StartFaceSearch' :: StartFaceSearch -> Maybe Double
$sel:clientRequestToken:StartFaceSearch' :: StartFaceSearch -> 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
"FaceMatchThreshold" 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 Double
faceMatchThreshold,
            (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),
            forall a. a -> Maybe a
Prelude.Just (Key
"CollectionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
collectionId)
          ]
      )

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

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

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

-- |
-- Create a value of 'StartFaceSearchResponse' 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', 'startFaceSearchResponse_jobId' - The identifier for the search job. Use @JobId@ to identify the job in a
-- subsequent call to @GetFaceSearch@.
--
-- 'httpStatus', 'startFaceSearchResponse_httpStatus' - The response's http status code.
newStartFaceSearchResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartFaceSearchResponse
newStartFaceSearchResponse :: Int -> StartFaceSearchResponse
newStartFaceSearchResponse Int
pHttpStatus_ =
  StartFaceSearchResponse'
    { $sel:jobId:StartFaceSearchResponse' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartFaceSearchResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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