{-# 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.DetectModerationLabels
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detects unsafe content in a specified JPEG or PNG format image. Use
-- @DetectModerationLabels@ to moderate images depending on your
-- requirements. For example, you might want to filter images that contain
-- nudity, but not images containing suggestive content.
--
-- To filter images, use the labels returned by @DetectModerationLabels@ to
-- determine which types of content are appropriate.
--
-- For information about moderation labels, see Detecting Unsafe Content in
-- the Amazon Rekognition Developer Guide.
--
-- You pass the input image either as base64-encoded image bytes or as a
-- reference to an image in an Amazon S3 bucket. If you use the AWS CLI to
-- call Amazon Rekognition operations, passing image bytes is not
-- supported. The image must be either a PNG or JPEG formatted file.
module Amazonka.Rekognition.DetectModerationLabels
  ( -- * Creating a Request
    DetectModerationLabels (..),
    newDetectModerationLabels,

    -- * Request Lenses
    detectModerationLabels_humanLoopConfig,
    detectModerationLabels_minConfidence,
    detectModerationLabels_image,

    -- * Destructuring the Response
    DetectModerationLabelsResponse (..),
    newDetectModerationLabelsResponse,

    -- * Response Lenses
    detectModerationLabelsResponse_humanLoopActivationOutput,
    detectModerationLabelsResponse_moderationLabels,
    detectModerationLabelsResponse_moderationModelVersion,
    detectModerationLabelsResponse_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:/ 'newDetectModerationLabels' smart constructor.
data DetectModerationLabels = DetectModerationLabels'
  { -- | Sets up the configuration for human evaluation, including the
    -- FlowDefinition the image will be sent to.
    DetectModerationLabels -> Maybe HumanLoopConfig
humanLoopConfig :: Prelude.Maybe HumanLoopConfig,
    -- | Specifies the minimum confidence level for the labels to return. Amazon
    -- Rekognition doesn\'t return any labels with a confidence level lower
    -- than this specified value.
    --
    -- If you don\'t specify @MinConfidence@, the operation returns labels with
    -- confidence values greater than or equal to 50 percent.
    DetectModerationLabels -> Maybe Double
minConfidence :: Prelude.Maybe Prelude.Double,
    -- | The input image as base64-encoded bytes or an S3 object. If you use the
    -- AWS CLI to call Amazon Rekognition operations, passing base64-encoded
    -- image bytes is not supported.
    --
    -- If you are using an AWS SDK to call Amazon Rekognition, you might not
    -- need to base64-encode image bytes passed using the @Bytes@ field. For
    -- more information, see Images in the Amazon Rekognition developer guide.
    DetectModerationLabels -> Image
image :: Image
  }
  deriving (DetectModerationLabels -> DetectModerationLabels -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetectModerationLabels -> DetectModerationLabels -> Bool
$c/= :: DetectModerationLabels -> DetectModerationLabels -> Bool
== :: DetectModerationLabels -> DetectModerationLabels -> Bool
$c== :: DetectModerationLabels -> DetectModerationLabels -> Bool
Prelude.Eq, ReadPrec [DetectModerationLabels]
ReadPrec DetectModerationLabels
Int -> ReadS DetectModerationLabels
ReadS [DetectModerationLabels]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetectModerationLabels]
$creadListPrec :: ReadPrec [DetectModerationLabels]
readPrec :: ReadPrec DetectModerationLabels
$creadPrec :: ReadPrec DetectModerationLabels
readList :: ReadS [DetectModerationLabels]
$creadList :: ReadS [DetectModerationLabels]
readsPrec :: Int -> ReadS DetectModerationLabels
$creadsPrec :: Int -> ReadS DetectModerationLabels
Prelude.Read, Int -> DetectModerationLabels -> ShowS
[DetectModerationLabels] -> ShowS
DetectModerationLabels -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetectModerationLabels] -> ShowS
$cshowList :: [DetectModerationLabels] -> ShowS
show :: DetectModerationLabels -> String
$cshow :: DetectModerationLabels -> String
showsPrec :: Int -> DetectModerationLabels -> ShowS
$cshowsPrec :: Int -> DetectModerationLabels -> ShowS
Prelude.Show, forall x. Rep DetectModerationLabels x -> DetectModerationLabels
forall x. DetectModerationLabels -> Rep DetectModerationLabels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetectModerationLabels x -> DetectModerationLabels
$cfrom :: forall x. DetectModerationLabels -> Rep DetectModerationLabels x
Prelude.Generic)

-- |
-- Create a value of 'DetectModerationLabels' 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:
--
-- 'humanLoopConfig', 'detectModerationLabels_humanLoopConfig' - Sets up the configuration for human evaluation, including the
-- FlowDefinition the image will be sent to.
--
-- 'minConfidence', 'detectModerationLabels_minConfidence' - Specifies the minimum confidence level for the labels to return. Amazon
-- Rekognition doesn\'t return any labels with a confidence level lower
-- than this specified value.
--
-- If you don\'t specify @MinConfidence@, the operation returns labels with
-- confidence values greater than or equal to 50 percent.
--
-- 'image', 'detectModerationLabels_image' - The input image as base64-encoded bytes or an S3 object. If you use the
-- AWS CLI to call Amazon Rekognition operations, passing base64-encoded
-- image bytes is not supported.
--
-- If you are using an AWS SDK to call Amazon Rekognition, you might not
-- need to base64-encode image bytes passed using the @Bytes@ field. For
-- more information, see Images in the Amazon Rekognition developer guide.
newDetectModerationLabels ::
  -- | 'image'
  Image ->
  DetectModerationLabels
newDetectModerationLabels :: Image -> DetectModerationLabels
newDetectModerationLabels Image
pImage_ =
  DetectModerationLabels'
    { $sel:humanLoopConfig:DetectModerationLabels' :: Maybe HumanLoopConfig
humanLoopConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:minConfidence:DetectModerationLabels' :: Maybe Double
minConfidence = forall a. Maybe a
Prelude.Nothing,
      $sel:image:DetectModerationLabels' :: Image
image = Image
pImage_
    }

-- | Sets up the configuration for human evaluation, including the
-- FlowDefinition the image will be sent to.
detectModerationLabels_humanLoopConfig :: Lens.Lens' DetectModerationLabels (Prelude.Maybe HumanLoopConfig)
detectModerationLabels_humanLoopConfig :: Lens' DetectModerationLabels (Maybe HumanLoopConfig)
detectModerationLabels_humanLoopConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabels' {Maybe HumanLoopConfig
humanLoopConfig :: Maybe HumanLoopConfig
$sel:humanLoopConfig:DetectModerationLabels' :: DetectModerationLabels -> Maybe HumanLoopConfig
humanLoopConfig} -> Maybe HumanLoopConfig
humanLoopConfig) (\s :: DetectModerationLabels
s@DetectModerationLabels' {} Maybe HumanLoopConfig
a -> DetectModerationLabels
s {$sel:humanLoopConfig:DetectModerationLabels' :: Maybe HumanLoopConfig
humanLoopConfig = Maybe HumanLoopConfig
a} :: DetectModerationLabels)

-- | Specifies the minimum confidence level for the labels to return. Amazon
-- Rekognition doesn\'t return any labels with a confidence level lower
-- than this specified value.
--
-- If you don\'t specify @MinConfidence@, the operation returns labels with
-- confidence values greater than or equal to 50 percent.
detectModerationLabels_minConfidence :: Lens.Lens' DetectModerationLabels (Prelude.Maybe Prelude.Double)
detectModerationLabels_minConfidence :: Lens' DetectModerationLabels (Maybe Double)
detectModerationLabels_minConfidence = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabels' {Maybe Double
minConfidence :: Maybe Double
$sel:minConfidence:DetectModerationLabels' :: DetectModerationLabels -> Maybe Double
minConfidence} -> Maybe Double
minConfidence) (\s :: DetectModerationLabels
s@DetectModerationLabels' {} Maybe Double
a -> DetectModerationLabels
s {$sel:minConfidence:DetectModerationLabels' :: Maybe Double
minConfidence = Maybe Double
a} :: DetectModerationLabels)

-- | The input image as base64-encoded bytes or an S3 object. If you use the
-- AWS CLI to call Amazon Rekognition operations, passing base64-encoded
-- image bytes is not supported.
--
-- If you are using an AWS SDK to call Amazon Rekognition, you might not
-- need to base64-encode image bytes passed using the @Bytes@ field. For
-- more information, see Images in the Amazon Rekognition developer guide.
detectModerationLabels_image :: Lens.Lens' DetectModerationLabels Image
detectModerationLabels_image :: Lens' DetectModerationLabels Image
detectModerationLabels_image = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabels' {Image
image :: Image
$sel:image:DetectModerationLabels' :: DetectModerationLabels -> Image
image} -> Image
image) (\s :: DetectModerationLabels
s@DetectModerationLabels' {} Image
a -> DetectModerationLabels
s {$sel:image:DetectModerationLabels' :: Image
image = Image
a} :: DetectModerationLabels)

instance Core.AWSRequest DetectModerationLabels where
  type
    AWSResponse DetectModerationLabels =
      DetectModerationLabelsResponse
  request :: (Service -> Service)
-> DetectModerationLabels -> Request DetectModerationLabels
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 DetectModerationLabels
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DetectModerationLabels)))
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 HumanLoopActivationOutput
-> Maybe [ModerationLabel]
-> Maybe Text
-> Int
-> DetectModerationLabelsResponse
DetectModerationLabelsResponse'
            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
"HumanLoopActivationOutput")
            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
"ModerationLabels"
                            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
"ModerationModelVersion")
            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 DetectModerationLabels where
  hashWithSalt :: Int -> DetectModerationLabels -> Int
hashWithSalt Int
_salt DetectModerationLabels' {Maybe Double
Maybe HumanLoopConfig
Image
image :: Image
minConfidence :: Maybe Double
humanLoopConfig :: Maybe HumanLoopConfig
$sel:image:DetectModerationLabels' :: DetectModerationLabels -> Image
$sel:minConfidence:DetectModerationLabels' :: DetectModerationLabels -> Maybe Double
$sel:humanLoopConfig:DetectModerationLabels' :: DetectModerationLabels -> Maybe HumanLoopConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HumanLoopConfig
humanLoopConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
minConfidence
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Image
image

instance Prelude.NFData DetectModerationLabels where
  rnf :: DetectModerationLabels -> ()
rnf DetectModerationLabels' {Maybe Double
Maybe HumanLoopConfig
Image
image :: Image
minConfidence :: Maybe Double
humanLoopConfig :: Maybe HumanLoopConfig
$sel:image:DetectModerationLabels' :: DetectModerationLabels -> Image
$sel:minConfidence:DetectModerationLabels' :: DetectModerationLabels -> Maybe Double
$sel:humanLoopConfig:DetectModerationLabels' :: DetectModerationLabels -> Maybe HumanLoopConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe HumanLoopConfig
humanLoopConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
minConfidence
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Image
image

instance Data.ToHeaders DetectModerationLabels where
  toHeaders :: DetectModerationLabels -> 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.DetectModerationLabels" ::
                          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 DetectModerationLabels where
  toJSON :: DetectModerationLabels -> Value
toJSON DetectModerationLabels' {Maybe Double
Maybe HumanLoopConfig
Image
image :: Image
minConfidence :: Maybe Double
humanLoopConfig :: Maybe HumanLoopConfig
$sel:image:DetectModerationLabels' :: DetectModerationLabels -> Image
$sel:minConfidence:DetectModerationLabels' :: DetectModerationLabels -> Maybe Double
$sel:humanLoopConfig:DetectModerationLabels' :: DetectModerationLabels -> Maybe HumanLoopConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"HumanLoopConfig" 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 HumanLoopConfig
humanLoopConfig,
            (Key
"MinConfidence" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Double
minConfidence,
            forall a. a -> Maybe a
Prelude.Just (Key
"Image" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Image
image)
          ]
      )

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

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

-- | /See:/ 'newDetectModerationLabelsResponse' smart constructor.
data DetectModerationLabelsResponse = DetectModerationLabelsResponse'
  { -- | Shows the results of the human in the loop evaluation.
    DetectModerationLabelsResponse -> Maybe HumanLoopActivationOutput
humanLoopActivationOutput :: Prelude.Maybe HumanLoopActivationOutput,
    -- | Array of detected Moderation labels and the time, in milliseconds from
    -- the start of the video, they were detected.
    DetectModerationLabelsResponse -> Maybe [ModerationLabel]
moderationLabels :: Prelude.Maybe [ModerationLabel],
    -- | Version number of the moderation detection model that was used to detect
    -- unsafe content.
    DetectModerationLabelsResponse -> Maybe Text
moderationModelVersion :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DetectModerationLabelsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DetectModerationLabelsResponse
-> DetectModerationLabelsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetectModerationLabelsResponse
-> DetectModerationLabelsResponse -> Bool
$c/= :: DetectModerationLabelsResponse
-> DetectModerationLabelsResponse -> Bool
== :: DetectModerationLabelsResponse
-> DetectModerationLabelsResponse -> Bool
$c== :: DetectModerationLabelsResponse
-> DetectModerationLabelsResponse -> Bool
Prelude.Eq, ReadPrec [DetectModerationLabelsResponse]
ReadPrec DetectModerationLabelsResponse
Int -> ReadS DetectModerationLabelsResponse
ReadS [DetectModerationLabelsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetectModerationLabelsResponse]
$creadListPrec :: ReadPrec [DetectModerationLabelsResponse]
readPrec :: ReadPrec DetectModerationLabelsResponse
$creadPrec :: ReadPrec DetectModerationLabelsResponse
readList :: ReadS [DetectModerationLabelsResponse]
$creadList :: ReadS [DetectModerationLabelsResponse]
readsPrec :: Int -> ReadS DetectModerationLabelsResponse
$creadsPrec :: Int -> ReadS DetectModerationLabelsResponse
Prelude.Read, Int -> DetectModerationLabelsResponse -> ShowS
[DetectModerationLabelsResponse] -> ShowS
DetectModerationLabelsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetectModerationLabelsResponse] -> ShowS
$cshowList :: [DetectModerationLabelsResponse] -> ShowS
show :: DetectModerationLabelsResponse -> String
$cshow :: DetectModerationLabelsResponse -> String
showsPrec :: Int -> DetectModerationLabelsResponse -> ShowS
$cshowsPrec :: Int -> DetectModerationLabelsResponse -> ShowS
Prelude.Show, forall x.
Rep DetectModerationLabelsResponse x
-> DetectModerationLabelsResponse
forall x.
DetectModerationLabelsResponse
-> Rep DetectModerationLabelsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DetectModerationLabelsResponse x
-> DetectModerationLabelsResponse
$cfrom :: forall x.
DetectModerationLabelsResponse
-> Rep DetectModerationLabelsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DetectModerationLabelsResponse' 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:
--
-- 'humanLoopActivationOutput', 'detectModerationLabelsResponse_humanLoopActivationOutput' - Shows the results of the human in the loop evaluation.
--
-- 'moderationLabels', 'detectModerationLabelsResponse_moderationLabels' - Array of detected Moderation labels and the time, in milliseconds from
-- the start of the video, they were detected.
--
-- 'moderationModelVersion', 'detectModerationLabelsResponse_moderationModelVersion' - Version number of the moderation detection model that was used to detect
-- unsafe content.
--
-- 'httpStatus', 'detectModerationLabelsResponse_httpStatus' - The response's http status code.
newDetectModerationLabelsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DetectModerationLabelsResponse
newDetectModerationLabelsResponse :: Int -> DetectModerationLabelsResponse
newDetectModerationLabelsResponse Int
pHttpStatus_ =
  DetectModerationLabelsResponse'
    { $sel:humanLoopActivationOutput:DetectModerationLabelsResponse' :: Maybe HumanLoopActivationOutput
humanLoopActivationOutput =
        forall a. Maybe a
Prelude.Nothing,
      $sel:moderationLabels:DetectModerationLabelsResponse' :: Maybe [ModerationLabel]
moderationLabels = forall a. Maybe a
Prelude.Nothing,
      $sel:moderationModelVersion:DetectModerationLabelsResponse' :: Maybe Text
moderationModelVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DetectModerationLabelsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Shows the results of the human in the loop evaluation.
detectModerationLabelsResponse_humanLoopActivationOutput :: Lens.Lens' DetectModerationLabelsResponse (Prelude.Maybe HumanLoopActivationOutput)
detectModerationLabelsResponse_humanLoopActivationOutput :: Lens'
  DetectModerationLabelsResponse (Maybe HumanLoopActivationOutput)
detectModerationLabelsResponse_humanLoopActivationOutput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabelsResponse' {Maybe HumanLoopActivationOutput
humanLoopActivationOutput :: Maybe HumanLoopActivationOutput
$sel:humanLoopActivationOutput:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe HumanLoopActivationOutput
humanLoopActivationOutput} -> Maybe HumanLoopActivationOutput
humanLoopActivationOutput) (\s :: DetectModerationLabelsResponse
s@DetectModerationLabelsResponse' {} Maybe HumanLoopActivationOutput
a -> DetectModerationLabelsResponse
s {$sel:humanLoopActivationOutput:DetectModerationLabelsResponse' :: Maybe HumanLoopActivationOutput
humanLoopActivationOutput = Maybe HumanLoopActivationOutput
a} :: DetectModerationLabelsResponse)

