{-# 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.GetFaceSearch
-- 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 face search results for Amazon Rekognition Video face search
-- started by StartFaceSearch. The search returns faces in a collection
-- that match the faces of persons detected in a video. It also includes
-- the time(s) that faces are matched in the video.
--
-- Face search in a video is an asynchronous operation. You start face
-- search by calling to StartFaceSearch which returns a job identifier
-- (@JobId@). When the search operation finishes, Amazon Rekognition Video
-- publishes a completion status to the Amazon Simple Notification Service
-- topic registered in the initial call to @StartFaceSearch@. 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 Searching Faces in a Collection in the Amazon
-- Rekognition Developer Guide.
--
-- The search results are retured in an array, @Persons@, of PersonMatch
-- objects. Each@PersonMatch@ element contains details about the matching
-- faces in the input collection, person information (facial attributes,
-- bounding boxes, and person identifer) for the matched person, and the
-- time the person was matched in the video.
--
-- @GetFaceSearch@ only returns the default facial attributes
-- (@BoundingBox@, @Confidence@, @Landmarks@, @Pose@, and @Quality@). 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 @Persons@ array is sorted by the time, in milliseconds
-- from the start of the video, persons are matched. You can also sort by
-- persons by specifying @INDEX@ for the @SORTBY@ input parameter.
module Amazonka.Rekognition.GetFaceSearch
  ( -- * Creating a Request
    GetFaceSearch (..),
    newGetFaceSearch,

    -- * Request Lenses
    getFaceSearch_maxResults,
    getFaceSearch_nextToken,
    getFaceSearch_sortBy,
    getFaceSearch_jobId,

    -- * Destructuring the Response
    GetFaceSearchResponse (..),
    newGetFaceSearchResponse,

    -- * Response Lenses
    getFaceSearchResponse_jobStatus,
    getFaceSearchResponse_nextToken,
    getFaceSearchResponse_persons,
    getFaceSearchResponse_statusMessage,
    getFaceSearchResponse_videoMetadata,
    getFaceSearchResponse_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:/ 'newGetFaceSearch' smart constructor.
data GetFaceSearch = GetFaceSearch'
  { -- | 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.
    GetFaceSearch -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there is more search
    -- results to retrieve), Amazon Rekognition Video returns a pagination
    -- token in the response. You can use this pagination token to retrieve the
    -- next set of search results.
    GetFaceSearch -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Sort to use for grouping faces in the response. Use @TIMESTAMP@ to group
    -- faces by the time that they are recognized. Use @INDEX@ to sort by
    -- recognized faces.
    GetFaceSearch -> Maybe FaceSearchSortBy
sortBy :: Prelude.Maybe FaceSearchSortBy,
    -- | The job identifer for the search request. You get the job identifier
    -- from an initial call to @StartFaceSearch@.
    GetFaceSearch -> Text
jobId :: Prelude.Text
  }
  deriving (GetFaceSearch -> GetFaceSearch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFaceSearch -> GetFaceSearch -> Bool
$c/= :: GetFaceSearch -> GetFaceSearch -> Bool
== :: GetFaceSearch -> GetFaceSearch -> Bool
$c== :: GetFaceSearch -> GetFaceSearch -> Bool
Prelude.Eq, ReadPrec [GetFaceSearch]
ReadPrec GetFaceSearch
Int -> ReadS GetFaceSearch
ReadS [GetFaceSearch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFaceSearch]
$creadListPrec :: ReadPrec [GetFaceSearch]
readPrec :: ReadPrec GetFaceSearch
$creadPrec :: ReadPrec GetFaceSearch
readList :: ReadS [GetFaceSearch]
$creadList :: ReadS [GetFaceSearch]
readsPrec :: Int -> ReadS GetFaceSearch
$creadsPrec :: Int -> ReadS GetFaceSearch
Prelude.Read, Int -> GetFaceSearch -> ShowS
[GetFaceSearch] -> ShowS
GetFaceSearch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFaceSearch] -> ShowS
$cshowList :: [GetFaceSearch] -> ShowS
show :: GetFaceSearch -> String
$cshow :: GetFaceSearch -> String
showsPrec :: Int -> GetFaceSearch -> ShowS
$cshowsPrec :: Int -> GetFaceSearch -> ShowS
Prelude.Show, forall x. Rep GetFaceSearch x -> GetFaceSearch
forall x. GetFaceSearch -> Rep GetFaceSearch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFaceSearch x -> GetFaceSearch
$cfrom :: forall x. GetFaceSearch -> Rep GetFaceSearch x
Prelude.Generic)

