{-# 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.Transcribe.CreateMedicalVocabulary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new custom medical vocabulary.
--
-- Before creating a new custom medical vocabulary, you must first upload a
-- text file that contains your new entries, phrases, and terms into an
-- Amazon S3 bucket. Note that this differs from , where you can include a
-- list of terms within your request using the @Phrases@ flag;
-- @CreateMedicalVocabulary@ does not support the @Phrases@ flag.
--
-- Each language has a character set that contains all allowed characters
-- for that specific language. If you use unsupported characters, your
-- custom vocabulary request fails. Refer to
-- <https://docs.aws.amazon.com/transcribe/latest/dg/charsets.html Character Sets for Custom Vocabularies>
-- to get the character set for your language.
--
-- For more information, see
-- <https://docs.aws.amazon.com/transcribe/latest/dg/custom-vocabulary.html Custom vocabularies>.
module Amazonka.Transcribe.CreateMedicalVocabulary
  ( -- * Creating a Request
    CreateMedicalVocabulary (..),
    newCreateMedicalVocabulary,

    -- * Request Lenses
    createMedicalVocabulary_tags,
    createMedicalVocabulary_vocabularyName,
    createMedicalVocabulary_languageCode,
    createMedicalVocabulary_vocabularyFileUri,

    -- * Destructuring the Response
    CreateMedicalVocabularyResponse (..),
    newCreateMedicalVocabularyResponse,

    -- * Response Lenses
    createMedicalVocabularyResponse_failureReason,
    createMedicalVocabularyResponse_languageCode,
    createMedicalVocabularyResponse_lastModifiedTime,
    createMedicalVocabularyResponse_vocabularyName,
    createMedicalVocabularyResponse_vocabularyState,
    createMedicalVocabularyResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Transcribe.Types

-- | /See:/ 'newCreateMedicalVocabulary' smart constructor.
data CreateMedicalVocabulary = CreateMedicalVocabulary'
  { -- | Adds one or more custom tags, each in the form of a key:value pair, to a
    -- new custom medical vocabulary at the time you create this new custom
    -- vocabulary.
    --
    -- To learn more about using tags with Amazon Transcribe, refer to
    -- <https://docs.aws.amazon.com/transcribe/latest/dg/tagging.html Tagging resources>.
    CreateMedicalVocabulary -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | A unique name, chosen by you, for your new custom medical vocabulary.
    --
    -- This name is case sensitive, cannot contain spaces, and must be unique
    -- within an Amazon Web Services account. If you try to create a new custom
    -- medical vocabulary with the same name as an existing custom medical
    -- vocabulary, you get a @ConflictException@ error.
    CreateMedicalVocabulary -> Text
vocabularyName :: Prelude.Text,
    -- | The language code that represents the language of the entries in your
    -- custom vocabulary. US English (@en-US@) is the only language supported
    -- with Amazon Transcribe Medical.
    CreateMedicalVocabulary -> LanguageCode
languageCode :: LanguageCode,
    -- | The Amazon S3 location (URI) of the text file that contains your custom
    -- medical vocabulary. The URI must be in the same Amazon Web Services
    -- Region as the resource you\'re calling.
    --
    -- Here\'s an example URI path:
    -- @s3:\/\/DOC-EXAMPLE-BUCKET\/my-vocab-file.txt@
    CreateMedicalVocabulary -> Text
vocabularyFileUri :: Prelude.Text
  }
  deriving (CreateMedicalVocabulary -> CreateMedicalVocabulary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMedicalVocabulary -> CreateMedicalVocabulary -> Bool
$c/= :: CreateMedicalVocabulary -> CreateMedicalVocabulary -> Bool
== :: CreateMedicalVocabulary -> CreateMedicalVocabulary -> Bool
$c== :: CreateMedicalVocabulary -> CreateMedicalVocabulary -> Bool
Prelude.Eq, ReadPrec [CreateMedicalVocabulary]
ReadPrec CreateMedicalVocabulary
Int -> ReadS CreateMedicalVocabulary
ReadS [CreateMedicalVocabulary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMedicalVocabulary]
$creadListPrec :: ReadPrec [CreateMedicalVocabulary]
readPrec :: ReadPrec CreateMedicalVocabulary
$creadPrec :: ReadPrec CreateMedicalVocabulary
readList :: ReadS [CreateMedicalVocabulary]
$creadList :: ReadS [CreateMedicalVocabulary]
readsPrec :: Int -> ReadS CreateMedicalVocabulary
$creadsPrec :: Int -> ReadS CreateMedicalVocabulary
Prelude.Read, Int -> CreateMedicalVocabulary -> ShowS
[CreateMedicalVocabulary] -> ShowS
CreateMedicalVocabulary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMedicalVocabulary] -> ShowS
$cshowList :: [CreateMedicalVocabulary] -> ShowS
show :: CreateMedicalVocabulary -> String
$cshow :: CreateMedicalVocabulary -> String
showsPrec :: Int -> CreateMedicalVocabulary -> ShowS
$cshowsPrec :: Int -> CreateMedicalVocabulary -> ShowS
Prelude.Show, forall x. Rep CreateMedicalVocabulary x -> CreateMedicalVocabulary
forall x. CreateMedicalVocabulary -> Rep CreateMedicalVocabulary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateMedicalVocabulary x -> CreateMedicalVocabulary
$cfrom :: forall x. CreateMedicalVocabulary -> Rep CreateMedicalVocabulary x
Prelude.Generic)

-- |
-- Create a value of 'CreateMedicalVocabulary' 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:
--
-- 'tags', 'createMedicalVocabulary_tags' - Adds one or more custom tags, each in the form of a key:value pair, to a
-- new custom medical vocabulary at the time you create this new custom
-- vocabulary.
--
-- To learn more about using tags with Amazon Transcribe, refer to
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tagging.html Tagging resources>.
--
-- 'vocabularyName', 'createMedicalVocabulary_vocabularyName' - A unique name, chosen by you, for your new custom medical vocabulary.
--
-- This name is case sensitive, cannot contain spaces, and must be unique
-- within an Amazon Web Services account. If you try to create a new custom
-- medical vocabulary with the same name as an existing custom medical
-- vocabulary, you get a @ConflictException@ error.
--
-- 'languageCode', 'createMedicalVocabulary_languageCode' - The language code that represents the language of the entries in your
-- custom vocabulary. US English (@en-US@) is the only language supported
-- with Amazon Transcribe Medical.
--
-- 'vocabularyFileUri', 'createMedicalVocabulary_vocabularyFileUri' - The Amazon S3 location (URI) of the text file that contains your custom
-- medical vocabulary. The URI must be in the same Amazon Web Services
-- Region as the resource you\'re calling.
--
-- Here\'s an example URI path:
-- @s3:\/\/DOC-EXAMPLE-BUCKET\/my-vocab-file.txt@
newCreateMedicalVocabulary ::
  -- | 'vocabularyName'
  Prelude.Text ->
  -- | 'languageCode'
  LanguageCode ->
  -- | 'vocabularyFileUri'
  Prelude.Text ->
  CreateMedicalVocabulary
newCreateMedicalVocabulary :: Text -> LanguageCode -> Text -> CreateMedicalVocabulary
newCreateMedicalVocabulary
  Text
pVocabularyName_
  LanguageCode
pLanguageCode_
  Text
pVocabularyFileUri_ =
    CreateMedicalVocabulary'
      { $sel:tags:CreateMedicalVocabulary' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vocabularyName:CreateMedicalVocabulary' :: Text
vocabularyName = Text
pVocabularyName_,
        $sel:languageCode:CreateMedicalVocabulary' :: LanguageCode
languageCode = LanguageCode
pLanguageCode_,
        $sel:vocabularyFileUri:CreateMedicalVocabulary' :: Text
vocabularyFileUri = Text
pVocabularyFileUri_
      }

-- | Adds one or more custom tags, each in the form of a key:value pair, to a
-- new custom medical vocabulary at the time you create this new custom
-- vocabulary.
--
-- To learn more about using tags with Amazon Transcribe, refer to
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tagging.html Tagging resources>.
createMedicalVocabulary_tags :: Lens.Lens' CreateMedicalVocabulary (Prelude.Maybe (Prelude.NonEmpty Tag))
createMedicalVocabulary_tags :: Lens' CreateMedicalVocabulary (Maybe (NonEmpty Tag))
createMedicalVocabulary_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabulary' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateMedicalVocabulary
s@CreateMedicalVocabulary' {} Maybe (NonEmpty Tag)
a -> CreateMedicalVocabulary
s {$sel:tags:CreateMedicalVocabulary' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: CreateMedicalVocabulary) 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

-- | A unique name, chosen by you, for your new custom medical vocabulary.
--
-- This name is case sensitive, cannot contain spaces, and must be unique
-- within an Amazon Web Services account. If you try to create a new custom
-- medical vocabulary with the same name as an existing custom medical
-- vocabulary, you get a @ConflictException@ error.
createMedicalVocabulary_vocabularyName :: Lens.Lens' CreateMedicalVocabulary Prelude.Text
createMedicalVocabulary_vocabularyName :: Lens' CreateMedicalVocabulary Text
createMedicalVocabulary_vocabularyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabulary' {Text
vocabularyName :: Text
$sel:vocabularyName:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
vocabularyName} -> Text
vocabularyName) (\s :: CreateMedicalVocabulary
s@CreateMedicalVocabulary' {} Text
a -> CreateMedicalVocabulary
s {$sel:vocabularyName:CreateMedicalVocabulary' :: Text
vocabularyName = Text
a} :: CreateMedicalVocabulary)

-- | The language code that represents the language of the entries in your
-- custom vocabulary. US English (@en-US@) is the only language supported
-- with Amazon Transcribe Medical.
createMedicalVocabulary_languageCode :: Lens.Lens' CreateMedicalVocabulary LanguageCode
createMedicalVocabulary_languageCode :: Lens' CreateMedicalVocabulary LanguageCode
createMedicalVocabulary_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabulary' {LanguageCode
languageCode :: LanguageCode
$sel:languageCode:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> LanguageCode
languageCode} -> LanguageCode
languageCode) (\s :: CreateMedicalVocabulary
s@CreateMedicalVocabulary' {} LanguageCode
a -> CreateMedicalVocabulary
s {$sel:languageCode:CreateMedicalVocabulary' :: LanguageCode
languageCode = LanguageCode
a} :: CreateMedicalVocabulary)

-- | The Amazon S3 location (URI) of the text file that contains your custom
-- medical vocabulary. The URI must be in the same Amazon Web Services
-- Region as the resource you\'re calling.
--
-- Here\'s an example URI path:
-- @s3:\/\/DOC-EXAMPLE-BUCKET\/my-vocab-file.txt@
createMedicalVocabulary_vocabularyFileUri :: Lens.Lens' CreateMedicalVocabulary Prelude.Text
createMedicalVocabulary_vocabularyFileUri :: Lens' CreateMedicalVocabulary Text
createMedicalVocabulary_vocabularyFileUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabulary' {Text
vocabularyFileUri :: Text
$sel:vocabularyFileUri:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
vocabularyFileUri} -> Text
vocabularyFileUri) (\s :: CreateMedicalVocabulary
s@CreateMedicalVocabulary' {} Text
a -> CreateMedicalVocabulary
s {$sel:vocabularyFileUri:CreateMedicalVocabulary' :: Text
vocabularyFileUri = Text
a} :: CreateMedicalVocabulary)

instance Core.AWSRequest CreateMedicalVocabulary where
  type
    AWSResponse CreateMedicalVocabulary =
      CreateMedicalVocabularyResponse
  request :: (Service -> Service)
-> CreateMedicalVocabulary -> Request CreateMedicalVocabulary
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 CreateMedicalVocabulary
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateMedicalVocabulary)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe LanguageCode
-> Maybe POSIX
-> Maybe Text
-> Maybe VocabularyState
-> Int
-> CreateMedicalVocabularyResponse
CreateMedicalVocabularyResponse'
            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
"FailureReason")
            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
"LanguageCode")
            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
"LastModifiedTime")
            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
"VocabularyName")
            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
"VocabularyState")
            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 CreateMedicalVocabulary where
  hashWithSalt :: Int -> CreateMedicalVocabulary -> Int
hashWithSalt Int
_salt CreateMedicalVocabulary' {Maybe (NonEmpty Tag)
Text
LanguageCode
vocabularyFileUri :: Text
languageCode :: LanguageCode
vocabularyName :: Text
tags :: Maybe (NonEmpty Tag)
$sel:vocabularyFileUri:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:languageCode:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> LanguageCode
$sel:vocabularyName:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:tags:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Maybe (NonEmpty Tag)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vocabularyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LanguageCode
languageCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vocabularyFileUri

instance Prelude.NFData CreateMedicalVocabulary where
  rnf :: CreateMedicalVocabulary -> ()
rnf CreateMedicalVocabulary' {Maybe (NonEmpty Tag)
Text
LanguageCode
vocabularyFileUri :: Text
languageCode :: LanguageCode
vocabularyName :: Text
tags :: Maybe (NonEmpty Tag)
$sel:vocabularyFileUri:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:languageCode:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> LanguageCode
$sel:vocabularyName:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:tags:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Maybe (NonEmpty Tag)
..} =
    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 Text
vocabularyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf LanguageCode
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vocabularyFileUri

instance Data.ToHeaders CreateMedicalVocabulary where
  toHeaders :: CreateMedicalVocabulary -> 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
"Transcribe.CreateMedicalVocabulary" ::
                          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 CreateMedicalVocabulary where
  toJSON :: CreateMedicalVocabulary -> Value
toJSON CreateMedicalVocabulary' {Maybe (NonEmpty Tag)
Text
LanguageCode
vocabularyFileUri :: Text
languageCode :: LanguageCode
vocabularyName :: Text
tags :: Maybe (NonEmpty Tag)
$sel:vocabularyFileUri:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:languageCode:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> LanguageCode
$sel:vocabularyName:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Text
$sel:tags:CreateMedicalVocabulary' :: CreateMedicalVocabulary -> Maybe (NonEmpty Tag)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Tags" 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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"VocabularyName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vocabularyName),
            forall a. a -> Maybe a
Prelude.Just (Key
"LanguageCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= LanguageCode
languageCode),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"VocabularyFileUri" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vocabularyFileUri)
          ]
      )

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

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

-- | /See:/ 'newCreateMedicalVocabularyResponse' smart constructor.
data CreateMedicalVocabularyResponse = CreateMedicalVocabularyResponse'
  { -- | If @VocabularyState@ is @FAILED@, @FailureReason@ contains information
    -- about why the medical transcription job request failed. See also:
    -- <https://docs.aws.amazon.com/transcribe/latest/APIReference/CommonErrors.html Common Errors>.
    CreateMedicalVocabularyResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The language code you selected for your custom medical vocabulary. US
    -- English (@en-US@) is the only language supported with Amazon Transcribe
    -- Medical.
    CreateMedicalVocabularyResponse -> Maybe LanguageCode
languageCode :: Prelude.Maybe LanguageCode,
    -- | The date and time you created your custom medical vocabulary.
    --
    -- 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 12:32 PM UTC-7 on
    -- May 4, 2022.
    CreateMedicalVocabularyResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name you chose for your custom medical vocabulary.
    CreateMedicalVocabularyResponse -> Maybe Text
vocabularyName :: Prelude.Maybe Prelude.Text,
    -- | The processing state of your custom medical vocabulary. If the state is
    -- @READY@, you can use the custom vocabulary in a
    -- @StartMedicalTranscriptionJob@ request.
    CreateMedicalVocabularyResponse -> Maybe VocabularyState
vocabularyState :: Prelude.Maybe VocabularyState,
    -- | The response's http status code.
    CreateMedicalVocabularyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateMedicalVocabularyResponse
-> CreateMedicalVocabularyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMedicalVocabularyResponse
-> CreateMedicalVocabularyResponse -> Bool
$c/= :: CreateMedicalVocabularyResponse
-> CreateMedicalVocabularyResponse -> Bool
== :: CreateMedicalVocabularyResponse
-> CreateMedicalVocabularyResponse -> Bool
$c== :: CreateMedicalVocabularyResponse
-> CreateMedicalVocabularyResponse -> Bool
Prelude.Eq, ReadPrec [CreateMedicalVocabularyResponse]
ReadPrec CreateMedicalVocabularyResponse
Int -> ReadS CreateMedicalVocabularyResponse
ReadS [CreateMedicalVocabularyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMedicalVocabularyResponse]
$creadListPrec :: ReadPrec [CreateMedicalVocabularyResponse]
readPrec :: ReadPrec CreateMedicalVocabularyResponse
$creadPrec :: ReadPrec CreateMedicalVocabularyResponse
readList :: ReadS [CreateMedicalVocabularyResponse]
$creadList :: ReadS [CreateMedicalVocabularyResponse]
readsPrec :: Int -> ReadS CreateMedicalVocabularyResponse
$creadsPrec :: Int -> ReadS CreateMedicalVocabularyResponse
Prelude.Read, Int -> CreateMedicalVocabularyResponse -> ShowS
[CreateMedicalVocabularyResponse] -> ShowS
CreateMedicalVocabularyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMedicalVocabularyResponse] -> ShowS
$cshowList :: [CreateMedicalVocabularyResponse] -> ShowS
show :: CreateMedicalVocabularyResponse -> String
$cshow :: CreateMedicalVocabularyResponse -> String
showsPrec :: Int -> CreateMedicalVocabularyResponse -> ShowS
$cshowsPrec :: Int -> CreateMedicalVocabularyResponse -> ShowS
Prelude.Show, forall x.
Rep CreateMedicalVocabularyResponse x
-> CreateMedicalVocabularyResponse
forall x.
CreateMedicalVocabularyResponse
-> Rep CreateMedicalVocabularyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateMedicalVocabularyResponse x
-> CreateMedicalVocabularyResponse
$cfrom :: forall x.
CreateMedicalVocabularyResponse
-> Rep CreateMedicalVocabularyResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateMedicalVocabularyResponse' 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:
--
-- 'failureReason', 'createMedicalVocabularyResponse_failureReason' - If @VocabularyState@ is @FAILED@, @FailureReason@ contains information
-- about why the medical transcription job request failed. See also:
-- <https://docs.aws.amazon.com/transcribe/latest/APIReference/CommonErrors.html Common Errors>.
--
-- 'languageCode', 'createMedicalVocabularyResponse_languageCode' - The language code you selected for your custom medical vocabulary. US
-- English (@en-US@) is the only language supported with Amazon Transcribe
-- Medical.
--
-- 'lastModifiedTime', 'createMedicalVocabularyResponse_lastModifiedTime' - The date and time you created your custom medical vocabulary.
--
-- 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 12:32 PM UTC-7 on
-- May 4, 2022.
--
-- 'vocabularyName', 'createMedicalVocabularyResponse_vocabularyName' - The name you chose for your custom medical vocabulary.
--
-- 'vocabularyState', 'createMedicalVocabularyResponse_vocabularyState' - The processing state of your custom medical vocabulary. If the state is
-- @READY@, you can use the custom vocabulary in a
-- @StartMedicalTranscriptionJob@ request.
--
-- 'httpStatus', 'createMedicalVocabularyResponse_httpStatus' - The response's http status code.
newCreateMedicalVocabularyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateMedicalVocabularyResponse
newCreateMedicalVocabularyResponse :: Int -> CreateMedicalVocabularyResponse
newCreateMedicalVocabularyResponse Int
pHttpStatus_ =
  CreateMedicalVocabularyResponse'
    { $sel:failureReason:CreateMedicalVocabularyResponse' :: Maybe Text
failureReason =
        forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:CreateMedicalVocabularyResponse' :: Maybe LanguageCode
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateMedicalVocabularyResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:vocabularyName:CreateMedicalVocabularyResponse' :: Maybe Text
vocabularyName = forall a. Maybe a
Prelude.Nothing,
      $sel:vocabularyState:CreateMedicalVocabularyResponse' :: Maybe VocabularyState
vocabularyState = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateMedicalVocabularyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The language code you selected for your custom medical vocabulary. US
-- English (@en-US@) is the only language supported with Amazon Transcribe
-- Medical.
createMedicalVocabularyResponse_languageCode :: Lens.Lens' CreateMedicalVocabularyResponse (Prelude.Maybe LanguageCode)
createMedicalVocabularyResponse_languageCode :: Lens' CreateMedicalVocabularyResponse (Maybe LanguageCode)
createMedicalVocabularyResponse_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabularyResponse' {Maybe LanguageCode
languageCode :: Maybe LanguageCode
$sel:languageCode:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe LanguageCode
languageCode} -> Maybe LanguageCode
languageCode) (\s :: CreateMedicalVocabularyResponse
s@CreateMedicalVocabularyResponse' {} Maybe LanguageCode
a -> CreateMedicalVocabularyResponse
s {$sel:languageCode:CreateMedicalVocabularyResponse' :: Maybe LanguageCode
languageCode = Maybe LanguageCode
a} :: CreateMedicalVocabularyResponse)

-- | The date and time you created your custom medical vocabulary.
--
-- 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 12:32 PM UTC-7 on
-- May 4, 2022.
createMedicalVocabularyResponse_lastModifiedTime :: Lens.Lens' CreateMedicalVocabularyResponse (Prelude.Maybe Prelude.UTCTime)
createMedicalVocabularyResponse_lastModifiedTime :: Lens' CreateMedicalVocabularyResponse (Maybe UTCTime)
createMedicalVocabularyResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabularyResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateMedicalVocabularyResponse
s@CreateMedicalVocabularyResponse' {} Maybe POSIX
a -> CreateMedicalVocabularyResponse
s {$sel:lastModifiedTime:CreateMedicalVocabularyResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateMedicalVocabularyResponse) 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 you chose for your custom medical vocabulary.
createMedicalVocabularyResponse_vocabularyName :: Lens.Lens' CreateMedicalVocabularyResponse (Prelude.Maybe Prelude.Text)
createMedicalVocabularyResponse_vocabularyName :: Lens' CreateMedicalVocabularyResponse (Maybe Text)
createMedicalVocabularyResponse_vocabularyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabularyResponse' {Maybe Text
vocabularyName :: Maybe Text
$sel:vocabularyName:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe Text
vocabularyName} -> Maybe Text
vocabularyName) (\s :: CreateMedicalVocabularyResponse
s@CreateMedicalVocabularyResponse' {} Maybe Text
a -> CreateMedicalVocabularyResponse
s {$sel:vocabularyName:CreateMedicalVocabularyResponse' :: Maybe Text
vocabularyName = Maybe Text
a} :: CreateMedicalVocabularyResponse)

-- | The processing state of your custom medical vocabulary. If the state is
-- @READY@, you can use the custom vocabulary in a
-- @StartMedicalTranscriptionJob@ request.
createMedicalVocabularyResponse_vocabularyState :: Lens.Lens' CreateMedicalVocabularyResponse (Prelude.Maybe VocabularyState)
createMedicalVocabularyResponse_vocabularyState :: Lens' CreateMedicalVocabularyResponse (Maybe VocabularyState)
createMedicalVocabularyResponse_vocabularyState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMedicalVocabularyResponse' {Maybe VocabularyState
vocabularyState :: Maybe VocabularyState
$sel:vocabularyState:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe VocabularyState
vocabularyState} -> Maybe VocabularyState
vocabularyState) (\s :: CreateMedicalVocabularyResponse
s@CreateMedicalVocabularyResponse' {} Maybe VocabularyState
a -> CreateMedicalVocabularyResponse
s {$sel:vocabularyState:CreateMedicalVocabularyResponse' :: Maybe VocabularyState
vocabularyState = Maybe VocabularyState
a} :: CreateMedicalVocabularyResponse)

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

instance
  Prelude.NFData
    CreateMedicalVocabularyResponse
  where
  rnf :: CreateMedicalVocabularyResponse -> ()
rnf CreateMedicalVocabularyResponse' {Int
Maybe Text
Maybe POSIX
Maybe LanguageCode
Maybe VocabularyState
httpStatus :: Int
vocabularyState :: Maybe VocabularyState
vocabularyName :: Maybe Text
lastModifiedTime :: Maybe POSIX
languageCode :: Maybe LanguageCode
failureReason :: Maybe Text
$sel:httpStatus:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Int
$sel:vocabularyState:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe VocabularyState
$sel:vocabularyName:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe Text
$sel:lastModifiedTime:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe POSIX
$sel:languageCode:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe LanguageCode
$sel:failureReason:CreateMedicalVocabularyResponse' :: CreateMedicalVocabularyResponse -> Maybe Text
..} =
    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 POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vocabularyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VocabularyState
vocabularyState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus