{-# 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.MedicalTranscriptionJob
-- 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.MedicalTranscriptionJob 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.LanguageCode
import Amazonka.Transcribe.Types.Media
import Amazonka.Transcribe.Types.MediaFormat
import Amazonka.Transcribe.Types.MedicalContentIdentificationType
import Amazonka.Transcribe.Types.MedicalTranscript
import Amazonka.Transcribe.Types.MedicalTranscriptionSetting
import Amazonka.Transcribe.Types.Specialty
import Amazonka.Transcribe.Types.Tag
import Amazonka.Transcribe.Types.TranscriptionJobStatus
import Amazonka.Transcribe.Types.Type

-- | Provides detailed information about a medical transcription job.
--
-- To view the status of the specified medical transcription job, check the
-- @TranscriptionJobStatus@ field. If the status is @COMPLETED@, the job is
-- finished and you can find the results at the location specified in
-- @TranscriptFileUri@. If the status is @FAILED@, @FailureReason@ provides
-- details on why your transcription job failed.
--
-- /See:/ 'newMedicalTranscriptionJob' smart constructor.
data MedicalTranscriptionJob = MedicalTranscriptionJob'
  { -- | The date and time the specified medical 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.
    MedicalTranscriptionJob -> Maybe POSIX
completionTime :: Prelude.Maybe Data.POSIX,
    -- | Indicates whether content identification was enabled for your
    -- transcription request.
    MedicalTranscriptionJob -> Maybe MedicalContentIdentificationType
contentIdentificationType :: Prelude.Maybe MedicalContentIdentificationType,
    -- | The date and time the specified medical 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.
    MedicalTranscriptionJob -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | If @TranscriptionJobStatus@ is @FAILED@, @FailureReason@ contains
    -- information about why the transcription job request failed.
    --
    -- The @FailureReason@ field contains one of the following values:
    --
    -- -   @Unsupported media format@.
    --
    --     The media format specified in @MediaFormat@ isn\'t valid. Refer to
    --     __MediaFormat__ for a list of supported formats.
    --
    -- -   @The media format provided does not match the detected media format@.
    --
    --     The media format specified in @MediaFormat@ doesn\'t match the
    --     format of the input file. Check the media format of your media file
    --     and correct the specified value.
    --
    -- -   @Invalid sample rate for audio file@.
    --
    --     The sample rate specified in @MediaSampleRateHertz@ isn\'t valid.
    --     The sample rate must be between 16,000 and 48,000 hertz.
    --
    -- -   @The sample rate provided does not match the detected sample rate@.
    --
    --     The sample rate specified in @MediaSampleRateHertz@ doesn\'t match
    --     the sample rate detected in your input media file. Check the sample
    --     rate of your media file and correct the specified value.
    --
    -- -   @Invalid file size: file size too large@.
    --
    --     The size of your media file is larger than what Amazon Transcribe
    --     can process. For more information, refer to
    --     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
    --
    -- -   @Invalid number of channels: number of channels too large@.
    --
    --     Your audio contains more channels than Amazon Transcribe is able to
    --     process. For more information, refer to
    --     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
    MedicalTranscriptionJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The language code used to create your medical transcription job. US
    -- English (@en-US@) is the only supported language for medical
    -- transcriptions.
    MedicalTranscriptionJob -> Maybe LanguageCode
languageCode :: Prelude.Maybe LanguageCode,
    MedicalTranscriptionJob -> Maybe Media
media :: Prelude.Maybe Media,
    -- | The format of the input media file.
    MedicalTranscriptionJob -> Maybe MediaFormat
mediaFormat :: Prelude.Maybe MediaFormat,
    -- | The sample rate, in hertz, of the audio track in your input media file.
    MedicalTranscriptionJob -> Maybe Natural
mediaSampleRateHertz :: Prelude.Maybe Prelude.Natural,
    -- | The name of the medical transcription job. Job names are case sensitive
    -- and must be unique within an Amazon Web Services account.
    MedicalTranscriptionJob -> Maybe Text
medicalTranscriptionJobName :: Prelude.Maybe Prelude.Text,
    -- | Provides information on any additional settings that were included in
    -- your request. Additional settings include channel identification,
    -- alternative transcriptions, speaker partitioning, custom vocabularies,
    -- and custom vocabulary filters.
    MedicalTranscriptionJob -> Maybe MedicalTranscriptionSetting
settings :: Prelude.Maybe MedicalTranscriptionSetting,
    -- | Describes the medical specialty represented in your media.
    MedicalTranscriptionJob -> Maybe Specialty
specialty :: Prelude.Maybe Specialty,
    -- | The date and time the specified medical 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.
    MedicalTranscriptionJob -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The tags, each in the form of a key:value pair, assigned to the
    -- specified medical transcription job.
    MedicalTranscriptionJob -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | Provides you with the Amazon S3 URI you can use to access your
    -- transcript.
    MedicalTranscriptionJob -> Maybe MedicalTranscript
transcript :: Prelude.Maybe MedicalTranscript,
    -- | Provides the status of the specified medical transcription job.
    --
    -- If the status is @COMPLETED@, the job is finished and you can find the
    -- results at the location specified in @TranscriptFileUri@. If the status
    -- is @FAILED@, @FailureReason@ provides details on why your transcription
    -- job failed.
    MedicalTranscriptionJob -> Maybe TranscriptionJobStatus
transcriptionJobStatus :: Prelude.Maybe TranscriptionJobStatus,
    -- | Indicates whether the input media is a dictation or a conversation, as
    -- specified in the @StartMedicalTranscriptionJob@ request.
    MedicalTranscriptionJob -> Maybe Type
type' :: Prelude.Maybe Type
  }
  deriving (MedicalTranscriptionJob -> MedicalTranscriptionJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MedicalTranscriptionJob -> MedicalTranscriptionJob -> Bool
$c/= :: MedicalTranscriptionJob -> MedicalTranscriptionJob -> Bool
== :: MedicalTranscriptionJob -> MedicalTranscriptionJob -> Bool
$c== :: MedicalTranscriptionJob -> MedicalTranscriptionJob -> Bool
Prelude.Eq, ReadPrec [MedicalTranscriptionJob]
ReadPrec MedicalTranscriptionJob
Int -> ReadS MedicalTranscriptionJob
ReadS [MedicalTranscriptionJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MedicalTranscriptionJob]
$creadListPrec :: ReadPrec [MedicalTranscriptionJob]
readPrec :: ReadPrec MedicalTranscriptionJob
$creadPrec :: ReadPrec MedicalTranscriptionJob
readList :: ReadS [MedicalTranscriptionJob]
$creadList :: ReadS [MedicalTranscriptionJob]
readsPrec :: Int -> ReadS MedicalTranscriptionJob
$creadsPrec :: Int -> ReadS MedicalTranscriptionJob
Prelude.Read, Int -> MedicalTranscriptionJob -> ShowS
[MedicalTranscriptionJob] -> ShowS
MedicalTranscriptionJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MedicalTranscriptionJob] -> ShowS
$cshowList :: [MedicalTranscriptionJob] -> ShowS
show :: MedicalTranscriptionJob -> String
$cshow :: MedicalTranscriptionJob -> String
showsPrec :: Int -> MedicalTranscriptionJob -> ShowS
$cshowsPrec :: Int -> MedicalTranscriptionJob -> ShowS
Prelude.Show, forall x. Rep MedicalTranscriptionJob x -> MedicalTranscriptionJob
forall x. MedicalTranscriptionJob -> Rep MedicalTranscriptionJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MedicalTranscriptionJob x -> MedicalTranscriptionJob
$cfrom :: forall x. MedicalTranscriptionJob -> Rep MedicalTranscriptionJob x
Prelude.Generic)

