{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Transcribe.Types.TranscriptionJobSummary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Transcribe.Types.TranscriptionJobSummary 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.Transcribe.Types.ContentRedaction
import Amazonka.Transcribe.Types.LanguageCode
import Amazonka.Transcribe.Types.LanguageCodeItem
import Amazonka.Transcribe.Types.ModelSettings
import Amazonka.Transcribe.Types.OutputLocationType
import Amazonka.Transcribe.Types.TranscriptionJobStatus

-- | Provides detailed information about a specific transcription job.
--
-- /See:/ 'newTranscriptionJobSummary' smart constructor.
data TranscriptionJobSummary = TranscriptionJobSummary'
  { -- | The date and time the specified transcription job finished processing.
    --
    -- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
    -- example, @2022-05-04T12:33:13.922000-07:00@ represents a transcription
    -- job that started processing at 12:33 PM UTC-7 on May 4, 2022.
    TranscriptionJobSummary -> Maybe POSIX
completionTime :: Prelude.Maybe Data.POSIX,
    -- | The content redaction settings of the transcription job.
    TranscriptionJobSummary -> Maybe ContentRedaction
contentRedaction :: Prelude.Maybe ContentRedaction,
    -- | The date and time the specified transcription job request was made.
    --
    -- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
    -- example, @2022-05-04T12:32:58.761000-07:00@ represents a transcription
    -- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
    TranscriptionJobSummary -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | If @TranscriptionJobStatus@ is @FAILED@, @FailureReason@ contains
    -- information about why the transcription job failed. See also:
    -- <https://docs.aws.amazon.com/transcribe/latest/APIReference/CommonErrors.html Common Errors>.
    TranscriptionJobSummary -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The confidence score associated with the language identified in your
    -- media file.
    --
    -- Confidence scores are values between 0 and 1; a larger value indicates a
    -- higher probability that the identified language correctly matches the
    -- language spoken in your media.
    TranscriptionJobSummary -> Maybe Double
identifiedLanguageScore :: Prelude.Maybe Prelude.Double,
    -- | Indicates whether automatic language identification was enabled (@TRUE@)
    -- for the specified transcription job.
    TranscriptionJobSummary -> Maybe Bool
identifyLanguage :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether automatic multi-language identification was enabled
    -- (@TRUE@) for the specified transcription job.
    TranscriptionJobSummary -> Maybe Bool
identifyMultipleLanguages :: Prelude.Maybe Prelude.Bool,
    -- | The language code used to create your transcription.
    TranscriptionJobSummary -> Maybe LanguageCode
languageCode :: Prelude.Maybe LanguageCode,
    -- | The language codes used to create your transcription job. This parameter
    -- is used with multi-language identification. For single-language
    -- identification, the singular version of this parameter, @LanguageCode@,
    -- is present.
    TranscriptionJobSummary -> Maybe [LanguageCodeItem]
languageCodes :: Prelude.Maybe [LanguageCodeItem],
    TranscriptionJobSummary -> Maybe ModelSettings
modelSettings :: Prelude.Maybe ModelSettings,
    -- | Indicates where the specified transcription output is stored.
    --
    -- If the value is @CUSTOMER_BUCKET@, the location is the Amazon S3 bucket
    -- you specified using the @OutputBucketName@ parameter in your request. If
    -- you also included @OutputKey@ in your request, your output is located in
    -- the path you specified in your request.
    --
    -- If the value is @SERVICE_BUCKET@, the location is a service-managed
    -- Amazon S3 bucket. To access a transcript stored in a service-managed
    -- bucket, use the URI shown in the @TranscriptFileUri@ or
    -- @RedactedTranscriptFileUri@ field.
    TranscriptionJobSummary -> Maybe OutputLocationType
outputLocationType :: Prelude.Maybe OutputLocationType,
    -- | The date and time your transcription job began processing.
    --
    -- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
    -- example, @2022-05-04T12:32:58.789000-07:00@ represents a transcription
    -- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
    TranscriptionJobSummary -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the transcription job. Job names are case sensitive and must
    -- be unique within an Amazon Web Services account.
    TranscriptionJobSummary -> Maybe Text
transcriptionJobName :: Prelude.Maybe Prelude.Text,
    -- | Provides the status of your transcription job.
    --
    -- If the status is @COMPLETED@, the job is finished and you can find the
    -- results at the location specified in @TranscriptFileUri@ (or
    -- @RedactedTranscriptFileUri@, if you requested transcript redaction). If
    -- the status is @FAILED@, @FailureReason@ provides details on why your
    -- transcription job failed.
    TranscriptionJobSummary -> Maybe TranscriptionJobStatus
transcriptionJobStatus :: Prelude.Maybe TranscriptionJobStatus
  }
  deriving (TranscriptionJobSummary -> TranscriptionJobSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TranscriptionJobSummary -> TranscriptionJobSummary -> Bool
$c/= :: TranscriptionJobSummary -> TranscriptionJobSummary -> Bool
== :: TranscriptionJobSummary -> TranscriptionJobSummary -> Bool
$c== :: TranscriptionJobSummary -> TranscriptionJobSummary -> Bool
Prelude.Eq, ReadPrec [TranscriptionJobSummary]
ReadPrec TranscriptionJobSummary
Int -> ReadS TranscriptionJobSummary
ReadS [TranscriptionJobSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TranscriptionJobSummary]
$creadListPrec :: ReadPrec [TranscriptionJobSummary]
readPrec :: ReadPrec TranscriptionJobSummary
$creadPrec :: ReadPrec TranscriptionJobSummary
readList :: ReadS [TranscriptionJobSummary]
$creadList :: ReadS [TranscriptionJobSummary]
readsPrec :: Int -> ReadS TranscriptionJobSummary
$creadsPrec :: Int -> ReadS TranscriptionJobSummary
Prelude.Read, Int -> TranscriptionJobSummary -> ShowS
[TranscriptionJobSummary] -> ShowS
TranscriptionJobSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TranscriptionJobSummary] -> ShowS
$cshowList :: [TranscriptionJobSummary] -> ShowS
show :: TranscriptionJobSummary -> String
$cshow :: TranscriptionJobSummary -> String
showsPrec :: Int -> TranscriptionJobSummary -> ShowS
$cshowsPrec :: Int -> TranscriptionJobSummary -> ShowS
Prelude.Show, forall x. Rep TranscriptionJobSummary x -> TranscriptionJobSummary
forall x. TranscriptionJobSummary -> Rep TranscriptionJobSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TranscriptionJobSummary x -> TranscriptionJobSummary
$cfrom :: forall x. TranscriptionJobSummary -> Rep TranscriptionJobSummary x
Prelude.Generic)

-- |
-- Create a value of 'TranscriptionJobSummary' 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:
--
-- 'completionTime', 'transcriptionJobSummary_completionTime' - The date and time the specified transcription job finished processing.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:33:13.922000-07:00@ represents a transcription
-- job that started processing at 12:33 PM UTC-7 on May 4, 2022.
--
-- 'contentRedaction', 'transcriptionJobSummary_contentRedaction' - The content redaction settings of the transcription job.
--
-- 'creationTime', 'transcriptionJobSummary_creationTime' - The date and time the specified transcription job request was made.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:32:58.761000-07:00@ represents a transcription
-- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
--
-- 'failureReason', 'transcriptionJobSummary_failureReason' - If @TranscriptionJobStatus@ is @FAILED@, @FailureReason@ contains
-- information about why the transcription job failed. See also:
-- <https://docs.aws.amazon.com/transcribe/latest/APIReference/CommonErrors.html Common Errors>.
--
-- 'identifiedLanguageScore', 'transcriptionJobSummary_identifiedLanguageScore' - The confidence score associated with the language identified in your
-- media file.
--
-- Confidence scores are values between 0 and 1; a larger value indicates a
-- higher probability that the identified language correctly matches the
-- language spoken in your media.
--
-- 'identifyLanguage', 'transcriptionJobSummary_identifyLanguage' - Indicates whether automatic language identification was enabled (@TRUE@)
-- for the specified transcription job.
--
-- 'identifyMultipleLanguages', 'transcriptionJobSummary_identifyMultipleLanguages' - Indicates whether automatic multi-language identification was enabled
-- (@TRUE@) for the specified transcription job.
--
-- 'languageCode', 'transcriptionJobSummary_languageCode' - The language code used to create your transcription.
--
-- 'languageCodes', 'transcriptionJobSummary_languageCodes' - The language codes used to create your transcription job. This parameter
-- is used with multi-language identification. For single-language
-- identification, the singular version of this parameter, @LanguageCode@,
-- is present.
--
-- 'modelSettings', 'transcriptionJobSummary_modelSettings' - Undocumented member.
--
-- 'outputLocationType', 'transcriptionJobSummary_outputLocationType' - Indicates where the specified transcription output is stored.
--
-- If the value is @CUSTOMER_BUCKET@, the location is the Amazon S3 bucket
-- you specified using the @OutputBucketName@ parameter in your request. If
-- you also included @OutputKey@ in your request, your output is located in
-- the path you specified in your request.
--
-- If the value is @SERVICE_BUCKET@, the location is a service-managed
-- Amazon S3 bucket. To access a transcript stored in a service-managed
-- bucket, use the URI shown in the @TranscriptFileUri@ or
-- @RedactedTranscriptFileUri@ field.
--
-- 'startTime', 'transcriptionJobSummary_startTime' - The date and time your transcription job began processing.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:32:58.789000-07:00@ represents a transcription
-- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
--
-- 'transcriptionJobName', 'transcriptionJobSummary_transcriptionJobName' - The name of the transcription job. Job names are case sensitive and must
-- be unique within an Amazon Web Services account.
--
-- 'transcriptionJobStatus', 'transcriptionJobSummary_transcriptionJobStatus' - Provides the status of your transcription job.
--
-- If the status is @COMPLETED@, the job is finished and you can find the
-- results at the location specified in @TranscriptFileUri@ (or
-- @RedactedTranscriptFileUri@, if you requested transcript redaction). If
-- the status is @FAILED@, @FailureReason@ provides details on why your
-- transcription job failed.
newTranscriptionJobSummary ::
  TranscriptionJobSummary
newTranscriptionJobSummary :: TranscriptionJobSummary
newTranscriptionJobSummary =
  TranscriptionJobSummary'
    { $sel:completionTime:TranscriptionJobSummary' :: Maybe POSIX
completionTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contentRedaction:TranscriptionJobSummary' :: Maybe ContentRedaction
contentRedaction = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:TranscriptionJobSummary' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:TranscriptionJobSummary' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:identifiedLanguageScore:TranscriptionJobSummary' :: Maybe Double
identifiedLanguageScore = forall a. Maybe a
Prelude.Nothing,
      $sel:identifyLanguage:TranscriptionJobSummary' :: Maybe Bool
identifyLanguage = forall a. Maybe a
Prelude.Nothing,
      $sel:identifyMultipleLanguages:TranscriptionJobSummary' :: Maybe Bool
identifyMultipleLanguages = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:TranscriptionJobSummary' :: Maybe LanguageCode
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCodes:TranscriptionJobSummary' :: Maybe [LanguageCodeItem]
languageCodes = forall a. Maybe a
Prelude.Nothing,
      $sel:modelSettings:TranscriptionJobSummary' :: Maybe ModelSettings
modelSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:outputLocationType:TranscriptionJobSummary' :: Maybe OutputLocationType
outputLocationType = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:TranscriptionJobSummary' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:transcriptionJobName:TranscriptionJobSummary' :: Maybe Text
transcriptionJobName = forall a. Maybe a
Prelude.Nothing,
      $sel:transcriptionJobStatus:TranscriptionJobSummary' :: Maybe TranscriptionJobStatus
transcriptionJobStatus = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time the specified transcription job finished processing.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:33:13.922000-07:00@ represents a transcription
-- job that started processing at 12:33 PM UTC-7 on May 4, 2022.
transcriptionJobSummary_completionTime :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.UTCTime)
transcriptionJobSummary_completionTime :: Lens' TranscriptionJobSummary (Maybe UTCTime)
transcriptionJobSummary_completionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe POSIX
completionTime :: Maybe POSIX
$sel:completionTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
completionTime} -> Maybe POSIX
completionTime) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe POSIX
a -> TranscriptionJobSummary
s {$sel:completionTime:TranscriptionJobSummary' :: Maybe POSIX
completionTime = Maybe POSIX
a} :: TranscriptionJobSummary) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The content redaction settings of the transcription job.
transcriptionJobSummary_contentRedaction :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe ContentRedaction)
transcriptionJobSummary_contentRedaction :: Lens' TranscriptionJobSummary (Maybe ContentRedaction)
transcriptionJobSummary_contentRedaction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe ContentRedaction
contentRedaction :: Maybe ContentRedaction
$sel:contentRedaction:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ContentRedaction
contentRedaction} -> Maybe ContentRedaction
contentRedaction) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe ContentRedaction
a -> TranscriptionJobSummary
s {$sel:contentRedaction:TranscriptionJobSummary' :: Maybe ContentRedaction
contentRedaction = Maybe ContentRedaction
a} :: TranscriptionJobSummary)

-- | The date and time the specified transcription job request was made.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:32:58.761000-07:00@ represents a transcription
-- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
transcriptionJobSummary_creationTime :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.UTCTime)
transcriptionJobSummary_creationTime :: Lens' TranscriptionJobSummary (Maybe UTCTime)
transcriptionJobSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe POSIX
a -> TranscriptionJobSummary
s {$sel:creationTime:TranscriptionJobSummary' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: TranscriptionJobSummary) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | If @TranscriptionJobStatus@ is @FAILED@, @FailureReason@ contains
-- information about why the transcription job failed. See also:
-- <https://docs.aws.amazon.com/transcribe/latest/APIReference/CommonErrors.html Common Errors>.
transcriptionJobSummary_failureReason :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.Text)
transcriptionJobSummary_failureReason :: Lens' TranscriptionJobSummary (Maybe Text)
transcriptionJobSummary_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe Text
a -> TranscriptionJobSummary
s {$sel:failureReason:TranscriptionJobSummary' :: Maybe Text
failureReason = Maybe Text
a} :: TranscriptionJobSummary)

-- | The confidence score associated with the language identified in your
-- media file.
--
-- Confidence scores are values between 0 and 1; a larger value indicates a
-- higher probability that the identified language correctly matches the
-- language spoken in your media.
transcriptionJobSummary_identifiedLanguageScore :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.Double)
transcriptionJobSummary_identifiedLanguageScore :: Lens' TranscriptionJobSummary (Maybe Double)
transcriptionJobSummary_identifiedLanguageScore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe Double
identifiedLanguageScore :: Maybe Double
$sel:identifiedLanguageScore:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Double
identifiedLanguageScore} -> Maybe Double
identifiedLanguageScore) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe Double
a -> TranscriptionJobSummary
s {$sel:identifiedLanguageScore:TranscriptionJobSummary' :: Maybe Double
identifiedLanguageScore = Maybe Double
a} :: TranscriptionJobSummary)

-- | Indicates whether automatic language identification was enabled (@TRUE@)
-- for the specified transcription job.
transcriptionJobSummary_identifyLanguage :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.Bool)
transcriptionJobSummary_identifyLanguage :: Lens' TranscriptionJobSummary (Maybe Bool)
transcriptionJobSummary_identifyLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe Bool
identifyLanguage :: Maybe Bool
$sel:identifyLanguage:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
identifyLanguage} -> Maybe Bool
identifyLanguage) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe Bool
a -> TranscriptionJobSummary
s {$sel:identifyLanguage:TranscriptionJobSummary' :: Maybe Bool
identifyLanguage = Maybe Bool
a} :: TranscriptionJobSummary)