-- | Array of detected Moderation labels and the time, in milliseconds from
-- the start of the video, they were detected.
detectModerationLabelsResponse_moderationLabels :: Lens.Lens' DetectModerationLabelsResponse (Prelude.Maybe [ModerationLabel])
detectModerationLabelsResponse_moderationLabels :: Lens' DetectModerationLabelsResponse (Maybe [ModerationLabel])
detectModerationLabelsResponse_moderationLabels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabelsResponse' {Maybe [ModerationLabel]
moderationLabels :: Maybe [ModerationLabel]
$sel:moderationLabels:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe [ModerationLabel]
moderationLabels} -> Maybe [ModerationLabel]
moderationLabels) (\s :: DetectModerationLabelsResponse
s@DetectModerationLabelsResponse' {} Maybe [ModerationLabel]
a -> DetectModerationLabelsResponse
s {$sel:moderationLabels:DetectModerationLabelsResponse' :: Maybe [ModerationLabel]
moderationLabels = Maybe [ModerationLabel]
a} :: DetectModerationLabelsResponse) 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

-- | Version number of the moderation detection model that was used to detect
-- unsafe content.
detectModerationLabelsResponse_moderationModelVersion :: Lens.Lens' DetectModerationLabelsResponse (Prelude.Maybe Prelude.Text)
detectModerationLabelsResponse_moderationModelVersion :: Lens' DetectModerationLabelsResponse (Maybe Text)
detectModerationLabelsResponse_moderationModelVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectModerationLabelsResponse' {Maybe Text
moderationModelVersion :: Maybe Text
$sel:moderationModelVersion:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe Text
moderationModelVersion} -> Maybe Text
moderationModelVersion) (\s :: DetectModerationLabelsResponse
s@DetectModerationLabelsResponse' {} Maybe Text
a -> DetectModerationLabelsResponse
s {$sel:moderationModelVersion:DetectModerationLabelsResponse' :: Maybe Text
moderationModelVersion = Maybe Text
a} :: DetectModerationLabelsResponse)

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

instance
  Prelude.NFData
    DetectModerationLabelsResponse
  where
  rnf :: DetectModerationLabelsResponse -> ()
rnf DetectModerationLabelsResponse' {Int
Maybe [ModerationLabel]
Maybe Text
Maybe HumanLoopActivationOutput
httpStatus :: Int
moderationModelVersion :: Maybe Text
moderationLabels :: Maybe [ModerationLabel]
humanLoopActivationOutput :: Maybe HumanLoopActivationOutput
$sel:httpStatus:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Int
$sel:moderationModelVersion:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe Text
$sel:moderationLabels:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe [ModerationLabel]
$sel:humanLoopActivationOutput:DetectModerationLabelsResponse' :: DetectModerationLabelsResponse -> Maybe HumanLoopActivationOutput
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe HumanLoopActivationOutput
humanLoopActivationOutput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ModerationLabel]
moderationLabels
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
moderationModelVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus