{-# 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.GetSegmentDetection
-- 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 segment detection results of a Amazon Rekognition Video
-- analysis started by StartSegmentDetection.
--
-- Segment detection with Amazon Rekognition Video is an asynchronous
-- operation. You start segment detection by calling StartSegmentDetection
-- which returns a job identifier (@JobId@). When the segment detection
-- operation finishes, Amazon Rekognition publishes a completion status to
-- the Amazon Simple Notification Service topic registered in the initial
-- call to @StartSegmentDetection@. To get the results of the segment
-- detection operation, first check that the status value published to the
-- Amazon SNS topic is @SUCCEEDED@. if so, call @GetSegmentDetection@ and
-- pass the job identifier (@JobId@) from the initial call of
-- @StartSegmentDetection@.
--
-- @GetSegmentDetection@ returns detected segments in an array (@Segments@)
-- of SegmentDetection objects. @Segments@ is sorted by the segment types
-- specified in the @SegmentTypes@ input parameter of
-- @StartSegmentDetection@. Each element of the array includes the detected
-- segment, the precentage confidence in the acuracy of the detected
-- segment, the type of the segment, and the frame in which the segment was
-- detected.
--
-- Use @SelectedSegmentTypes@ to find out the type of segment detection
-- requested in the call to @StartSegmentDetection@.
--
-- Use the @MaxResults@ parameter to limit the number of segment detections
-- returned. If there are more results than specified in @MaxResults@, the
-- value of @NextToken@ in the operation response contains a pagination
-- token for getting the next set of results. To get the next page of
-- results, call @GetSegmentDetection@ and populate the @NextToken@ request
-- parameter with the token value returned from the previous call to
-- @GetSegmentDetection@.
--
-- For more information, see Detecting video segments in stored video in
-- the Amazon Rekognition Developer Guide.
module Amazonka.Rekognition.GetSegmentDetection
  ( -- * Creating a Request
    GetSegmentDetection (..),
    newGetSegmentDetection,

    -- * Request Lenses
    getSegmentDetection_maxResults,
    getSegmentDetection_nextToken,
    getSegmentDetection_jobId,

    -- * Destructuring the Response
    GetSegmentDetectionResponse (..),
    newGetSegmentDetectionResponse,

    -- * Response Lenses
    getSegmentDetectionResponse_audioMetadata,
    getSegmentDetectionResponse_jobStatus,
    getSegmentDetectionResponse_nextToken,
    getSegmentDetectionResponse_segments,
    getSegmentDetectionResponse_selectedSegmentTypes,
    getSegmentDetectionResponse_statusMessage,
    getSegmentDetectionResponse_videoMetadata,
    getSegmentDetectionResponse_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:/ 'newGetSegmentDetection' smart constructor.
data GetSegmentDetection = GetSegmentDetection'
  { -- | Maximum number of results to return per paginated call. The largest
    -- value you can specify is 1000.
    GetSegmentDetection -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | 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 text.
    GetSegmentDetection -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Job identifier for the text detection operation for which you want
    -- results returned. You get the job identifer from an initial call to
    -- @StartSegmentDetection@.
    GetSegmentDetection -> Text
jobId :: Prelude.Text
  }
  deriving (GetSegmentDetection -> GetSegmentDetection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSegmentDetection -> GetSegmentDetection -> Bool
$c/= :: GetSegmentDetection -> GetSegmentDetection -> Bool
== :: GetSegmentDetection -> GetSegmentDetection -> Bool
$c== :: GetSegmentDetection -> GetSegmentDetection -> Bool
Prelude.Eq, ReadPrec [GetSegmentDetection]
ReadPrec GetSegmentDetection
Int -> ReadS GetSegmentDetection
ReadS [GetSegmentDetection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSegmentDetection]
$creadListPrec :: ReadPrec [GetSegmentDetection]
readPrec :: ReadPrec GetSegmentDetection
$creadPrec :: ReadPrec GetSegmentDetection
readList :: ReadS [GetSegmentDetection]
$creadList :: ReadS [GetSegmentDetection]
readsPrec :: Int -> ReadS GetSegmentDetection
$creadsPrec :: Int -> ReadS GetSegmentDetection
Prelude.Read, Int -> GetSegmentDetection -> ShowS
[GetSegmentDetection] -> ShowS
GetSegmentDetection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSegmentDetection] -> ShowS
$cshowList :: [GetSegmentDetection] -> ShowS
show :: GetSegmentDetection -> String
$cshow :: GetSegmentDetection -> String
showsPrec :: Int -> GetSegmentDetection -> ShowS
$cshowsPrec :: Int -> GetSegmentDetection -> ShowS
Prelude.Show, forall x. Rep GetSegmentDetection x -> GetSegmentDetection
forall x. GetSegmentDetection -> Rep GetSegmentDetection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSegmentDetection x -> GetSegmentDetection
$cfrom :: forall x. GetSegmentDetection -> Rep GetSegmentDetection x
Prelude.Generic)

-- |
-- Create a value of 'GetSegmentDetection' 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', 'getSegmentDetection_maxResults' - Maximum number of results to return per paginated call. The largest
-- value you can specify is 1000.
--
-- 'nextToken', 'getSegmentDetection_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 text.
--
-- 'jobId', 'getSegmentDetection_jobId' - Job identifier for the text detection operation for which you want
-- results returned. You get the job identifer from an initial call to
-- @StartSegmentDetection@.
newGetSegmentDetection ::
  -- | 'jobId'
  Prelude.Text ->
  GetSegmentDetection
newGetSegmentDetection :: Text -> GetSegmentDetection
newGetSegmentDetection Text
pJobId_ =
  GetSegmentDetection'
    { $sel:maxResults:GetSegmentDetection' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetSegmentDetection' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:GetSegmentDetection' :: Text
jobId = Text
pJobId_
    }

-- | Maximum number of results to return per paginated call. The largest
-- value you can specify is 1000.
getSegmentDetection_maxResults :: Lens.Lens' GetSegmentDetection (Prelude.Maybe Prelude.Natural)
getSegmentDetection_maxResults :: Lens' GetSegmentDetection (Maybe Natural)
getSegmentDetection_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetection' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetSegmentDetection' :: GetSegmentDetection -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetSegmentDetection
s@GetSegmentDetection' {} Maybe Natural
a -> GetSegmentDetection
s {$sel:maxResults:GetSegmentDetection' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetSegmentDetection)

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

-- | Job identifier for the text detection operation for which you want
-- results returned. You get the job identifer from an initial call to
-- @StartSegmentDetection@.
getSegmentDetection_jobId :: Lens.Lens' GetSegmentDetection Prelude.Text
getSegmentDetection_jobId :: Lens' GetSegmentDetection Text
getSegmentDetection_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetection' {Text
jobId :: Text
$sel:jobId:GetSegmentDetection' :: GetSegmentDetection -> Text
jobId} -> Text
jobId) (\s :: GetSegmentDetection
s@GetSegmentDetection' {} Text
a -> GetSegmentDetection
s {$sel:jobId:GetSegmentDetection' :: Text
jobId = Text
a} :: GetSegmentDetection)

instance Core.AWSRequest GetSegmentDetection where
  type
    AWSResponse GetSegmentDetection =
      GetSegmentDetectionResponse
  request :: (Service -> Service)
-> GetSegmentDetection -> Request GetSegmentDetection
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 GetSegmentDetection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSegmentDetection)))
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 [AudioMetadata]
-> Maybe VideoJobStatus
-> Maybe Text
-> Maybe [SegmentDetection]
-> Maybe [SegmentTypeInfo]
-> Maybe Text
-> Maybe [VideoMetadata]
-> Int
-> GetSegmentDetectionResponse
GetSegmentDetectionResponse'
            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
"AudioMetadata" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"JobStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Segments" 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
"SelectedSegmentTypes"
                            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. 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetSegmentDetection where
  hashWithSalt :: Int -> GetSegmentDetection -> Int
hashWithSalt Int
_salt GetSegmentDetection' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetSegmentDetection' :: GetSegmentDetection -> Text
$sel:nextToken:GetSegmentDetection' :: GetSegmentDetection -> Maybe Text
$sel:maxResults:GetSegmentDetection' :: GetSegmentDetection -> 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` Text
jobId

instance Prelude.NFData GetSegmentDetection where
  rnf :: GetSegmentDetection -> ()
rnf GetSegmentDetection' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetSegmentDetection' :: GetSegmentDetection -> Text
$sel:nextToken:GetSegmentDetection' :: GetSegmentDetection -> Maybe Text
$sel:maxResults:GetSegmentDetection' :: GetSegmentDetection -> 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 Text
jobId

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

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

-- | /See:/ 'newGetSegmentDetectionResponse' smart constructor.
data GetSegmentDetectionResponse = GetSegmentDetectionResponse'
  { -- | An array of objects. There can be multiple audio streams. Each
    -- @AudioMetadata@ object contains metadata for a single audio stream.
    -- Audio information in an @AudioMetadata@ objects includes the audio
    -- codec, the number of audio channels, the duration of the audio stream,
    -- and the sample rate. Audio metadata is returned in each page of
    -- information returned by @GetSegmentDetection@.
    GetSegmentDetectionResponse -> Maybe [AudioMetadata]
audioMetadata :: Prelude.Maybe [AudioMetadata],
    -- | Current status of the segment detection job.
    GetSegmentDetectionResponse -> Maybe VideoJobStatus
jobStatus :: Prelude.Maybe VideoJobStatus,
    -- | If the previous response was incomplete (because there are more labels
    -- to retrieve), Amazon Rekognition Video returns a pagination token in the
    -- response. You can use this pagination token to retrieve the next set of
    -- text.
    GetSegmentDetectionResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of segments detected in a video. The array is sorted by the
    -- segment types (TECHNICAL_CUE or SHOT) specified in the @SegmentTypes@
    -- input parameter of @StartSegmentDetection@. Within each segment type the
    -- array is sorted by timestamp values.
    GetSegmentDetectionResponse -> Maybe [SegmentDetection]
segments :: Prelude.Maybe [SegmentDetection],
    -- | An array containing the segment types requested in the call to
    -- @StartSegmentDetection@.
    GetSegmentDetectionResponse -> Maybe [SegmentTypeInfo]
selectedSegmentTypes :: Prelude.Maybe [SegmentTypeInfo],
    -- | If the job fails, @StatusMessage@ provides a descriptive error message.
    GetSegmentDetectionResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | Currently, Amazon Rekognition Video returns a single object in the
    -- @VideoMetadata@ array. The object contains information about the video
    -- stream in the input file that Amazon Rekognition Video chose to analyze.
    -- The @VideoMetadata@ object includes the video codec, video format and
    -- other information. Video metadata is returned in each page of
    -- information returned by @GetSegmentDetection@.
    GetSegmentDetectionResponse -> Maybe [VideoMetadata]
videoMetadata :: Prelude.Maybe [VideoMetadata],
    -- | The response's http status code.
    GetSegmentDetectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSegmentDetectionResponse -> GetSegmentDetectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSegmentDetectionResponse -> GetSegmentDetectionResponse -> Bool
$c/= :: GetSegmentDetectionResponse -> GetSegmentDetectionResponse -> Bool
== :: GetSegmentDetectionResponse -> GetSegmentDetectionResponse -> Bool
$c== :: GetSegmentDetectionResponse -> GetSegmentDetectionResponse -> Bool
Prelude.Eq, ReadPrec [GetSegmentDetectionResponse]
ReadPrec GetSegmentDetectionResponse
Int -> ReadS GetSegmentDetectionResponse
ReadS [GetSegmentDetectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSegmentDetectionResponse]
$creadListPrec :: ReadPrec [GetSegmentDetectionResponse]
readPrec :: ReadPrec GetSegmentDetectionResponse
$creadPrec :: ReadPrec GetSegmentDetectionResponse
readList :: ReadS [GetSegmentDetectionResponse]
$creadList :: ReadS [GetSegmentDetectionResponse]
readsPrec :: Int -> ReadS GetSegmentDetectionResponse
$creadsPrec :: Int -> ReadS GetSegmentDetectionResponse
Prelude.Read, Int -> GetSegmentDetectionResponse -> ShowS
[GetSegmentDetectionResponse] -> ShowS
GetSegmentDetectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSegmentDetectionResponse] -> ShowS
$cshowList :: [GetSegmentDetectionResponse] -> ShowS
show :: GetSegmentDetectionResponse -> String
$cshow :: GetSegmentDetectionResponse -> String
showsPrec :: Int -> GetSegmentDetectionResponse -> ShowS
$cshowsPrec :: Int -> GetSegmentDetectionResponse -> ShowS
Prelude.Show, forall x.
Rep GetSegmentDetectionResponse x -> GetSegmentDetectionResponse
forall x.
GetSegmentDetectionResponse -> Rep GetSegmentDetectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSegmentDetectionResponse x -> GetSegmentDetectionResponse
$cfrom :: forall x.
GetSegmentDetectionResponse -> Rep GetSegmentDetectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSegmentDetectionResponse' 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:
--
-- 'audioMetadata', 'getSegmentDetectionResponse_audioMetadata' - An array of objects. There can be multiple audio streams. Each
-- @AudioMetadata@ object contains metadata for a single audio stream.
-- Audio information in an @AudioMetadata@ objects includes the audio
-- codec, the number of audio channels, the duration of the audio stream,
-- and the sample rate. Audio metadata is returned in each page of
-- information returned by @GetSegmentDetection@.
--
-- 'jobStatus', 'getSegmentDetectionResponse_jobStatus' - Current status of the segment detection job.
--
-- 'nextToken', 'getSegmentDetectionResponse_nextToken' - If the previous response was incomplete (because there are more labels
-- to retrieve), Amazon Rekognition Video returns a pagination token in the
-- response. You can use this pagination token to retrieve the next set of
-- text.
--
-- 'segments', 'getSegmentDetectionResponse_segments' - An array of segments detected in a video. The array is sorted by the
-- segment types (TECHNICAL_CUE or SHOT) specified in the @SegmentTypes@
-- input parameter of @StartSegmentDetection@. Within each segment type the
-- array is sorted by timestamp values.
--
-- 'selectedSegmentTypes', 'getSegmentDetectionResponse_selectedSegmentTypes' - An array containing the segment types requested in the call to
-- @StartSegmentDetection@.
--
-- 'statusMessage', 'getSegmentDetectionResponse_statusMessage' - If the job fails, @StatusMessage@ provides a descriptive error message.
--
-- 'videoMetadata', 'getSegmentDetectionResponse_videoMetadata' - Currently, Amazon Rekognition Video returns a single object in the
-- @VideoMetadata@ array. The object contains information about the video
-- stream in the input file that Amazon Rekognition Video chose to analyze.
-- The @VideoMetadata@ object includes the video codec, video format and
-- other information. Video metadata is returned in each page of
-- information returned by @GetSegmentDetection@.
--
-- 'httpStatus', 'getSegmentDetectionResponse_httpStatus' - The response's http status code.
newGetSegmentDetectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSegmentDetectionResponse
newGetSegmentDetectionResponse :: Int -> GetSegmentDetectionResponse
newGetSegmentDetectionResponse Int
pHttpStatus_ =
  GetSegmentDetectionResponse'
    { $sel:audioMetadata:GetSegmentDetectionResponse' :: Maybe [AudioMetadata]
audioMetadata =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobStatus:GetSegmentDetectionResponse' :: Maybe VideoJobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetSegmentDetectionResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:segments:GetSegmentDetectionResponse' :: Maybe [SegmentDetection]
segments = forall a. Maybe a
Prelude.Nothing,
      $sel:selectedSegmentTypes:GetSegmentDetectionResponse' :: Maybe [SegmentTypeInfo]
selectedSegmentTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetSegmentDetectionResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:videoMetadata:GetSegmentDetectionResponse' :: Maybe [VideoMetadata]
videoMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSegmentDetectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects. There can be multiple audio streams. Each
-- @AudioMetadata@ object contains metadata for a single audio stream.
-- Audio information in an @AudioMetadata@ objects includes the audio
-- codec, the number of audio channels, the duration of the audio stream,
-- and the sample rate. Audio metadata is returned in each page of
-- information returned by @GetSegmentDetection@.
getSegmentDetectionResponse_audioMetadata :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe [AudioMetadata])
getSegmentDetectionResponse_audioMetadata :: Lens' GetSegmentDetectionResponse (Maybe [AudioMetadata])
getSegmentDetectionResponse_audioMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe [AudioMetadata]
audioMetadata :: Maybe [AudioMetadata]
$sel:audioMetadata:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [AudioMetadata]
audioMetadata} -> Maybe [AudioMetadata]
audioMetadata) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe [AudioMetadata]
a -> GetSegmentDetectionResponse
s {$sel:audioMetadata:GetSegmentDetectionResponse' :: Maybe [AudioMetadata]
audioMetadata = Maybe [AudioMetadata]
a} :: GetSegmentDetectionResponse) 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

-- | Current status of the segment detection job.
getSegmentDetectionResponse_jobStatus :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe VideoJobStatus)
getSegmentDetectionResponse_jobStatus :: Lens' GetSegmentDetectionResponse (Maybe VideoJobStatus)
getSegmentDetectionResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe VideoJobStatus
jobStatus :: Maybe VideoJobStatus
$sel:jobStatus:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe VideoJobStatus
jobStatus} -> Maybe VideoJobStatus
jobStatus) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe VideoJobStatus
a -> GetSegmentDetectionResponse
s {$sel:jobStatus:GetSegmentDetectionResponse' :: Maybe VideoJobStatus
jobStatus = Maybe VideoJobStatus
a} :: GetSegmentDetectionResponse)

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

-- | An array of segments detected in a video. The array is sorted by the
-- segment types (TECHNICAL_CUE or SHOT) specified in the @SegmentTypes@
-- input parameter of @StartSegmentDetection@. Within each segment type the
-- array is sorted by timestamp values.
getSegmentDetectionResponse_segments :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe [SegmentDetection])
getSegmentDetectionResponse_segments :: Lens' GetSegmentDetectionResponse (Maybe [SegmentDetection])
getSegmentDetectionResponse_segments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe [SegmentDetection]
segments :: Maybe [SegmentDetection]
$sel:segments:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [SegmentDetection]
segments} -> Maybe [SegmentDetection]
segments) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe [SegmentDetection]
a -> GetSegmentDetectionResponse
s {$sel:segments:GetSegmentDetectionResponse' :: Maybe [SegmentDetection]
segments = Maybe [SegmentDetection]
a} :: GetSegmentDetectionResponse) 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

-- | An array containing the segment types requested in the call to
-- @StartSegmentDetection@.
getSegmentDetectionResponse_selectedSegmentTypes :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe [SegmentTypeInfo])
getSegmentDetectionResponse_selectedSegmentTypes :: Lens' GetSegmentDetectionResponse (Maybe [SegmentTypeInfo])
getSegmentDetectionResponse_selectedSegmentTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe [SegmentTypeInfo]
selectedSegmentTypes :: Maybe [SegmentTypeInfo]
$sel:selectedSegmentTypes:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [SegmentTypeInfo]
selectedSegmentTypes} -> Maybe [SegmentTypeInfo]
selectedSegmentTypes) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe [SegmentTypeInfo]
a -> GetSegmentDetectionResponse
s {$sel:selectedSegmentTypes:GetSegmentDetectionResponse' :: Maybe [SegmentTypeInfo]
selectedSegmentTypes = Maybe [SegmentTypeInfo]
a} :: GetSegmentDetectionResponse) 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.
getSegmentDetectionResponse_statusMessage :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe Prelude.Text)
getSegmentDetectionResponse_statusMessage :: Lens' GetSegmentDetectionResponse (Maybe Text)
getSegmentDetectionResponse_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe Text
a -> GetSegmentDetectionResponse
s {$sel:statusMessage:GetSegmentDetectionResponse' :: Maybe Text
statusMessage = Maybe Text
a} :: GetSegmentDetectionResponse)

-- | Currently, Amazon Rekognition Video returns a single object in the
-- @VideoMetadata@ array. The object contains information about the video
-- stream in the input file that Amazon Rekognition Video chose to analyze.
-- The @VideoMetadata@ object includes the video codec, video format and
-- other information. Video metadata is returned in each page of
-- information returned by @GetSegmentDetection@.
getSegmentDetectionResponse_videoMetadata :: Lens.Lens' GetSegmentDetectionResponse (Prelude.Maybe [VideoMetadata])
getSegmentDetectionResponse_videoMetadata :: Lens' GetSegmentDetectionResponse (Maybe [VideoMetadata])
getSegmentDetectionResponse_videoMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentDetectionResponse' {Maybe [VideoMetadata]
videoMetadata :: Maybe [VideoMetadata]
$sel:videoMetadata:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [VideoMetadata]
videoMetadata} -> Maybe [VideoMetadata]
videoMetadata) (\s :: GetSegmentDetectionResponse
s@GetSegmentDetectionResponse' {} Maybe [VideoMetadata]
a -> GetSegmentDetectionResponse
s {$sel:videoMetadata:GetSegmentDetectionResponse' :: Maybe [VideoMetadata]
videoMetadata = Maybe [VideoMetadata]
a} :: GetSegmentDetectionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetSegmentDetectionResponse where
  rnf :: GetSegmentDetectionResponse -> ()
rnf GetSegmentDetectionResponse' {Int
Maybe [AudioMetadata]
Maybe [SegmentTypeInfo]
Maybe [SegmentDetection]
Maybe [VideoMetadata]
Maybe Text
Maybe VideoJobStatus
httpStatus :: Int
videoMetadata :: Maybe [VideoMetadata]
statusMessage :: Maybe Text
selectedSegmentTypes :: Maybe [SegmentTypeInfo]
segments :: Maybe [SegmentDetection]
nextToken :: Maybe Text
jobStatus :: Maybe VideoJobStatus
audioMetadata :: Maybe [AudioMetadata]
$sel:httpStatus:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Int
$sel:videoMetadata:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [VideoMetadata]
$sel:statusMessage:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe Text
$sel:selectedSegmentTypes:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [SegmentTypeInfo]
$sel:segments:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [SegmentDetection]
$sel:nextToken:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe Text
$sel:jobStatus:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe VideoJobStatus
$sel:audioMetadata:GetSegmentDetectionResponse' :: GetSegmentDetectionResponse -> Maybe [AudioMetadata]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AudioMetadata]
audioMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VideoJobStatus
jobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SegmentDetection]
segments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SegmentTypeInfo]
selectedSegmentTypes
      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