-- | Indicates whether automatic multi-language identification was enabled
-- (@TRUE@) for the specified transcription job.
transcriptionJobSummary_identifyMultipleLanguages :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.Bool)
transcriptionJobSummary_identifyMultipleLanguages :: Lens' TranscriptionJobSummary (Maybe Bool)
transcriptionJobSummary_identifyMultipleLanguages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe Bool
identifyMultipleLanguages :: Maybe Bool
$sel:identifyMultipleLanguages:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
identifyMultipleLanguages} -> Maybe Bool
identifyMultipleLanguages) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe Bool
a -> TranscriptionJobSummary
s {$sel:identifyMultipleLanguages:TranscriptionJobSummary' :: Maybe Bool
identifyMultipleLanguages = Maybe Bool
a} :: TranscriptionJobSummary)

-- | The language code used to create your transcription.
transcriptionJobSummary_languageCode :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe LanguageCode)
transcriptionJobSummary_languageCode :: Lens' TranscriptionJobSummary (Maybe LanguageCode)
transcriptionJobSummary_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe LanguageCode
languageCode :: Maybe LanguageCode
$sel:languageCode:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe LanguageCode
languageCode} -> Maybe LanguageCode
languageCode) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe LanguageCode
a -> TranscriptionJobSummary
s {$sel:languageCode:TranscriptionJobSummary' :: Maybe LanguageCode
languageCode = Maybe LanguageCode
a} :: TranscriptionJobSummary)

-- | The language codes used to create your transcription job. This parameter
-- is used with multi-language identification. For single-language
-- identification, the singular version of this parameter, @LanguageCode@,
-- is present.
transcriptionJobSummary_languageCodes :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe [LanguageCodeItem])
transcriptionJobSummary_languageCodes :: Lens' TranscriptionJobSummary (Maybe [LanguageCodeItem])
transcriptionJobSummary_languageCodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe [LanguageCodeItem]
languageCodes :: Maybe [LanguageCodeItem]
$sel:languageCodes:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe [LanguageCodeItem]
languageCodes} -> Maybe [LanguageCodeItem]
languageCodes) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe [LanguageCodeItem]
a -> TranscriptionJobSummary
s {$sel:languageCodes:TranscriptionJobSummary' :: Maybe [LanguageCodeItem]
languageCodes = Maybe [LanguageCodeItem]
a} :: TranscriptionJobSummary) 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

-- | Undocumented member.
transcriptionJobSummary_modelSettings :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe ModelSettings)
transcriptionJobSummary_modelSettings :: Lens' TranscriptionJobSummary (Maybe ModelSettings)
transcriptionJobSummary_modelSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe ModelSettings
modelSettings :: Maybe ModelSettings
$sel:modelSettings:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ModelSettings
modelSettings} -> Maybe ModelSettings
modelSettings) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe ModelSettings
a -> TranscriptionJobSummary
s {$sel:modelSettings:TranscriptionJobSummary' :: Maybe ModelSettings
modelSettings = Maybe ModelSettings
a} :: TranscriptionJobSummary)

-- | Indicates where the specified transcription output is stored.
--
-- If the value is @CUSTOMER_BUCKET@, the location is the Amazon S3 bucket
-- you specified using the @OutputBucketName@ parameter in your request. If
-- you also included @OutputKey@ in your request, your output is located in
-- the path you specified in your request.
--
-- If the value is @SERVICE_BUCKET@, the location is a service-managed
-- Amazon S3 bucket. To access a transcript stored in a service-managed
-- bucket, use the URI shown in the @TranscriptFileUri@ or
-- @RedactedTranscriptFileUri@ field.
transcriptionJobSummary_outputLocationType :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe OutputLocationType)
transcriptionJobSummary_outputLocationType :: Lens' TranscriptionJobSummary (Maybe OutputLocationType)
transcriptionJobSummary_outputLocationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe OutputLocationType
outputLocationType :: Maybe OutputLocationType
$sel:outputLocationType:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe OutputLocationType
outputLocationType} -> Maybe OutputLocationType
outputLocationType) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe OutputLocationType
a -> TranscriptionJobSummary
s {$sel:outputLocationType:TranscriptionJobSummary' :: Maybe OutputLocationType
outputLocationType = Maybe OutputLocationType
a} :: TranscriptionJobSummary)