-- |
-- Create a value of 'GetFaceSearch' 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', 'getFaceSearch_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', 'getFaceSearch_nextToken' - If the previous response was incomplete (because there is more search
-- results to retrieve), Amazon Rekognition Video returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of search results.
--
-- 'sortBy', 'getFaceSearch_sortBy' - Sort to use for grouping faces in the response. Use @TIMESTAMP@ to group
-- faces by the time that they are recognized. Use @INDEX@ to sort by
-- recognized faces.
--
-- 'jobId', 'getFaceSearch_jobId' - The job identifer for the search request. You get the job identifier
-- from an initial call to @StartFaceSearch@.
newGetFaceSearch ::
  -- | 'jobId'
  Prelude.Text ->
  GetFaceSearch
newGetFaceSearch :: Text -> GetFaceSearch
newGetFaceSearch Text
pJobId_ =
  GetFaceSearch'
    { $sel:maxResults:GetFaceSearch' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetFaceSearch' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:GetFaceSearch' :: Maybe FaceSearchSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:GetFaceSearch' :: 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.
getFaceSearch_maxResults :: Lens.Lens' GetFaceSearch (Prelude.Maybe Prelude.Natural)
getFaceSearch_maxResults :: Lens' GetFaceSearch (Maybe Natural)
getFaceSearch_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearch' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetFaceSearch' :: GetFaceSearch -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetFaceSearch
s@GetFaceSearch' {} Maybe Natural
a -> GetFaceSearch
s {$sel:maxResults:GetFaceSearch' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetFaceSearch)

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

-- | Sort to use for grouping faces in the response. Use @TIMESTAMP@ to group
-- faces by the time that they are recognized. Use @INDEX@ to sort by
-- recognized faces.
getFaceSearch_sortBy :: Lens.Lens' GetFaceSearch (Prelude.Maybe FaceSearchSortBy)
getFaceSearch_sortBy :: Lens' GetFaceSearch (Maybe FaceSearchSortBy)
getFaceSearch_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearch' {Maybe FaceSearchSortBy
sortBy :: Maybe FaceSearchSortBy
$sel:sortBy:GetFaceSearch' :: GetFaceSearch -> Maybe FaceSearchSortBy
sortBy} -> Maybe FaceSearchSortBy
sortBy) (\s :: GetFaceSearch
s@GetFaceSearch' {} Maybe FaceSearchSortBy
a -> GetFaceSearch
s {$sel:sortBy:GetFaceSearch' :: Maybe FaceSearchSortBy
sortBy = Maybe FaceSearchSortBy
a} :: GetFaceSearch)

-- | The job identifer for the search request. You get the job identifier
-- from an initial call to @StartFaceSearch@.
getFaceSearch_jobId :: Lens.Lens' GetFaceSearch Prelude.Text
getFaceSearch_jobId :: Lens' GetFaceSearch Text
getFaceSearch_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearch' {Text
jobId :: Text
$sel:jobId:GetFaceSearch' :: GetFaceSearch -> Text
jobId} -> Text
jobId) (\s :: GetFaceSearch
s@GetFaceSearch' {} Text
a -> GetFaceSearch
s {$sel:jobId:GetFaceSearch' :: Text
jobId = Text
a} :: GetFaceSearch)

instance Core.AWSRequest GetFaceSearch where
  type
    AWSResponse GetFaceSearch =
      GetFaceSearchResponse
  request :: (Service -> Service) -> GetFaceSearch -> Request GetFaceSearch
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 GetFaceSearch
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFaceSearch)))
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 VideoJobStatus
-> Maybe Text
-> Maybe [PersonMatch]
-> Maybe Text
-> Maybe VideoMetadata
-> Int
-> GetFaceSearchResponse
GetFaceSearchResponse'
            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
"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
"Persons" 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
"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 GetFaceSearch where
  hashWithSalt :: Int -> GetFaceSearch -> Int
hashWithSalt Int
_salt GetFaceSearch' {Maybe Natural
Maybe Text
Maybe FaceSearchSortBy
Text
jobId :: Text
sortBy :: Maybe FaceSearchSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetFaceSearch' :: GetFaceSearch -> Text
$sel:sortBy:GetFaceSearch' :: GetFaceSearch -> Maybe FaceSearchSortBy
$sel:nextToken:GetFaceSearch' :: GetFaceSearch -> Maybe Text
$sel:maxResults:GetFaceSearch' :: GetFaceSearch -> 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 FaceSearchSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData GetFaceSearch where
  rnf :: GetFaceSearch -> ()
rnf GetFaceSearch' {Maybe Natural
Maybe Text
Maybe FaceSearchSortBy
Text
jobId :: Text
sortBy :: Maybe FaceSearchSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetFaceSearch' :: GetFaceSearch -> Text
$sel:sortBy:GetFaceSearch' :: GetFaceSearch -> Maybe FaceSearchSortBy
$sel:nextToken:GetFaceSearch' :: GetFaceSearch -> Maybe Text
$sel:maxResults:GetFaceSearch' :: GetFaceSearch -> 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 FaceSearchSortBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

