{-# 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.StartSegmentDetection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts asynchronous detection of segment detection in a stored video.
--
-- Amazon Rekognition Video can detect segments in a video stored in an
-- Amazon S3 bucket. Use Video to specify the bucket name and the filename
-- of the video. @StartSegmentDetection@ returns a job identifier (@JobId@)
-- which you use to get the results of the operation. When segment
-- detection is finished, Amazon Rekognition Video publishes a completion
-- status to the Amazon Simple Notification Service topic that you specify
-- in @NotificationChannel@.
--
-- You can use the @Filters@ (StartSegmentDetectionFilters) input parameter
-- to specify the minimum detection confidence returned in the response.
-- Within @Filters@, use @ShotFilter@ (StartShotDetectionFilter) to filter
-- detected shots. Use @TechnicalCueFilter@
-- (StartTechnicalCueDetectionFilter) to filter technical cues.
--
-- 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 to @StartSegmentDetection@.
--
-- For more information, see Detecting video segments in stored video in
-- the Amazon Rekognition Developer Guide.
module Amazonka.Rekognition.StartSegmentDetection
  ( -- * Creating a Request
    StartSegmentDetection (..),
    newStartSegmentDetection,

    -- * Request Lenses
    startSegmentDetection_clientRequestToken,
    startSegmentDetection_filters,
    startSegmentDetection_jobTag,
    startSegmentDetection_notificationChannel,
    startSegmentDetection_video,
    startSegmentDetection_segmentTypes,

    -- * Destructuring the Response
    StartSegmentDetectionResponse (..),
    newStartSegmentDetectionResponse,

    -- * Response Lenses
    startSegmentDetectionResponse_jobId,
    startSegmentDetectionResponse_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:/ 'newStartSegmentDetection' smart constructor.
data StartSegmentDetection = StartSegmentDetection'
  { -- | Idempotent token used to identify the start request. If you use the same
    -- token with multiple @StartSegmentDetection@ requests, the same @JobId@
    -- is returned. Use @ClientRequestToken@ to prevent the same job from being
    -- accidently started more than once.
    StartSegmentDetection -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | Filters for technical cue or shot detection.
    StartSegmentDetection -> Maybe StartSegmentDetectionFilters
filters :: Prelude.Maybe StartSegmentDetectionFilters,
    -- | 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.
    StartSegmentDetection -> 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 segment detection
    -- operation. Note that 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.
    StartSegmentDetection -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    StartSegmentDetection -> Video
video :: Video,
    -- | An array of segment types to detect in the video. Valid values are
    -- TECHNICAL_CUE and SHOT.
    StartSegmentDetection -> NonEmpty SegmentType
segmentTypes :: Prelude.NonEmpty SegmentType
  }
  deriving (StartSegmentDetection -> StartSegmentDetection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartSegmentDetection -> StartSegmentDetection -> Bool
$c/= :: StartSegmentDetection -> StartSegmentDetection -> Bool
== :: StartSegmentDetection -> StartSegmentDetection -> Bool
$c== :: StartSegmentDetection -> StartSegmentDetection -> Bool
Prelude.Eq, ReadPrec [StartSegmentDetection]
ReadPrec StartSegmentDetection
Int -> ReadS StartSegmentDetection
ReadS [StartSegmentDetection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartSegmentDetection]
$creadListPrec :: ReadPrec [StartSegmentDetection]
readPrec :: ReadPrec StartSegmentDetection
$creadPrec :: ReadPrec StartSegmentDetection
readList :: ReadS [StartSegmentDetection]
$creadList :: ReadS [StartSegmentDetection]
readsPrec :: Int -> ReadS StartSegmentDetection
$creadsPrec :: Int -> ReadS StartSegmentDetection
Prelude.Read, Int -> StartSegmentDetection -> ShowS
[StartSegmentDetection] -> ShowS
StartSegmentDetection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartSegmentDetection] -> ShowS
$cshowList :: [StartSegmentDetection] -> ShowS
show :: StartSegmentDetection -> String
$cshow :: StartSegmentDetection -> String
showsPrec :: Int -> StartSegmentDetection -> ShowS
$cshowsPrec :: Int -> StartSegmentDetection -> ShowS
Prelude.Show, forall x. Rep StartSegmentDetection x -> StartSegmentDetection
forall x. StartSegmentDetection -> Rep StartSegmentDetection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartSegmentDetection x -> StartSegmentDetection
$cfrom :: forall x. StartSegmentDetection -> Rep StartSegmentDetection x
Prelude.Generic)

-- |
-- Create a value of 'StartSegmentDetection' 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', 'startSegmentDetection_clientRequestToken' - Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartSegmentDetection@ requests, the same @JobId@
-- is returned. Use @ClientRequestToken@ to prevent the same job from being
-- accidently started more than once.
--
-- 'filters', 'startSegmentDetection_filters' - Filters for technical cue or shot detection.
--
-- 'jobTag', 'startSegmentDetection_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', 'startSegmentDetection_notificationChannel' - The ARN of the Amazon SNS topic to which you want Amazon Rekognition
-- Video to publish the completion status of the segment detection
-- operation. Note that 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', 'startSegmentDetection_video' - Undocumented member.
--
-- 'segmentTypes', 'startSegmentDetection_segmentTypes' - An array of segment types to detect in the video. Valid values are
-- TECHNICAL_CUE and SHOT.
newStartSegmentDetection ::
  -- | 'video'
  Video ->
  -- | 'segmentTypes'
  Prelude.NonEmpty SegmentType ->
  StartSegmentDetection
newStartSegmentDetection :: Video -> NonEmpty SegmentType -> StartSegmentDetection
newStartSegmentDetection Video
pVideo_ NonEmpty SegmentType
pSegmentTypes_ =
  StartSegmentDetection'
    { $sel:clientRequestToken:StartSegmentDetection' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:filters:StartSegmentDetection' :: Maybe StartSegmentDetectionFilters
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartSegmentDetection' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartSegmentDetection' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:video:StartSegmentDetection' :: Video
video = Video
pVideo_,
      $sel:segmentTypes:StartSegmentDetection' :: NonEmpty SegmentType
segmentTypes = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty SegmentType
pSegmentTypes_
    }

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

-- | Filters for technical cue or shot detection.
startSegmentDetection_filters :: Lens.Lens' StartSegmentDetection (Prelude.Maybe StartSegmentDetectionFilters)
startSegmentDetection_filters :: Lens' StartSegmentDetection (Maybe StartSegmentDetectionFilters)
startSegmentDetection_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartSegmentDetection' {Maybe StartSegmentDetectionFilters
filters :: Maybe StartSegmentDetectionFilters
$sel:filters:StartSegmentDetection' :: StartSegmentDetection -> Maybe StartSegmentDetectionFilters
filters} -> Maybe StartSegmentDetectionFilters
filters) (\s :: StartSegmentDetection
s@StartSegmentDetection' {} Maybe StartSegmentDetectionFilters
a -> StartSegmentDetection
s {$sel:filters:StartSegmentDetection' :: Maybe StartSegmentDetectionFilters
filters = Maybe StartSegmentDetectionFilters
a} :: StartSegmentDetection)

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

-- | The ARN of the Amazon SNS topic to which you want Amazon Rekognition
-- Video to publish the completion status of the segment detection
-- operation. Note that 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.
startSegmentDetection_notificationChannel :: Lens.Lens' StartSegmentDetection (Prelude.Maybe NotificationChannel)
startSegmentDetection_notificationChannel :: Lens' StartSegmentDetection (Maybe NotificationChannel)
startSegmentDetection_notificationChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartSegmentDetection' {Maybe NotificationChannel
notificationChannel :: Maybe NotificationChannel
$sel:notificationChannel:StartSegmentDetection' :: StartSegmentDetection -> Maybe NotificationChannel
notificationChannel} -> Maybe NotificationChannel
notificationChannel) (\s :: StartSegmentDetection
s@StartSegmentDetection' {} Maybe NotificationChannel
a -> StartSegmentDetection
s {$sel:notificationChannel:StartSegmentDetection' :: Maybe NotificationChannel
notificationChannel = Maybe NotificationChannel
a} :: StartSegmentDetection)

-- | Undocumented member.
startSegmentDetection_video :: Lens.Lens' StartSegmentDetection Video
startSegmentDetection_video :: Lens' StartSegmentDetection Video
startSegmentDetection_video = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartSegmentDetection' {Video
video :: Video
$sel:video:StartSegmentDetection' :: StartSegmentDetection -> Video
video} -> Video
video) (\s :: StartSegmentDetection
s@StartSegmentDetection' {} Video
a -> StartSegmentDetection
s {$sel:video:StartSegmentDetection' :: Video
video = Video
a} :: StartSegmentDetection)

-- | An array of segment types to detect in the video. Valid values are
-- TECHNICAL_CUE and SHOT.
startSegmentDetection_segmentTypes :: Lens.Lens' StartSegmentDetection (Prelude.NonEmpty SegmentType)
startSegmentDetection_segmentTypes :: Lens' StartSegmentDetection (NonEmpty SegmentType)
startSegmentDetection_segmentTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartSegmentDetection' {NonEmpty SegmentType
segmentTypes :: NonEmpty SegmentType
$sel:segmentTypes:StartSegmentDetection' :: StartSegmentDetection -> NonEmpty SegmentType
segmentTypes} -> NonEmpty SegmentType
segmentTypes) (\s :: StartSegmentDetection
s@StartSegmentDetection' {} NonEmpty SegmentType
a -> StartSegmentDetection
s {$sel:segmentTypes:StartSegmentDetection' :: NonEmpty SegmentType
segmentTypes = NonEmpty SegmentType
a} :: StartSegmentDetection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest StartSegmentDetection where
  type
    AWSResponse StartSegmentDetection =
      StartSegmentDetectionResponse
  request :: (Service -> Service)
-> StartSegmentDetection -> Request StartSegmentDetection
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 StartSegmentDetection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartSegmentDetection)))
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 -> StartSegmentDetectionResponse
StartSegmentDetectionResponse'
            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 StartSegmentDetection where
  hashWithSalt :: Int -> StartSegmentDetection -> Int
hashWithSalt Int
_salt StartSegmentDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartSegmentDetectionFilters
NonEmpty SegmentType
Video
segmentTypes :: NonEmpty SegmentType
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartSegmentDetectionFilters
clientRequestToken :: Maybe Text
$sel:segmentTypes:StartSegmentDetection' :: StartSegmentDetection -> NonEmpty SegmentType
$sel:video:StartSegmentDetection' :: StartSegmentDetection -> Video
$sel:notificationChannel:StartSegmentDetection' :: StartSegmentDetection -> Maybe NotificationChannel
$sel:jobTag:StartSegmentDetection' :: StartSegmentDetection -> Maybe Text
$sel:filters:StartSegmentDetection' :: StartSegmentDetection -> Maybe StartSegmentDetectionFilters
$sel:clientRequestToken:StartSegmentDetection' :: StartSegmentDetection -> 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 StartSegmentDetectionFilters
filters
      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` NonEmpty SegmentType
segmentTypes

instance Prelude.NFData StartSegmentDetection where
  rnf :: StartSegmentDetection -> ()
rnf StartSegmentDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartSegmentDetectionFilters
NonEmpty SegmentType
Video
segmentTypes :: NonEmpty SegmentType
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartSegmentDetectionFilters
clientRequestToken :: Maybe Text
$sel:segmentTypes:StartSegmentDetection' :: StartSegmentDetection -> NonEmpty SegmentType
$sel:video:StartSegmentDetection' :: StartSegmentDetection -> Video
$sel:notificationChannel:StartSegmentDetection' :: StartSegmentDetection -> Maybe NotificationChannel
$sel:jobTag:StartSegmentDetection' :: StartSegmentDetection -> Maybe Text
$sel:filters:StartSegmentDetection' :: StartSegmentDetection -> Maybe StartSegmentDetectionFilters
$sel:clientRequestToken:StartSegmentDetection' :: StartSegmentDetection -> 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 StartSegmentDetectionFilters
filters
      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 NonEmpty SegmentType
segmentTypes

instance Data.ToHeaders StartSegmentDetection where
  toHeaders :: StartSegmentDetection -> 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.StartSegmentDetection" ::
                          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 StartSegmentDetection where
  toJSON :: StartSegmentDetection -> Value
toJSON StartSegmentDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartSegmentDetectionFilters
NonEmpty SegmentType
Video
segmentTypes :: NonEmpty SegmentType
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartSegmentDetectionFilters
clientRequestToken :: Maybe Text
$sel:segmentTypes:StartSegmentDetection' :: StartSegmentDetection -> NonEmpty SegmentType
$sel:video:StartSegmentDetection' :: StartSegmentDetection -> Video
$sel:notificationChannel:StartSegmentDetection' :: StartSegmentDetection -> Maybe NotificationChannel
$sel:jobTag:StartSegmentDetection' :: StartSegmentDetection -> Maybe Text
$sel:filters:StartSegmentDetection' :: StartSegmentDetection -> Maybe StartSegmentDetectionFilters
$sel:clientRequestToken:StartSegmentDetection' :: StartSegmentDetection -> 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
"Filters" 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 StartSegmentDetectionFilters
filters,
            (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
"SegmentTypes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty SegmentType
segmentTypes)
          ]
      )

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

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

-- | /See:/ 'newStartSegmentDetectionResponse' smart constructor.
data StartSegmentDetectionResponse = StartSegmentDetectionResponse'
  { -- | Unique identifier for the segment detection job. The @JobId@ is returned
    -- from @StartSegmentDetection@.
    StartSegmentDetectionResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartSegmentDetectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartSegmentDetectionResponse
-> StartSegmentDetectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartSegmentDetectionResponse
-> StartSegmentDetectionResponse -> Bool
$c/= :: StartSegmentDetectionResponse
-> StartSegmentDetectionResponse -> Bool
== :: StartSegmentDetectionResponse
-> StartSegmentDetectionResponse -> Bool
$c== :: StartSegmentDetectionResponse
-> StartSegmentDetectionResponse -> Bool
Prelude.Eq, ReadPrec [StartSegmentDetectionResponse]
ReadPrec StartSegmentDetectionResponse
Int -> ReadS StartSegmentDetectionResponse
ReadS [StartSegmentDetectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartSegmentDetectionResponse]
$creadListPrec :: ReadPrec [StartSegmentDetectionResponse]
readPrec :: ReadPrec StartSegmentDetectionResponse
$creadPrec :: ReadPrec StartSegmentDetectionResponse
readList :: ReadS [StartSegmentDetectionResponse]
$creadList :: ReadS [StartSegmentDetectionResponse]
readsPrec :: Int -> ReadS StartSegmentDetectionResponse
$creadsPrec :: Int -> ReadS StartSegmentDetectionResponse
Prelude.Read, Int -> StartSegmentDetectionResponse -> ShowS
[StartSegmentDetectionResponse] -> ShowS
StartSegmentDetectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartSegmentDetectionResponse] -> ShowS
$cshowList :: [StartSegmentDetectionResponse] -> ShowS
show :: StartSegmentDetectionResponse -> String
$cshow :: StartSegmentDetectionResponse -> String
showsPrec :: Int -> StartSegmentDetectionResponse -> ShowS
$cshowsPrec :: Int -> StartSegmentDetectionResponse -> ShowS
Prelude.Show, forall x.
Rep StartSegmentDetectionResponse x
-> StartSegmentDetectionResponse
forall x.
StartSegmentDetectionResponse
-> Rep StartSegmentDetectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartSegmentDetectionResponse x
-> StartSegmentDetectionResponse
$cfrom :: forall x.
StartSegmentDetectionResponse
-> Rep StartSegmentDetectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartSegmentDetectionResponse' 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', 'startSegmentDetectionResponse_jobId' - Unique identifier for the segment detection job. The @JobId@ is returned
-- from @StartSegmentDetection@.
--
-- 'httpStatus', 'startSegmentDetectionResponse_httpStatus' - The response's http status code.
newStartSegmentDetectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartSegmentDetectionResponse
newStartSegmentDetectionResponse :: Int -> StartSegmentDetectionResponse
newStartSegmentDetectionResponse Int
pHttpStatus_ =
  StartSegmentDetectionResponse'
    { $sel:jobId:StartSegmentDetectionResponse' :: Maybe Text
jobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartSegmentDetectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Unique identifier for the segment detection job. The @JobId@ is returned
-- from @StartSegmentDetection@.
startSegmentDetectionResponse_jobId :: Lens.Lens' StartSegmentDetectionResponse (Prelude.Maybe Prelude.Text)
startSegmentDetectionResponse_jobId :: Lens' StartSegmentDetectionResponse (Maybe Text)
startSegmentDetectionResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartSegmentDetectionResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:StartSegmentDetectionResponse' :: StartSegmentDetectionResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: StartSegmentDetectionResponse
s@StartSegmentDetectionResponse' {} Maybe Text
a -> StartSegmentDetectionResponse
s {$sel:jobId:StartSegmentDetectionResponse' :: Maybe Text
jobId = Maybe Text
a} :: StartSegmentDetectionResponse)

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

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