-- | The date and time your transcription job began processing.
--
-- Timestamps are in the format @YYYY-MM-DD\'T\'HH:MM:SS.SSSSSS-UTC@. For
-- example, @2022-05-04T12:32:58.789000-07:00@ represents a transcription
-- job that started processing at 12:32 PM UTC-7 on May 4, 2022.
transcriptionJobSummary_startTime :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.UTCTime)
transcriptionJobSummary_startTime :: Lens' TranscriptionJobSummary (Maybe UTCTime)
transcriptionJobSummary_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe POSIX
a -> TranscriptionJobSummary
s {$sel:startTime:TranscriptionJobSummary' :: Maybe POSIX
startTime = Maybe POSIX
a} :: TranscriptionJobSummary) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the transcription job. Job names are case sensitive and must
-- be unique within an Amazon Web Services account.
transcriptionJobSummary_transcriptionJobName :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe Prelude.Text)
transcriptionJobSummary_transcriptionJobName :: Lens' TranscriptionJobSummary (Maybe Text)
transcriptionJobSummary_transcriptionJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe Text
transcriptionJobName :: Maybe Text
$sel:transcriptionJobName:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
transcriptionJobName} -> Maybe Text
transcriptionJobName) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe Text
a -> TranscriptionJobSummary
s {$sel:transcriptionJobName:TranscriptionJobSummary' :: Maybe Text
transcriptionJobName = Maybe Text
a} :: TranscriptionJobSummary)

-- | Provides the status of your transcription job.
--
-- If the status is @COMPLETED@, the job is finished and you can find the
-- results at the location specified in @TranscriptFileUri@ (or
-- @RedactedTranscriptFileUri@, if you requested transcript redaction). If
-- the status is @FAILED@, @FailureReason@ provides details on why your
-- transcription job failed.
transcriptionJobSummary_transcriptionJobStatus :: Lens.Lens' TranscriptionJobSummary (Prelude.Maybe TranscriptionJobStatus)
transcriptionJobSummary_transcriptionJobStatus :: Lens' TranscriptionJobSummary (Maybe TranscriptionJobStatus)
transcriptionJobSummary_transcriptionJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranscriptionJobSummary' {Maybe TranscriptionJobStatus
transcriptionJobStatus :: Maybe TranscriptionJobStatus
$sel:transcriptionJobStatus:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe TranscriptionJobStatus
transcriptionJobStatus} -> Maybe TranscriptionJobStatus
transcriptionJobStatus) (\s :: TranscriptionJobSummary
s@TranscriptionJobSummary' {} Maybe TranscriptionJobStatus
a -> TranscriptionJobSummary
s {$sel:transcriptionJobStatus:TranscriptionJobSummary' :: Maybe TranscriptionJobStatus
transcriptionJobStatus = Maybe TranscriptionJobStatus
a} :: TranscriptionJobSummary)

instance Data.FromJSON TranscriptionJobSummary where
  parseJSON :: Value -> Parser TranscriptionJobSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TranscriptionJobSummary"
      ( \Object
x ->
          Maybe POSIX
-> Maybe ContentRedaction
-> Maybe POSIX
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Bool
-> Maybe LanguageCode
-> Maybe [LanguageCodeItem]
-> Maybe ModelSettings
-> Maybe OutputLocationType
-> Maybe POSIX
-> Maybe Text
-> Maybe TranscriptionJobStatus
-> TranscriptionJobSummary
TranscriptionJobSummary'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CompletionTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ContentRedaction")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IdentifiedLanguageScore")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IdentifyLanguage")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IdentifyMultipleLanguages")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LanguageCode")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LanguageCodes" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"ModelSettings")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"OutputLocationType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StartTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TranscriptionJobName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TranscriptionJobStatus")
      )

instance Prelude.Hashable TranscriptionJobSummary where
  hashWithSalt :: Int -> TranscriptionJobSummary -> Int
hashWithSalt Int
_salt TranscriptionJobSummary' {Maybe Bool
Maybe Double
Maybe [LanguageCodeItem]
Maybe Text
Maybe POSIX
Maybe LanguageCode
Maybe ModelSettings
Maybe OutputLocationType
Maybe ContentRedaction
Maybe TranscriptionJobStatus
transcriptionJobStatus :: Maybe TranscriptionJobStatus
transcriptionJobName :: Maybe Text
startTime :: Maybe POSIX
outputLocationType :: Maybe OutputLocationType
modelSettings :: Maybe ModelSettings
languageCodes :: Maybe [LanguageCodeItem]
languageCode :: Maybe LanguageCode
identifyMultipleLanguages :: Maybe Bool
identifyLanguage :: Maybe Bool
identifiedLanguageScore :: Maybe Double
failureReason :: Maybe Text
creationTime :: Maybe POSIX
contentRedaction :: Maybe ContentRedaction
completionTime :: Maybe POSIX
$sel:transcriptionJobStatus:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe TranscriptionJobStatus
$sel:transcriptionJobName:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
$sel:startTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
$sel:outputLocationType:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe OutputLocationType
$sel:modelSettings:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ModelSettings
$sel:languageCodes:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe [LanguageCodeItem]
$sel:languageCode:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe LanguageCode
$sel:identifyMultipleLanguages:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
$sel:identifyLanguage:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
$sel:identifiedLanguageScore:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Double
$sel:failureReason:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
$sel:creationTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
$sel:contentRedaction:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ContentRedaction
$sel:completionTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
completionTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ContentRedaction
contentRedaction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
identifiedLanguageScore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
identifyLanguage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
identifyMultipleLanguages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LanguageCode
languageCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LanguageCodeItem]
languageCodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelSettings
modelSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputLocationType
outputLocationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transcriptionJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TranscriptionJobStatus
transcriptionJobStatus

instance Prelude.NFData TranscriptionJobSummary where
  rnf :: TranscriptionJobSummary -> ()
rnf TranscriptionJobSummary' {Maybe Bool
Maybe Double
Maybe [LanguageCodeItem]
Maybe Text
Maybe POSIX
Maybe LanguageCode
Maybe ModelSettings
Maybe OutputLocationType
Maybe ContentRedaction
Maybe TranscriptionJobStatus
transcriptionJobStatus :: Maybe TranscriptionJobStatus
transcriptionJobName :: Maybe Text
startTime :: Maybe POSIX
outputLocationType :: Maybe OutputLocationType
modelSettings :: Maybe ModelSettings
languageCodes :: Maybe [LanguageCodeItem]
languageCode :: Maybe LanguageCode
identifyMultipleLanguages :: Maybe Bool
identifyLanguage :: Maybe Bool
identifiedLanguageScore :: Maybe Double
failureReason :: Maybe Text
creationTime :: Maybe POSIX
contentRedaction :: Maybe ContentRedaction
completionTime :: Maybe POSIX
$sel:transcriptionJobStatus:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe TranscriptionJobStatus
$sel:transcriptionJobName:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
$sel:startTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
$sel:outputLocationType:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe OutputLocationType
$sel:modelSettings:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ModelSettings
$sel:languageCodes:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe [LanguageCodeItem]
$sel:languageCode:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe LanguageCode
$sel:identifyMultipleLanguages:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
$sel:identifyLanguage:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Bool
$sel:identifiedLanguageScore:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Double
$sel:failureReason:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe Text
$sel:creationTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
$sel:contentRedaction:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe ContentRedaction
$sel:completionTime:TranscriptionJobSummary' :: TranscriptionJobSummary -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ContentRedaction
contentRedaction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
identifiedLanguageScore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
identifyLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
identifyMultipleLanguages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LanguageCode
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LanguageCodeItem]
languageCodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelSettings
modelSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputLocationType
outputLocationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transcriptionJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TranscriptionJobStatus
transcriptionJobStatus