{-# 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.Translate.Types.TranslationSettings
-- 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.Translate.Types.TranslationSettings 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.Translate.Types.Formality
import Amazonka.Translate.Types.Profanity

-- | Optional settings that configure the translation output. Use these
-- settings for real time translations and asynchronous translation jobs.
--
-- /See:/ 'newTranslationSettings' smart constructor.
data TranslationSettings = TranslationSettings'
  { -- | You can optionally specify the desired level of formality for
    -- translations to supported target languages. The formality setting
    -- controls the level of formal language usage (also known as
    -- <https://en.wikipedia.org/wiki/Register_(sociolinguistics) register>) in
    -- the translation output. You can set the value to informal or formal. If
    -- you don\'t specify a value for formality, or if the target language
    -- doesn\'t support formality, the translation will ignore the formality
    -- setting.
    --
    -- If you specify multiple target languages for the job, translate ignores
    -- the formality setting for any unsupported target language.
    --
    -- For a list of target languages that support formality, see
    -- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-formality.html#customizing-translations-formality-languages Supported languages>
    -- in the Amazon Translate Developer Guide.
    TranslationSettings -> Maybe Formality
formality :: Prelude.Maybe Formality,
    -- | Enable the profanity setting if you want Amazon Translate to mask
    -- profane words and phrases in your translation output.
    --
    -- To mask profane words and phrases, Amazon Translate replaces them with
    -- the grawlix string “?$#\@$“. This 5-character sequence is used for each
    -- profane word or phrase, regardless of the length or number of words.
    --
    -- Amazon Translate doesn\'t detect profanity in all of its supported
    -- languages. For languages that don\'t support profanity detection, see
    -- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-profanity.html#customizing-translations-profanity-languages Unsupported languages>
    -- in the Amazon Translate Developer Guide.
    --
    -- If you specify multiple target languages for the job, all the target
    -- languages must support profanity masking. If any of the target languages
    -- don\'t support profanity masking, the translation job won\'t mask
    -- profanity for any target language.
    TranslationSettings -> Maybe Profanity
profanity :: Prelude.Maybe Profanity
  }
  deriving (TranslationSettings -> TranslationSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TranslationSettings -> TranslationSettings -> Bool
$c/= :: TranslationSettings -> TranslationSettings -> Bool
== :: TranslationSettings -> TranslationSettings -> Bool
$c== :: TranslationSettings -> TranslationSettings -> Bool
Prelude.Eq, ReadPrec [TranslationSettings]
ReadPrec TranslationSettings
Int -> ReadS TranslationSettings
ReadS [TranslationSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TranslationSettings]
$creadListPrec :: ReadPrec [TranslationSettings]
readPrec :: ReadPrec TranslationSettings
$creadPrec :: ReadPrec TranslationSettings
readList :: ReadS [TranslationSettings]
$creadList :: ReadS [TranslationSettings]
readsPrec :: Int -> ReadS TranslationSettings
$creadsPrec :: Int -> ReadS TranslationSettings
Prelude.Read, Int -> TranslationSettings -> ShowS
[TranslationSettings] -> ShowS
TranslationSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TranslationSettings] -> ShowS
$cshowList :: [TranslationSettings] -> ShowS
show :: TranslationSettings -> String
$cshow :: TranslationSettings -> String
showsPrec :: Int -> TranslationSettings -> ShowS
$cshowsPrec :: Int -> TranslationSettings -> ShowS
Prelude.Show, forall x. Rep TranslationSettings x -> TranslationSettings
forall x. TranslationSettings -> Rep TranslationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TranslationSettings x -> TranslationSettings
$cfrom :: forall x. TranslationSettings -> Rep TranslationSettings x
Prelude.Generic)

-- |
-- Create a value of 'TranslationSettings' 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:
--
-- 'formality', 'translationSettings_formality' - You can optionally specify the desired level of formality for
-- translations to supported target languages. The formality setting
-- controls the level of formal language usage (also known as
-- <https://en.wikipedia.org/wiki/Register_(sociolinguistics) register>) in
-- the translation output. You can set the value to informal or formal. If
-- you don\'t specify a value for formality, or if the target language
-- doesn\'t support formality, the translation will ignore the formality
-- setting.
--
-- If you specify multiple target languages for the job, translate ignores
-- the formality setting for any unsupported target language.
--
-- For a list of target languages that support formality, see
-- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-formality.html#customizing-translations-formality-languages Supported languages>
-- in the Amazon Translate Developer Guide.
--
-- 'profanity', 'translationSettings_profanity' - Enable the profanity setting if you want Amazon Translate to mask
-- profane words and phrases in your translation output.
--
-- To mask profane words and phrases, Amazon Translate replaces them with
-- the grawlix string “?$#\@$“. This 5-character sequence is used for each
-- profane word or phrase, regardless of the length or number of words.
--
-- Amazon Translate doesn\'t detect profanity in all of its supported
-- languages. For languages that don\'t support profanity detection, see
-- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-profanity.html#customizing-translations-profanity-languages Unsupported languages>
-- in the Amazon Translate Developer Guide.
--
-- If you specify multiple target languages for the job, all the target
-- languages must support profanity masking. If any of the target languages
-- don\'t support profanity masking, the translation job won\'t mask
-- profanity for any target language.
newTranslationSettings ::
  TranslationSettings
newTranslationSettings :: TranslationSettings
newTranslationSettings =
  TranslationSettings'
    { $sel:formality:TranslationSettings' :: Maybe Formality
formality = forall a. Maybe a
Prelude.Nothing,
      $sel:profanity:TranslationSettings' :: Maybe Profanity
profanity = forall a. Maybe a
Prelude.Nothing
    }

-- | You can optionally specify the desired level of formality for
-- translations to supported target languages. The formality setting
-- controls the level of formal language usage (also known as
-- <https://en.wikipedia.org/wiki/Register_(sociolinguistics) register>) in
-- the translation output. You can set the value to informal or formal. If
-- you don\'t specify a value for formality, or if the target language
-- doesn\'t support formality, the translation will ignore the formality
-- setting.
--
-- If you specify multiple target languages for the job, translate ignores
-- the formality setting for any unsupported target language.
--
-- For a list of target languages that support formality, see
-- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-formality.html#customizing-translations-formality-languages Supported languages>
-- in the Amazon Translate Developer Guide.
translationSettings_formality :: Lens.Lens' TranslationSettings (Prelude.Maybe Formality)
translationSettings_formality :: Lens' TranslationSettings (Maybe Formality)
translationSettings_formality = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranslationSettings' {Maybe Formality
formality :: Maybe Formality
$sel:formality:TranslationSettings' :: TranslationSettings -> Maybe Formality
formality} -> Maybe Formality
formality) (\s :: TranslationSettings
s@TranslationSettings' {} Maybe Formality
a -> TranslationSettings
s {$sel:formality:TranslationSettings' :: Maybe Formality
formality = Maybe Formality
a} :: TranslationSettings)

-- | Enable the profanity setting if you want Amazon Translate to mask
-- profane words and phrases in your translation output.
--
-- To mask profane words and phrases, Amazon Translate replaces them with
-- the grawlix string “?$#\@$“. This 5-character sequence is used for each
-- profane word or phrase, regardless of the length or number of words.
--
-- Amazon Translate doesn\'t detect profanity in all of its supported
-- languages. For languages that don\'t support profanity detection, see
-- <https://docs.aws.amazon.com/translate/latest/dg/customizing-translations-profanity.html#customizing-translations-profanity-languages Unsupported languages>
-- in the Amazon Translate Developer Guide.
--
-- If you specify multiple target languages for the job, all the target
-- languages must support profanity masking. If any of the target languages
-- don\'t support profanity masking, the translation job won\'t mask
-- profanity for any target language.
translationSettings_profanity :: Lens.Lens' TranslationSettings (Prelude.Maybe Profanity)
translationSettings_profanity :: Lens' TranslationSettings (Maybe Profanity)
translationSettings_profanity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TranslationSettings' {Maybe Profanity
profanity :: Maybe Profanity
$sel:profanity:TranslationSettings' :: TranslationSettings -> Maybe Profanity
profanity} -> Maybe Profanity
profanity) (\s :: TranslationSettings
s@TranslationSettings' {} Maybe Profanity
a -> TranslationSettings
s {$sel:profanity:TranslationSettings' :: Maybe Profanity
profanity = Maybe Profanity
a} :: TranslationSettings)

