{-# 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.CreateVocabularyFilter
-- 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 vocabulary filter.
--
-- You can use custom vocabulary filters to mask, delete, or flag specific
-- words from your transcript. Custom vocabulary filters are commonly used
-- to mask profanity in transcripts.
--
-- Each language has a character set that contains all allowed characters
-- for that specific language. If you use unsupported characters, your
-- custom vocabulary filter 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/vocabulary-filtering.html Vocabulary filtering>.
module Amazonka.Transcribe.CreateVocabularyFilter
  ( -- * Creating a Request
    CreateVocabularyFilter (..),
    newCreateVocabularyFilter,

    -- * Request Lenses
    createVocabularyFilter_tags,
    createVocabularyFilter_vocabularyFilterFileUri,
    createVocabularyFilter_words,
    createVocabularyFilter_vocabularyFilterName,
    createVocabularyFilter_languageCode,

    -- * Destructuring the Response
    CreateVocabularyFilterResponse (..),
    newCreateVocabularyFilterResponse,

    -- * Response Lenses
    createVocabularyFilterResponse_languageCode,
    createVocabularyFilterResponse_lastModifiedTime,
    createVocabularyFilterResponse_vocabularyFilterName,
    createVocabularyFilterResponse_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:/ 'newCreateVocabularyFilter' smart constructor.
data CreateVocabularyFilter = CreateVocabularyFilter'
  { -- | Adds one or more custom tags, each in the form of a key:value pair, to a
    -- new custom vocabulary filter at the time you create this new vocabulary
    -- filter.
    --
    -- To learn more about using tags with Amazon Transcribe, refer to
    -- <https://docs.aws.amazon.com/transcribe/latest/dg/tagging.html Tagging resources>.
    CreateVocabularyFilter -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The Amazon S3 location of the text file that contains your custom
    -- vocabulary filter terms. The URI must be located 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-filter-file.txt@
    --
    -- Note that if you include @VocabularyFilterFileUri@ in your request, you
    -- cannot use @Words@; you must choose one or the other.
    CreateVocabularyFilter -> Maybe Text
vocabularyFilterFileUri :: Prelude.Maybe Prelude.Text,
    -- | Use this parameter if you want to create your custom vocabulary filter
    -- by including all desired terms, as comma-separated values, within your
    -- request. The other option for creating your vocabulary filter is to save
    -- your entries in a text file and upload them to an Amazon S3 bucket, then
    -- specify the location of your file using the @VocabularyFilterFileUri@
    -- parameter.
    --
    -- Note that if you include @Words@ in your request, you cannot use
    -- @VocabularyFilterFileUri@; you must choose one or the other.
    --
    -- Each language has a character set that contains all allowed characters
    -- for that specific language. If you use unsupported characters, your
    -- custom vocabulary filter 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.
    CreateVocabularyFilter -> Maybe (NonEmpty Text)
words :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | A unique name, chosen by you, for your new custom vocabulary filter.
    --
    -- 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
    -- vocabulary filter with the same name as an existing custom vocabulary
    -- filter, you get a @ConflictException@ error.
    CreateVocabularyFilter -> Text
vocabularyFilterName :: Prelude.Text,
    -- | The language code that represents the language of the entries in your
    -- vocabulary filter. Each custom vocabulary filter must contain terms in
    -- only one language.
    --
    -- A custom vocabulary filter can only be used to transcribe files in the
    -- same language as the filter. For example, if you create a custom
    -- vocabulary filter using US English (@en-US@), you can only apply this
    -- filter to files that contain English audio.
    --
    -- For a list of supported languages and their associated language codes,
    -- refer to the
    -- <https://docs.aws.amazon.com/transcribe/latest/dg/supported-languages.html Supported languages>
    -- table.
    CreateVocabularyFilter -> LanguageCode
languageCode :: LanguageCode
  }
  deriving (CreateVocabularyFilter -> CreateVocabularyFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVocabularyFilter -> CreateVocabularyFilter -> Bool
$c/= :: CreateVocabularyFilter -> CreateVocabularyFilter -> Bool
== :: CreateVocabularyFilter -> CreateVocabularyFilter -> Bool
$c== :: CreateVocabularyFilter -> CreateVocabularyFilter -> Bool
Prelude.Eq, ReadPrec [CreateVocabularyFilter]
ReadPrec CreateVocabularyFilter
Int -> ReadS CreateVocabularyFilter
ReadS [CreateVocabularyFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVocabularyFilter]
$creadListPrec :: ReadPrec [CreateVocabularyFilter]
readPrec :: ReadPrec CreateVocabularyFilter
$creadPrec :: ReadPrec CreateVocabularyFilter
readList :: ReadS [CreateVocabularyFilter]
$creadList :: ReadS [CreateVocabularyFilter]
readsPrec :: Int -> ReadS CreateVocabularyFilter
$creadsPrec :: Int -> ReadS CreateVocabularyFilter
Prelude.Read, Int -> CreateVocabularyFilter -> ShowS
[CreateVocabularyFilter] -> ShowS
CreateVocabularyFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVocabularyFilter] -> ShowS
$cshowList :: [CreateVocabularyFilter] -> ShowS
show :: CreateVocabularyFilter -> String
$cshow :: CreateVocabularyFilter -> String
showsPrec :: Int -> CreateVocabularyFilter -> ShowS
$cshowsPrec :: Int -> CreateVocabularyFilter -> ShowS
Prelude.Show, forall x. Rep CreateVocabularyFilter x -> CreateVocabularyFilter
forall x. CreateVocabularyFilter -> Rep CreateVocabularyFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateVocabularyFilter x -> CreateVocabularyFilter
$cfrom :: forall x. CreateVocabularyFilter -> Rep CreateVocabularyFilter x
Prelude.Generic)

-- |
-- Create a value of 'CreateVocabularyFilter' 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', 'createVocabularyFilter_tags' - Adds one or more custom tags, each in the form of a key:value pair, to a
-- new custom vocabulary filter at the time you create this new vocabulary
-- filter.
--
-- To learn more about using tags with Amazon Transcribe, refer to
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tagging.html Tagging resources>.
--
-- 'vocabularyFilterFileUri', 'createVocabularyFilter_vocabularyFilterFileUri' - The Amazon S3 location of the text file that contains your custom
-- vocabulary filter terms. The URI must be located 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-filter-file.txt@
--
-- Note that if you include @VocabularyFilterFileUri@ in your request, you
-- cannot use @Words@; you must choose one or the other.
--
-- 'words', 'createVocabularyFilter_words' - Use this parameter if you want to create your custom vocabulary filter
-- by including all desired terms, as comma-separated values, within your
-- request. The other option for creating your vocabulary filter is to save
-- your entries in a text file and upload them to an Amazon S3 bucket, then
-- specify the location of your file using the @VocabularyFilterFileUri@
-- parameter.
--
-- Note that if you include @Words@ in your request, you cannot use
-- @VocabularyFilterFileUri@; you must choose one or the other.
--
-- Each language has a character set that contains all allowed characters
-- for that specific language. If you use unsupported characters, your
-- custom vocabulary filter 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.
--
-- 'vocabularyFilterName', 'createVocabularyFilter_vocabularyFilterName' - A unique name, chosen by you, for your new custom vocabulary filter.
--
-- 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
-- vocabulary filter with the same name as an existing custom vocabulary
-- filter, you get a @ConflictException@ error.
--
-- 'languageCode', 'createVocabularyFilter_languageCode' - The language code that represents the language of the entries in your
-- vocabulary filter. Each custom vocabulary filter must contain terms in
-- only one language.
--
-- A custom vocabulary filter can only be used to transcribe files in the
-- same language as the filter. For example, if you create a custom
-- vocabulary filter using US English (@en-US@), you can only apply this
-- filter to files that contain English audio.
--
-- For a list of supported languages and their associated language codes,
-- refer to the
-- <https://docs.aws.amazon.com/transcribe/latest/dg/supported-languages.html Supported languages>
-- table.
newCreateVocabularyFilter ::
  -- | 'vocabularyFilterName'
  Prelude.Text ->
  -- | 'languageCode'
  LanguageCode ->
  CreateVocabularyFilter
newCreateVocabularyFilter :: Text -> LanguageCode -> CreateVocabularyFilter
newCreateVocabularyFilter
  Text
pVocabularyFilterName_
  LanguageCode
pLanguageCode_ =
    CreateVocabularyFilter'
      { $sel:tags:CreateVocabularyFilter' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vocabularyFilterFileUri:CreateVocabularyFilter' :: Maybe Text
vocabularyFilterFileUri = forall a. Maybe a
Prelude.Nothing,
        $sel:words:CreateVocabularyFilter' :: Maybe (NonEmpty Text)
words = forall a. Maybe a
Prelude.Nothing,
        $sel:vocabularyFilterName:CreateVocabularyFilter' :: Text
vocabularyFilterName = Text
pVocabularyFilterName_,
        $sel:languageCode:CreateVocabularyFilter' :: LanguageCode
languageCode = LanguageCode
pLanguageCode_
      }

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

-- | The Amazon S3 location of the text file that contains your custom
-- vocabulary filter terms. The URI must be located 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-filter-file.txt@
--
-- Note that if you include @VocabularyFilterFileUri@ in your request, you
-- cannot use @Words@; you must choose one or the other.
createVocabularyFilter_vocabularyFilterFileUri :: Lens.Lens' CreateVocabularyFilter (Prelude.Maybe Prelude.Text)
createVocabularyFilter_vocabularyFilterFileUri :: Lens' CreateVocabularyFilter (Maybe Text)
createVocabularyFilter_vocabularyFilterFileUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilter' {Maybe Text
vocabularyFilterFileUri :: Maybe Text
$sel:vocabularyFilterFileUri:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe Text
vocabularyFilterFileUri} -> Maybe Text
vocabularyFilterFileUri) (\s :: CreateVocabularyFilter
s@CreateVocabularyFilter' {} Maybe Text
a -> CreateVocabularyFilter
s {$sel:vocabularyFilterFileUri:CreateVocabularyFilter' :: Maybe Text
vocabularyFilterFileUri = Maybe Text
a} :: CreateVocabularyFilter)

-- | Use this parameter if you want to create your custom vocabulary filter
-- by including all desired terms, as comma-separated values, within your
-- request. The other option for creating your vocabulary filter is to save
-- your entries in a text file and upload them to an Amazon S3 bucket, then
-- specify the location of your file using the @VocabularyFilterFileUri@
-- parameter.
--
-- Note that if you include @Words@ in your request, you cannot use
-- @VocabularyFilterFileUri@; you must choose one or the other.
--
-- Each language has a character set that contains all allowed characters
-- for that specific language. If you use unsupported characters, your
-- custom vocabulary filter 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.
createVocabularyFilter_words :: Lens.Lens' CreateVocabularyFilter (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
createVocabularyFilter_words :: Lens' CreateVocabularyFilter (Maybe (NonEmpty Text))
createVocabularyFilter_words = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilter' {Maybe (NonEmpty Text)
words :: Maybe (NonEmpty Text)
$sel:words:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe (NonEmpty Text)
words} -> Maybe (NonEmpty Text)
words) (\s :: CreateVocabularyFilter
s@CreateVocabularyFilter' {} Maybe (NonEmpty Text)
a -> CreateVocabularyFilter
s {$sel:words:CreateVocabularyFilter' :: Maybe (NonEmpty Text)
words = Maybe (NonEmpty Text)
a} :: CreateVocabularyFilter) 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 vocabulary filter.
--
-- 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
-- vocabulary filter with the same name as an existing custom vocabulary
-- filter, you get a @ConflictException@ error.
createVocabularyFilter_vocabularyFilterName :: Lens.Lens' CreateVocabularyFilter Prelude.Text
createVocabularyFilter_vocabularyFilterName :: Lens' CreateVocabularyFilter Text
createVocabularyFilter_vocabularyFilterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilter' {Text
vocabularyFilterName :: Text
$sel:vocabularyFilterName:CreateVocabularyFilter' :: CreateVocabularyFilter -> Text
vocabularyFilterName} -> Text
vocabularyFilterName) (\s :: CreateVocabularyFilter
s@CreateVocabularyFilter' {} Text
a -> CreateVocabularyFilter
s {$sel:vocabularyFilterName:CreateVocabularyFilter' :: Text
vocabularyFilterName = Text
a} :: CreateVocabularyFilter)

-- | The language code that represents the language of the entries in your
-- vocabulary filter. Each custom vocabulary filter must contain terms in
-- only one language.
--
-- A custom vocabulary filter can only be used to transcribe files in the
-- same language as the filter. For example, if you create a custom
-- vocabulary filter using US English (@en-US@), you can only apply this
-- filter to files that contain English audio.
--
-- For a list of supported languages and their associated language codes,
-- refer to the
-- <https://docs.aws.amazon.com/transcribe/latest/dg/supported-languages.html Supported languages>
-- table.
createVocabularyFilter_languageCode :: Lens.Lens' CreateVocabularyFilter LanguageCode
createVocabularyFilter_languageCode :: Lens' CreateVocabularyFilter LanguageCode
createVocabularyFilter_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilter' {LanguageCode
languageCode :: LanguageCode
$sel:languageCode:CreateVocabularyFilter' :: CreateVocabularyFilter -> LanguageCode
languageCode} -> LanguageCode
languageCode) (\s :: CreateVocabularyFilter
s@CreateVocabularyFilter' {} LanguageCode
a -> CreateVocabularyFilter
s {$sel:languageCode:CreateVocabularyFilter' :: LanguageCode
languageCode = LanguageCode
a} :: CreateVocabularyFilter)

instance Core.AWSRequest CreateVocabularyFilter where
  type
    AWSResponse CreateVocabularyFilter =
      CreateVocabularyFilterResponse
  request :: (Service -> Service)
-> CreateVocabularyFilter -> Request CreateVocabularyFilter
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 CreateVocabularyFilter
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateVocabularyFilter)))
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 LanguageCode
-> Maybe POSIX
-> Maybe Text
-> Int
-> CreateVocabularyFilterResponse
CreateVocabularyFilterResponse'
            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
"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
"VocabularyFilterName")
            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 CreateVocabularyFilter where
  hashWithSalt :: Int -> CreateVocabularyFilter -> Int
hashWithSalt Int
_salt CreateVocabularyFilter' {Maybe (NonEmpty Text)
Maybe (NonEmpty Tag)
Maybe Text
Text
LanguageCode
languageCode :: LanguageCode
vocabularyFilterName :: Text
words :: Maybe (NonEmpty Text)
vocabularyFilterFileUri :: Maybe Text
tags :: Maybe (NonEmpty Tag)
$sel:languageCode:CreateVocabularyFilter' :: CreateVocabularyFilter -> LanguageCode
$sel:vocabularyFilterName:CreateVocabularyFilter' :: CreateVocabularyFilter -> Text
$sel:words:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe (NonEmpty Text)
$sel:vocabularyFilterFileUri:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe Text
$sel:tags:CreateVocabularyFilter' :: CreateVocabularyFilter -> 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` Maybe Text
vocabularyFilterFileUri
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
words
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vocabularyFilterName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LanguageCode
languageCode

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

instance Data.ToHeaders CreateVocabularyFilter where
  toHeaders :: CreateVocabularyFilter -> 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.CreateVocabularyFilter" ::
                          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 CreateVocabularyFilter where
  toJSON :: CreateVocabularyFilter -> Value
toJSON CreateVocabularyFilter' {Maybe (NonEmpty Text)
Maybe (NonEmpty Tag)
Maybe Text
Text
LanguageCode
languageCode :: LanguageCode
vocabularyFilterName :: Text
words :: Maybe (NonEmpty Text)
vocabularyFilterFileUri :: Maybe Text
tags :: Maybe (NonEmpty Tag)
$sel:languageCode:CreateVocabularyFilter' :: CreateVocabularyFilter -> LanguageCode
$sel:vocabularyFilterName:CreateVocabularyFilter' :: CreateVocabularyFilter -> Text
$sel:words:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe (NonEmpty Text)
$sel:vocabularyFilterFileUri:CreateVocabularyFilter' :: CreateVocabularyFilter -> Maybe Text
$sel:tags:CreateVocabularyFilter' :: CreateVocabularyFilter -> 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,
            (Key
"VocabularyFilterFileUri" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
vocabularyFilterFileUri,
            (Key
"Words" 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 Text)
words,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"VocabularyFilterName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vocabularyFilterName
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"LanguageCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= LanguageCode
languageCode)
          ]
      )

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

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

-- | /See:/ 'newCreateVocabularyFilterResponse' smart constructor.
data CreateVocabularyFilterResponse = CreateVocabularyFilterResponse'
  { -- | The language code you selected for your custom vocabulary filter.
    CreateVocabularyFilterResponse -> Maybe LanguageCode
languageCode :: Prelude.Maybe LanguageCode,
    -- | The date and time you created your custom vocabulary filter.
    --
    -- 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.
    CreateVocabularyFilterResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name you chose for your custom vocabulary filter.
    CreateVocabularyFilterResponse -> Maybe Text
vocabularyFilterName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateVocabularyFilterResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateVocabularyFilterResponse
-> CreateVocabularyFilterResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVocabularyFilterResponse
-> CreateVocabularyFilterResponse -> Bool
$c/= :: CreateVocabularyFilterResponse
-> CreateVocabularyFilterResponse -> Bool
== :: CreateVocabularyFilterResponse
-> CreateVocabularyFilterResponse -> Bool
$c== :: CreateVocabularyFilterResponse
-> CreateVocabularyFilterResponse -> Bool
Prelude.Eq, ReadPrec [CreateVocabularyFilterResponse]
ReadPrec CreateVocabularyFilterResponse
Int -> ReadS CreateVocabularyFilterResponse
ReadS [CreateVocabularyFilterResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVocabularyFilterResponse]
$creadListPrec :: ReadPrec [CreateVocabularyFilterResponse]
readPrec :: ReadPrec CreateVocabularyFilterResponse
$creadPrec :: ReadPrec CreateVocabularyFilterResponse
readList :: ReadS [CreateVocabularyFilterResponse]
$creadList :: ReadS [CreateVocabularyFilterResponse]
readsPrec :: Int -> ReadS CreateVocabularyFilterResponse
$creadsPrec :: Int -> ReadS CreateVocabularyFilterResponse
Prelude.Read, Int -> CreateVocabularyFilterResponse -> ShowS
[CreateVocabularyFilterResponse] -> ShowS
CreateVocabularyFilterResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVocabularyFilterResponse] -> ShowS
$cshowList :: [CreateVocabularyFilterResponse] -> ShowS
show :: CreateVocabularyFilterResponse -> String
$cshow :: CreateVocabularyFilterResponse -> String
showsPrec :: Int -> CreateVocabularyFilterResponse -> ShowS
$cshowsPrec :: Int -> CreateVocabularyFilterResponse -> ShowS
Prelude.Show, forall x.
Rep CreateVocabularyFilterResponse x
-> CreateVocabularyFilterResponse
forall x.
CreateVocabularyFilterResponse
-> Rep CreateVocabularyFilterResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVocabularyFilterResponse x
-> CreateVocabularyFilterResponse
$cfrom :: forall x.
CreateVocabularyFilterResponse
-> Rep CreateVocabularyFilterResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateVocabularyFilterResponse' 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:
--
-- 'languageCode', 'createVocabularyFilterResponse_languageCode' - The language code you selected for your custom vocabulary filter.
--
-- 'lastModifiedTime', 'createVocabularyFilterResponse_lastModifiedTime' - The date and time you created your custom vocabulary filter.
--
-- 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.
--
-- 'vocabularyFilterName', 'createVocabularyFilterResponse_vocabularyFilterName' - The name you chose for your custom vocabulary filter.
--
-- 'httpStatus', 'createVocabularyFilterResponse_httpStatus' - The response's http status code.
newCreateVocabularyFilterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateVocabularyFilterResponse
newCreateVocabularyFilterResponse :: Int -> CreateVocabularyFilterResponse
newCreateVocabularyFilterResponse Int
pHttpStatus_ =
  CreateVocabularyFilterResponse'
    { $sel:languageCode:CreateVocabularyFilterResponse' :: Maybe LanguageCode
languageCode =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateVocabularyFilterResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:vocabularyFilterName:CreateVocabularyFilterResponse' :: Maybe Text
vocabularyFilterName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateVocabularyFilterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The language code you selected for your custom vocabulary filter.
createVocabularyFilterResponse_languageCode :: Lens.Lens' CreateVocabularyFilterResponse (Prelude.Maybe LanguageCode)
createVocabularyFilterResponse_languageCode :: Lens' CreateVocabularyFilterResponse (Maybe LanguageCode)
createVocabularyFilterResponse_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilterResponse' {Maybe LanguageCode
languageCode :: Maybe LanguageCode
$sel:languageCode:CreateVocabularyFilterResponse' :: CreateVocabularyFilterResponse -> Maybe LanguageCode
languageCode} -> Maybe LanguageCode
languageCode) (\s :: CreateVocabularyFilterResponse
s@CreateVocabularyFilterResponse' {} Maybe LanguageCode
a -> CreateVocabularyFilterResponse
s {$sel:languageCode:CreateVocabularyFilterResponse' :: Maybe LanguageCode
languageCode = Maybe LanguageCode
a} :: CreateVocabularyFilterResponse)

-- | The date and time you created your custom vocabulary filter.
--
-- 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.
createVocabularyFilterResponse_lastModifiedTime :: Lens.Lens' CreateVocabularyFilterResponse (Prelude.Maybe Prelude.UTCTime)
createVocabularyFilterResponse_lastModifiedTime :: Lens' CreateVocabularyFilterResponse (Maybe UTCTime)
createVocabularyFilterResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilterResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateVocabularyFilterResponse' :: CreateVocabularyFilterResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateVocabularyFilterResponse
s@CreateVocabularyFilterResponse' {} Maybe POSIX
a -> CreateVocabularyFilterResponse
s {$sel:lastModifiedTime:CreateVocabularyFilterResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateVocabularyFilterResponse) 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 vocabulary filter.
createVocabularyFilterResponse_vocabularyFilterName :: Lens.Lens' CreateVocabularyFilterResponse (Prelude.Maybe Prelude.Text)
createVocabularyFilterResponse_vocabularyFilterName :: Lens' CreateVocabularyFilterResponse (Maybe Text)
createVocabularyFilterResponse_vocabularyFilterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVocabularyFilterResponse' {Maybe Text
vocabularyFilterName :: Maybe Text
$sel:vocabularyFilterName:CreateVocabularyFilterResponse' :: CreateVocabularyFilterResponse -> Maybe Text
vocabularyFilterName} -> Maybe Text
vocabularyFilterName) (\s :: CreateVocabularyFilterResponse
s@CreateVocabularyFilterResponse' {} Maybe Text
a -> CreateVocabularyFilterResponse
s {$sel:vocabularyFilterName:CreateVocabularyFilterResponse' :: Maybe Text
vocabularyFilterName = Maybe Text
a} :: CreateVocabularyFilterResponse)

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

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