-- |
-- Create a value of 'MedicalTranscriptionJob' 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', 'medicalTranscriptionJob_completionTime' - The date and time the specified medical 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.
--
-- 'contentIdentificationType', 'medicalTranscriptionJob_contentIdentificationType' - Indicates whether content identification was enabled for your
-- transcription request.
--
-- 'creationTime', 'medicalTranscriptionJob_creationTime' - The date and time the specified medical 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', 'medicalTranscriptionJob_failureReason' - If @TranscriptionJobStatus@ is @FAILED@, @FailureReason@ contains
-- information about why the transcription job request failed.
--
-- The @FailureReason@ field contains one of the following values:
--
-- -   @Unsupported media format@.
--
--     The media format specified in @MediaFormat@ isn\'t valid. Refer to
--     __MediaFormat__ for a list of supported formats.
--
-- -   @The media format provided does not match the detected media format@.
--
--     The media format specified in @MediaFormat@ doesn\'t match the
--     format of the input file. Check the media format of your media file
--     and correct the specified value.
--
-- -   @Invalid sample rate for audio file@.
--
--     The sample rate specified in @MediaSampleRateHertz@ isn\'t valid.
--     The sample rate must be between 16,000 and 48,000 hertz.
--
-- -   @The sample rate provided does not match the detected sample rate@.
--
--     The sample rate specified in @MediaSampleRateHertz@ doesn\'t match
--     the sample rate detected in your input media file. Check the sample
--     rate of your media file and correct the specified value.
--
-- -   @Invalid file size: file size too large@.
--
--     The size of your media file is larger than what Amazon Transcribe
--     can process. For more information, refer to
--     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
--
-- -   @Invalid number of channels: number of channels too large@.
--
--     Your audio contains more channels than Amazon Transcribe is able to
--     process. For more information, refer to
--     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
--
-- 'languageCode', 'medicalTranscriptionJob_languageCode' - The language code used to create your medical transcription job. US
-- English (@en-US@) is the only supported language for medical
-- transcriptions.
--
-- 'media', 'medicalTranscriptionJob_media' - Undocumented member.
--
-- 'mediaFormat', 'medicalTranscriptionJob_mediaFormat' - The format of the input media file.
--
-- 'mediaSampleRateHertz', 'medicalTranscriptionJob_mediaSampleRateHertz' - The sample rate, in hertz, of the audio track in your input media file.
--
-- 'medicalTranscriptionJobName', 'medicalTranscriptionJob_medicalTranscriptionJobName' - The name of the medical transcription job. Job names are case sensitive
-- and must be unique within an Amazon Web Services account.
--
-- 'settings', 'medicalTranscriptionJob_settings' - Provides information on any additional settings that were included in
-- your request. Additional settings include channel identification,
-- alternative transcriptions, speaker partitioning, custom vocabularies,
-- and custom vocabulary filters.
--
-- 'specialty', 'medicalTranscriptionJob_specialty' - Describes the medical specialty represented in your media.
--
-- 'startTime', 'medicalTranscriptionJob_startTime' - The date and time the specified medical 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.
--
-- 'tags', 'medicalTranscriptionJob_tags' - The tags, each in the form of a key:value pair, assigned to the
-- specified medical transcription job.
--
-- 'transcript', 'medicalTranscriptionJob_transcript' - Provides you with the Amazon S3 URI you can use to access your
-- transcript.
--
-- 'transcriptionJobStatus', 'medicalTranscriptionJob_transcriptionJobStatus' - Provides the status of the specified medical transcription job.
--
-- If the status is @COMPLETED@, the job is finished and you can find the
-- results at the location specified in @TranscriptFileUri@. If the status
-- is @FAILED@, @FailureReason@ provides details on why your transcription
-- job failed.
--
-- 'type'', 'medicalTranscriptionJob_type' - Indicates whether the input media is a dictation or a conversation, as
-- specified in the @StartMedicalTranscriptionJob@ request.
newMedicalTranscriptionJob ::
  MedicalTranscriptionJob
newMedicalTranscriptionJob :: MedicalTranscriptionJob
newMedicalTranscriptionJob =
  MedicalTranscriptionJob'
    { $sel:completionTime:MedicalTranscriptionJob' :: Maybe POSIX
completionTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contentIdentificationType:MedicalTranscriptionJob' :: Maybe MedicalContentIdentificationType
contentIdentificationType = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:MedicalTranscriptionJob' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:MedicalTranscriptionJob' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:MedicalTranscriptionJob' :: Maybe LanguageCode
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:media:MedicalTranscriptionJob' :: Maybe Media
media = forall a. Maybe a
Prelude.Nothing,
      $sel:mediaFormat:MedicalTranscriptionJob' :: Maybe MediaFormat
mediaFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:mediaSampleRateHertz:MedicalTranscriptionJob' :: Maybe Natural
mediaSampleRateHertz = forall a. Maybe a
Prelude.Nothing,
      $sel:medicalTranscriptionJobName:MedicalTranscriptionJob' :: Maybe Text
medicalTranscriptionJobName = forall a. Maybe a
Prelude.Nothing,
      $sel:settings:MedicalTranscriptionJob' :: Maybe MedicalTranscriptionSetting
settings = forall a. Maybe a
Prelude.Nothing,
      $sel:specialty:MedicalTranscriptionJob' :: Maybe Specialty
specialty = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:MedicalTranscriptionJob' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:MedicalTranscriptionJob' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:transcript:MedicalTranscriptionJob' :: Maybe MedicalTranscript
transcript = forall a. Maybe a
Prelude.Nothing,
      $sel:transcriptionJobStatus:MedicalTranscriptionJob' :: Maybe TranscriptionJobStatus
transcriptionJobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:type':MedicalTranscriptionJob' :: Maybe Type
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time the specified medical 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.
medicalTranscriptionJob_completionTime :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Prelude.UTCTime)
medicalTranscriptionJob_completionTime :: Lens' MedicalTranscriptionJob (Maybe UTCTime)
medicalTranscriptionJob_completionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe POSIX
completionTime :: Maybe POSIX
$sel:completionTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
completionTime} -> Maybe POSIX
completionTime) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe POSIX
a -> MedicalTranscriptionJob
s {$sel:completionTime:MedicalTranscriptionJob' :: Maybe POSIX
completionTime = Maybe POSIX
a} :: MedicalTranscriptionJob) 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

-- | Indicates whether content identification was enabled for your
-- transcription request.
medicalTranscriptionJob_contentIdentificationType :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe MedicalContentIdentificationType)
medicalTranscriptionJob_contentIdentificationType :: Lens'
  MedicalTranscriptionJob (Maybe MedicalContentIdentificationType)
medicalTranscriptionJob_contentIdentificationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe MedicalContentIdentificationType
contentIdentificationType :: Maybe MedicalContentIdentificationType
$sel:contentIdentificationType:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalContentIdentificationType
contentIdentificationType} -> Maybe MedicalContentIdentificationType
contentIdentificationType) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe MedicalContentIdentificationType
a -> MedicalTranscriptionJob
s {$sel:contentIdentificationType:MedicalTranscriptionJob' :: Maybe MedicalContentIdentificationType
contentIdentificationType = Maybe MedicalContentIdentificationType
a} :: MedicalTranscriptionJob)

-- | The date and time the specified medical 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.
medicalTranscriptionJob_creationTime :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Prelude.UTCTime)
medicalTranscriptionJob_creationTime :: Lens' MedicalTranscriptionJob (Maybe UTCTime)
medicalTranscriptionJob_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe POSIX
a -> MedicalTranscriptionJob
s {$sel:creationTime:MedicalTranscriptionJob' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: MedicalTranscriptionJob) 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 request failed.
--
-- The @FailureReason@ field contains one of the following values:
--
-- -   @Unsupported media format@.
--
--     The media format specified in @MediaFormat@ isn\'t valid. Refer to
--     __MediaFormat__ for a list of supported formats.
--
-- -   @The media format provided does not match the detected media format@.
--
--     The media format specified in @MediaFormat@ doesn\'t match the
--     format of the input file. Check the media format of your media file
--     and correct the specified value.
--
-- -   @Invalid sample rate for audio file@.
--
--     The sample rate specified in @MediaSampleRateHertz@ isn\'t valid.
--     The sample rate must be between 16,000 and 48,000 hertz.
--
-- -   @The sample rate provided does not match the detected sample rate@.
--
--     The sample rate specified in @MediaSampleRateHertz@ doesn\'t match
--     the sample rate detected in your input media file. Check the sample
--     rate of your media file and correct the specified value.
--
-- -   @Invalid file size: file size too large@.
--
--     The size of your media file is larger than what Amazon Transcribe
--     can process. For more information, refer to
--     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
--
-- -   @Invalid number of channels: number of channels too large@.
--
--     Your audio contains more channels than Amazon Transcribe is able to
--     process. For more information, refer to
--     <https://docs.aws.amazon.com/transcribe/latest/dg/limits-guidelines.html#limits Guidelines and quotas>.
medicalTranscriptionJob_failureReason :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Prelude.Text)
medicalTranscriptionJob_failureReason :: Lens' MedicalTranscriptionJob (Maybe Text)
medicalTranscriptionJob_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe Text
a -> MedicalTranscriptionJob
s {$sel:failureReason:MedicalTranscriptionJob' :: Maybe Text
failureReason = Maybe Text
a} :: MedicalTranscriptionJob)

-- | The language code used to create your medical transcription job. US
-- English (@en-US@) is the only supported language for medical
-- transcriptions.
medicalTranscriptionJob_languageCode :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe LanguageCode)
medicalTranscriptionJob_languageCode :: Lens' MedicalTranscriptionJob (Maybe LanguageCode)
medicalTranscriptionJob_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe LanguageCode
languageCode :: Maybe LanguageCode
$sel:languageCode:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe LanguageCode
languageCode} -> Maybe LanguageCode
languageCode) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe LanguageCode
a -> MedicalTranscriptionJob
s {$sel:languageCode:MedicalTranscriptionJob' :: Maybe LanguageCode
languageCode = Maybe LanguageCode
a} :: MedicalTranscriptionJob)

-- | Undocumented member.
medicalTranscriptionJob_media :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Media)
medicalTranscriptionJob_media :: Lens' MedicalTranscriptionJob (Maybe Media)
medicalTranscriptionJob_media = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe Media
media :: Maybe Media
$sel:media:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Media
media} -> Maybe Media
media) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe Media
a -> MedicalTranscriptionJob
s {$sel:media:MedicalTranscriptionJob' :: Maybe Media
media = Maybe Media
a} :: MedicalTranscriptionJob)

-- | The format of the input media file.
medicalTranscriptionJob_mediaFormat :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe MediaFormat)
medicalTranscriptionJob_mediaFormat :: Lens' MedicalTranscriptionJob (Maybe MediaFormat)
medicalTranscriptionJob_mediaFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe MediaFormat
mediaFormat :: Maybe MediaFormat
$sel:mediaFormat:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MediaFormat
mediaFormat} -> Maybe MediaFormat
mediaFormat) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe MediaFormat
a -> MedicalTranscriptionJob
s {$sel:mediaFormat:MedicalTranscriptionJob' :: Maybe MediaFormat
mediaFormat = Maybe MediaFormat
a} :: MedicalTranscriptionJob)

-- | The sample rate, in hertz, of the audio track in your input media file.
medicalTranscriptionJob_mediaSampleRateHertz :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Prelude.Natural)
medicalTranscriptionJob_mediaSampleRateHertz :: Lens' MedicalTranscriptionJob (Maybe Natural)
medicalTranscriptionJob_mediaSampleRateHertz = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe Natural
mediaSampleRateHertz :: Maybe Natural
$sel:mediaSampleRateHertz:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Natural
mediaSampleRateHertz} -> Maybe Natural
mediaSampleRateHertz) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe Natural
a -> MedicalTranscriptionJob
s {$sel:mediaSampleRateHertz:MedicalTranscriptionJob' :: Maybe Natural
mediaSampleRateHertz = Maybe Natural
a} :: MedicalTranscriptionJob)

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

-- | Provides information on any additional settings that were included in
-- your request. Additional settings include channel identification,
-- alternative transcriptions, speaker partitioning, custom vocabularies,
-- and custom vocabulary filters.
medicalTranscriptionJob_settings :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe MedicalTranscriptionSetting)
medicalTranscriptionJob_settings :: Lens' MedicalTranscriptionJob (Maybe MedicalTranscriptionSetting)
medicalTranscriptionJob_settings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe MedicalTranscriptionSetting
settings :: Maybe MedicalTranscriptionSetting
$sel:settings:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscriptionSetting
settings} -> Maybe MedicalTranscriptionSetting
settings) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe MedicalTranscriptionSetting
a -> MedicalTranscriptionJob
s {$sel:settings:MedicalTranscriptionJob' :: Maybe MedicalTranscriptionSetting
settings = Maybe MedicalTranscriptionSetting
a} :: MedicalTranscriptionJob)

-- | Describes the medical specialty represented in your media.
medicalTranscriptionJob_specialty :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Specialty)
medicalTranscriptionJob_specialty :: Lens' MedicalTranscriptionJob (Maybe Specialty)
medicalTranscriptionJob_specialty = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe Specialty
specialty :: Maybe Specialty
$sel:specialty:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Specialty
specialty} -> Maybe Specialty
specialty) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe Specialty
a -> MedicalTranscriptionJob
s {$sel:specialty:MedicalTranscriptionJob' :: Maybe Specialty
specialty = Maybe Specialty
a} :: MedicalTranscriptionJob)

-- | The date and time the specified medical 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.
medicalTranscriptionJob_startTime :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Prelude.UTCTime)
medicalTranscriptionJob_startTime :: Lens' MedicalTranscriptionJob (Maybe UTCTime)
medicalTranscriptionJob_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe POSIX
a -> MedicalTranscriptionJob
s {$sel:startTime:MedicalTranscriptionJob' :: Maybe POSIX
startTime = Maybe POSIX
a} :: MedicalTranscriptionJob) 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 tags, each in the form of a key:value pair, assigned to the
-- specified medical transcription job.
medicalTranscriptionJob_tags :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe (Prelude.NonEmpty Tag))
medicalTranscriptionJob_tags :: Lens' MedicalTranscriptionJob (Maybe (NonEmpty Tag))
medicalTranscriptionJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe (NonEmpty Tag)
a -> MedicalTranscriptionJob
s {$sel:tags:MedicalTranscriptionJob' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: MedicalTranscriptionJob) 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

-- | Provides you with the Amazon S3 URI you can use to access your
-- transcript.
medicalTranscriptionJob_transcript :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe MedicalTranscript)
medicalTranscriptionJob_transcript :: Lens' MedicalTranscriptionJob (Maybe MedicalTranscript)
medicalTranscriptionJob_transcript = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe MedicalTranscript
transcript :: Maybe MedicalTranscript
$sel:transcript:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscript
transcript} -> Maybe MedicalTranscript
transcript) (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe MedicalTranscript
a -> MedicalTranscriptionJob
s {$sel:transcript:MedicalTranscriptionJob' :: Maybe MedicalTranscript
transcript = Maybe MedicalTranscript
a} :: MedicalTranscriptionJob)

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

-- | Indicates whether the input media is a dictation or a conversation, as
-- specified in the @StartMedicalTranscriptionJob@ request.
medicalTranscriptionJob_type :: Lens.Lens' MedicalTranscriptionJob (Prelude.Maybe Type)
medicalTranscriptionJob_type :: Lens' MedicalTranscriptionJob (Maybe Type)
medicalTranscriptionJob_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MedicalTranscriptionJob' {Maybe Type
type' :: Maybe Type
$sel:type':MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Type
type'} -> Maybe Type
type') (\s :: MedicalTranscriptionJob
s@MedicalTranscriptionJob' {} Maybe Type
a -> MedicalTranscriptionJob
s {$sel:type':MedicalTranscriptionJob' :: Maybe Type
type' = Maybe Type
a} :: MedicalTranscriptionJob)

instance Data.FromJSON MedicalTranscriptionJob where
  parseJSON :: Value -> Parser MedicalTranscriptionJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MedicalTranscriptionJob"
      ( \Object
x ->
          Maybe POSIX
-> Maybe MedicalContentIdentificationType
-> Maybe POSIX
-> Maybe Text
-> Maybe LanguageCode
-> Maybe Media
-> Maybe MediaFormat
-> Maybe Natural
-> Maybe Text
-> Maybe MedicalTranscriptionSetting
-> Maybe Specialty
-> Maybe POSIX
-> Maybe (NonEmpty Tag)
-> Maybe MedicalTranscript
-> Maybe TranscriptionJobStatus
-> Maybe Type
-> MedicalTranscriptionJob
MedicalTranscriptionJob'
            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
"ContentIdentificationType")
            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
"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
"Media")
            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
"MediaFormat")
            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
"MediaSampleRateHertz")
            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
"MedicalTranscriptionJobName")
            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
"Settings")
            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
"Specialty")
            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
"Tags")
            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
"Transcript")
            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")
            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
"Type")
      )

instance Prelude.Hashable MedicalTranscriptionJob where
  hashWithSalt :: Int -> MedicalTranscriptionJob -> Int
hashWithSalt Int
_salt MedicalTranscriptionJob' {Maybe Natural
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe LanguageCode
Maybe Media
Maybe MediaFormat
Maybe MedicalContentIdentificationType
Maybe MedicalTranscript
Maybe MedicalTranscriptionSetting
Maybe Specialty
Maybe TranscriptionJobStatus
Maybe Type
type' :: Maybe Type
transcriptionJobStatus :: Maybe TranscriptionJobStatus
transcript :: Maybe MedicalTranscript
tags :: Maybe (NonEmpty Tag)
startTime :: Maybe POSIX
specialty :: Maybe Specialty
settings :: Maybe MedicalTranscriptionSetting
medicalTranscriptionJobName :: Maybe Text
mediaSampleRateHertz :: Maybe Natural
mediaFormat :: Maybe MediaFormat
media :: Maybe Media
languageCode :: Maybe LanguageCode
failureReason :: Maybe Text
creationTime :: Maybe POSIX
contentIdentificationType :: Maybe MedicalContentIdentificationType
completionTime :: Maybe POSIX
$sel:type':MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Type
$sel:transcriptionJobStatus:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe TranscriptionJobStatus
$sel:transcript:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscript
$sel:tags:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe (NonEmpty Tag)
$sel:startTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
$sel:specialty:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Specialty
$sel:settings:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscriptionSetting
$sel:medicalTranscriptionJobName:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Text
$sel:mediaSampleRateHertz:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Natural
$sel:mediaFormat:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MediaFormat
$sel:media:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Media
$sel:languageCode:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe LanguageCode
$sel:failureReason:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Text
$sel:creationTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
$sel:contentIdentificationType:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalContentIdentificationType
$sel:completionTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> 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 MedicalContentIdentificationType
contentIdentificationType
      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 LanguageCode
languageCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Media
media
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MediaFormat
mediaFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
mediaSampleRateHertz
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
medicalTranscriptionJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MedicalTranscriptionSetting
settings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Specialty
specialty
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MedicalTranscript
transcript
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TranscriptionJobStatus
transcriptionJobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Type
type'

instance Prelude.NFData MedicalTranscriptionJob where
  rnf :: MedicalTranscriptionJob -> ()
rnf MedicalTranscriptionJob' {Maybe Natural
Maybe (NonEmpty Tag)
Maybe Text
Maybe POSIX
Maybe LanguageCode
Maybe Media
Maybe MediaFormat
Maybe MedicalContentIdentificationType
Maybe MedicalTranscript
Maybe MedicalTranscriptionSetting
Maybe Specialty
Maybe TranscriptionJobStatus
Maybe Type
type' :: Maybe Type
transcriptionJobStatus :: Maybe TranscriptionJobStatus
transcript :: Maybe MedicalTranscript
tags :: Maybe (NonEmpty Tag)
startTime :: Maybe POSIX
specialty :: Maybe Specialty
settings :: Maybe MedicalTranscriptionSetting
medicalTranscriptionJobName :: Maybe Text
mediaSampleRateHertz :: Maybe Natural
mediaFormat :: Maybe MediaFormat
media :: Maybe Media
languageCode :: Maybe LanguageCode
failureReason :: Maybe Text
creationTime :: Maybe POSIX
contentIdentificationType :: Maybe MedicalContentIdentificationType
completionTime :: Maybe POSIX
$sel:type':MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Type
$sel:transcriptionJobStatus:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe TranscriptionJobStatus
$sel:transcript:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscript
$sel:tags:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe (NonEmpty Tag)
$sel:startTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
$sel:specialty:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Specialty
$sel:settings:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalTranscriptionSetting
$sel:medicalTranscriptionJobName:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Text
$sel:mediaSampleRateHertz:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Natural
$sel:mediaFormat:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MediaFormat
$sel:media:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Media
$sel:languageCode:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe LanguageCode
$sel:failureReason:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe Text
$sel:creationTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe POSIX
$sel:contentIdentificationType:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> Maybe MedicalContentIdentificationType
$sel:completionTime:MedicalTranscriptionJob' :: MedicalTranscriptionJob -> 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 MedicalContentIdentificationType
contentIdentificationType
      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 LanguageCode
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Media
media
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MediaFormat
mediaFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
mediaSampleRateHertz
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
medicalTranscriptionJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MedicalTranscriptionSetting
settings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Specialty
specialty
      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 (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MedicalTranscript
transcript
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TranscriptionJobStatus
transcriptionJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Type
type'