instance Data.ToHeaders GetFaceSearch where
  toHeaders :: GetFaceSearch -> 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.GetFaceSearch" ::
                          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 GetFaceSearch where
  toJSON :: GetFaceSearch -> Value
toJSON GetFaceSearch' {Maybe Natural
Maybe Text
Maybe FaceSearchSortBy
Text
jobId :: Text
sortBy :: Maybe FaceSearchSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetFaceSearch' :: GetFaceSearch -> Text
$sel:sortBy:GetFaceSearch' :: GetFaceSearch -> Maybe FaceSearchSortBy
$sel:nextToken:GetFaceSearch' :: GetFaceSearch -> Maybe Text
$sel:maxResults:GetFaceSearch' :: GetFaceSearch -> 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 FaceSearchSortBy
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 GetFaceSearch where
  toPath :: GetFaceSearch -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetFaceSearchResponse' smart constructor.
data GetFaceSearchResponse = GetFaceSearchResponse'
  { -- | The current status of the face search job.
    GetFaceSearchResponse -> 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 search results.
    GetFaceSearchResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of persons, PersonMatch, in the video whose face(s) match the
    -- face(s) in an Amazon Rekognition collection. It also includes time
    -- information for when persons are matched in the video. You specify the
    -- input collection in an initial call to @StartFaceSearch@. Each @Persons@
    -- element includes a time the person was matched, face match details
    -- (@FaceMatches@) for matching faces in the collection, and person
    -- information (@Person@) for the matched person.
    GetFaceSearchResponse -> Maybe [PersonMatch]
persons :: Prelude.Maybe [PersonMatch],
    -- | If the job fails, @StatusMessage@ provides a descriptive error message.
    GetFaceSearchResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | Information about a video that Amazon Rekognition analyzed.
    -- @Videometadata@ is returned in every page of paginated responses from a
    -- Amazon Rekognition Video operation.
    GetFaceSearchResponse -> Maybe VideoMetadata
videoMetadata :: Prelude.Maybe VideoMetadata,
    -- | The response's http status code.
    GetFaceSearchResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFaceSearchResponse -> GetFaceSearchResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFaceSearchResponse -> GetFaceSearchResponse -> Bool
$c/= :: GetFaceSearchResponse -> GetFaceSearchResponse -> Bool
== :: GetFaceSearchResponse -> GetFaceSearchResponse -> Bool
$c== :: GetFaceSearchResponse -> GetFaceSearchResponse -> Bool
Prelude.Eq, ReadPrec [GetFaceSearchResponse]
ReadPrec GetFaceSearchResponse
Int -> ReadS GetFaceSearchResponse
ReadS [GetFaceSearchResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFaceSearchResponse]
$creadListPrec :: ReadPrec [GetFaceSearchResponse]
readPrec :: ReadPrec GetFaceSearchResponse
$creadPrec :: ReadPrec GetFaceSearchResponse
readList :: ReadS [GetFaceSearchResponse]
$creadList :: ReadS [GetFaceSearchResponse]
readsPrec :: Int -> ReadS GetFaceSearchResponse
$creadsPrec :: Int -> ReadS GetFaceSearchResponse
Prelude.Read, Int -> GetFaceSearchResponse -> ShowS
[GetFaceSearchResponse] -> ShowS
GetFaceSearchResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFaceSearchResponse] -> ShowS
$cshowList :: [GetFaceSearchResponse] -> ShowS
show :: GetFaceSearchResponse -> String
$cshow :: GetFaceSearchResponse -> String
showsPrec :: Int -> GetFaceSearchResponse -> ShowS
$cshowsPrec :: Int -> GetFaceSearchResponse -> ShowS
Prelude.Show, forall x. Rep GetFaceSearchResponse x -> GetFaceSearchResponse
forall x. GetFaceSearchResponse -> Rep GetFaceSearchResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFaceSearchResponse x -> GetFaceSearchResponse
$cfrom :: forall x. GetFaceSearchResponse -> Rep GetFaceSearchResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFaceSearchResponse' 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:
--
-- 'jobStatus', 'getFaceSearchResponse_jobStatus' - The current status of the face search job.
--
-- 'nextToken', 'getFaceSearchResponse_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 search results.
--
-- 'persons', 'getFaceSearchResponse_persons' - An array of persons, PersonMatch, in the video whose face(s) match the
-- face(s) in an Amazon Rekognition collection. It also includes time
-- information for when persons are matched in the video. You specify the
-- input collection in an initial call to @StartFaceSearch@. Each @Persons@
-- element includes a time the person was matched, face match details
-- (@FaceMatches@) for matching faces in the collection, and person
-- information (@Person@) for the matched person.
--
-- 'statusMessage', 'getFaceSearchResponse_statusMessage' - If the job fails, @StatusMessage@ provides a descriptive error message.
--
-- 'videoMetadata', 'getFaceSearchResponse_videoMetadata' - Information about a video that Amazon Rekognition analyzed.
-- @Videometadata@ is returned in every page of paginated responses from a
-- Amazon Rekognition Video operation.
--
-- 'httpStatus', 'getFaceSearchResponse_httpStatus' - The response's http status code.
newGetFaceSearchResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFaceSearchResponse
newGetFaceSearchResponse :: Int -> GetFaceSearchResponse
newGetFaceSearchResponse Int
pHttpStatus_ =
  GetFaceSearchResponse'
    { $sel:jobStatus:GetFaceSearchResponse' :: Maybe VideoJobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetFaceSearchResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:persons:GetFaceSearchResponse' :: Maybe [PersonMatch]
persons = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetFaceSearchResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:videoMetadata:GetFaceSearchResponse' :: Maybe VideoMetadata
videoMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFaceSearchResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The current status of the face search job.
getFaceSearchResponse_jobStatus :: Lens.Lens' GetFaceSearchResponse (Prelude.Maybe VideoJobStatus)
getFaceSearchResponse_jobStatus :: Lens' GetFaceSearchResponse (Maybe VideoJobStatus)
getFaceSearchResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearchResponse' {Maybe VideoJobStatus
jobStatus :: Maybe VideoJobStatus
$sel:jobStatus:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe VideoJobStatus
jobStatus} -> Maybe VideoJobStatus
jobStatus) (\s :: GetFaceSearchResponse
s@GetFaceSearchResponse' {} Maybe VideoJobStatus
a -> GetFaceSearchResponse
s {$sel:jobStatus:GetFaceSearchResponse' :: Maybe VideoJobStatus
jobStatus = Maybe VideoJobStatus
a} :: GetFaceSearchResponse)

-- | 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 search results.
getFaceSearchResponse_nextToken :: Lens.Lens' GetFaceSearchResponse (Prelude.Maybe Prelude.Text)
getFaceSearchResponse_nextToken :: Lens' GetFaceSearchResponse (Maybe Text)
getFaceSearchResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearchResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetFaceSearchResponse
s@GetFaceSearchResponse' {} Maybe Text
a -> GetFaceSearchResponse
s {$sel:nextToken:GetFaceSearchResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetFaceSearchResponse)

-- | An array of persons, PersonMatch, in the video whose face(s) match the
-- face(s) in an Amazon Rekognition collection. It also includes time
-- information for when persons are matched in the video. You specify the
-- input collection in an initial call to @StartFaceSearch@. Each @Persons@
-- element includes a time the person was matched, face match details
-- (@FaceMatches@) for matching faces in the collection, and person
-- information (@Person@) for the matched person.
getFaceSearchResponse_persons :: Lens.Lens' GetFaceSearchResponse (Prelude.Maybe [PersonMatch])
getFaceSearchResponse_persons :: Lens' GetFaceSearchResponse (Maybe [PersonMatch])
getFaceSearchResponse_persons = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFaceSearchResponse' {Maybe [PersonMatch]
persons :: Maybe [PersonMatch]
$sel:persons:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe [PersonMatch]
persons} -> Maybe [PersonMatch]
persons) (\s :: GetFaceSearchResponse
s@GetFaceSearchResponse' {} Maybe [PersonMatch]
a -> GetFaceSearchResponse
s {$sel:persons:GetFaceSearchResponse' :: Maybe [PersonMatch]
persons = Maybe [PersonMatch]
a} :: GetFaceSearchResponse) 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

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

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

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

instance Prelude.NFData GetFaceSearchResponse where
  rnf :: GetFaceSearchResponse -> ()
rnf GetFaceSearchResponse' {Int
Maybe [PersonMatch]
Maybe Text
Maybe VideoJobStatus
Maybe VideoMetadata
httpStatus :: Int
videoMetadata :: Maybe VideoMetadata
statusMessage :: Maybe Text
persons :: Maybe [PersonMatch]
nextToken :: Maybe Text
jobStatus :: Maybe VideoJobStatus
$sel:httpStatus:GetFaceSearchResponse' :: GetFaceSearchResponse -> Int
$sel:videoMetadata:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe VideoMetadata
$sel:statusMessage:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe Text
$sel:persons:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe [PersonMatch]
$sel:nextToken:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe Text
$sel:jobStatus:GetFaceSearchResponse' :: GetFaceSearchResponse -> Maybe VideoJobStatus
..} =
    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 [PersonMatch]
persons
      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