instance Data.FromJSON TranslationSettings where
  parseJSON :: Value -> Parser TranslationSettings
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TranslationSettings"
      ( \Object
x ->
          Maybe Formality -> Maybe Profanity -> TranslationSettings
TranslationSettings'
            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
"Formality")
            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
"Profanity")
      )

instance Prelude.Hashable TranslationSettings where
  hashWithSalt :: Int -> TranslationSettings -> Int
hashWithSalt Int
_salt TranslationSettings' {Maybe Formality
Maybe Profanity
profanity :: Maybe Profanity
formality :: Maybe Formality
$sel:profanity:TranslationSettings' :: TranslationSettings -> Maybe Profanity
$sel:formality:TranslationSettings' :: TranslationSettings -> Maybe Formality
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Formality
formality
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Profanity
profanity

instance Prelude.NFData TranslationSettings where
  rnf :: TranslationSettings -> ()
rnf TranslationSettings' {Maybe Formality
Maybe Profanity
profanity :: Maybe Profanity
formality :: Maybe Formality
$sel:profanity:TranslationSettings' :: TranslationSettings -> Maybe Profanity
$sel:formality:TranslationSettings' :: TranslationSettings -> Maybe Formality
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Formality
formality
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Profanity
profanity

instance Data.ToJSON TranslationSettings where
  toJSON :: TranslationSettings -> Value
toJSON TranslationSettings' {Maybe Formality
Maybe Profanity
profanity :: Maybe Profanity
formality :: Maybe Formality
$sel:profanity:TranslationSettings' :: TranslationSettings -> Maybe Profanity
$sel:formality:TranslationSettings' :: TranslationSettings -> Maybe Formality
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Formality" 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 Formality
formality,
            (Key
"Profanity" 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 Profanity
profanity
          ]
      )