{-# 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.SESV2.Types.VdmAttributes
-- 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.SESV2.Types.VdmAttributes 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.SESV2.Types.DashboardAttributes
import Amazonka.SESV2.Types.FeatureStatus
import Amazonka.SESV2.Types.GuardianAttributes

-- | The VDM attributes that apply to your Amazon SES account.
--
-- /See:/ 'newVdmAttributes' smart constructor.
data VdmAttributes = VdmAttributes'
  { -- | Specifies additional settings for your VDM configuration as applicable
    -- to the Dashboard.
    VdmAttributes -> Maybe DashboardAttributes
dashboardAttributes :: Prelude.Maybe DashboardAttributes,
    -- | Specifies additional settings for your VDM configuration as applicable
    -- to the Guardian.
    VdmAttributes -> Maybe GuardianAttributes
guardianAttributes :: Prelude.Maybe GuardianAttributes,
    -- | Specifies the status of your VDM configuration. Can be one of the
    -- following:
    --
    -- -   @ENABLED@ – Amazon SES enables VDM for your account.
    --
    -- -   @DISABLED@ – Amazon SES disables VDM for your account.
    VdmAttributes -> FeatureStatus
vdmEnabled :: FeatureStatus
  }
  deriving (VdmAttributes -> VdmAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VdmAttributes -> VdmAttributes -> Bool
$c/= :: VdmAttributes -> VdmAttributes -> Bool
== :: VdmAttributes -> VdmAttributes -> Bool
$c== :: VdmAttributes -> VdmAttributes -> Bool
Prelude.Eq, ReadPrec [VdmAttributes]
ReadPrec VdmAttributes
Int -> ReadS VdmAttributes
ReadS [VdmAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VdmAttributes]
$creadListPrec :: ReadPrec [VdmAttributes]
readPrec :: ReadPrec VdmAttributes
$creadPrec :: ReadPrec VdmAttributes
readList :: ReadS [VdmAttributes]
$creadList :: ReadS [VdmAttributes]
readsPrec :: Int -> ReadS VdmAttributes
$creadsPrec :: Int -> ReadS VdmAttributes
Prelude.Read, Int -> VdmAttributes -> ShowS
[VdmAttributes] -> ShowS
VdmAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VdmAttributes] -> ShowS
$cshowList :: [VdmAttributes] -> ShowS
show :: VdmAttributes -> String
$cshow :: VdmAttributes -> String
showsPrec :: Int -> VdmAttributes -> ShowS
$cshowsPrec :: Int -> VdmAttributes -> ShowS
Prelude.Show, forall x. Rep VdmAttributes x -> VdmAttributes
forall x. VdmAttributes -> Rep VdmAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VdmAttributes x -> VdmAttributes
$cfrom :: forall x. VdmAttributes -> Rep VdmAttributes x
Prelude.Generic)

-- |
-- Create a value of 'VdmAttributes' 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:
--
-- 'dashboardAttributes', 'vdmAttributes_dashboardAttributes' - Specifies additional settings for your VDM configuration as applicable
-- to the Dashboard.
--
-- 'guardianAttributes', 'vdmAttributes_guardianAttributes' - Specifies additional settings for your VDM configuration as applicable
-- to the Guardian.
--
-- 'vdmEnabled', 'vdmAttributes_vdmEnabled' - Specifies the status of your VDM configuration. Can be one of the
-- following:
--
-- -   @ENABLED@ – Amazon SES enables VDM for your account.
--
-- -   @DISABLED@ – Amazon SES disables VDM for your account.
newVdmAttributes ::
  -- | 'vdmEnabled'
  FeatureStatus ->
  VdmAttributes
newVdmAttributes :: FeatureStatus -> VdmAttributes
newVdmAttributes FeatureStatus
pVdmEnabled_ =
  VdmAttributes'
    { $sel:dashboardAttributes:VdmAttributes' :: Maybe DashboardAttributes
dashboardAttributes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:guardianAttributes:VdmAttributes' :: Maybe GuardianAttributes
guardianAttributes = forall a. Maybe a
Prelude.Nothing,
      $sel:vdmEnabled:VdmAttributes' :: FeatureStatus
vdmEnabled = FeatureStatus
pVdmEnabled_
    }

-- | Specifies additional settings for your VDM configuration as applicable
-- to the Dashboard.
vdmAttributes_dashboardAttributes :: Lens.Lens' VdmAttributes (Prelude.Maybe DashboardAttributes)
vdmAttributes_dashboardAttributes :: Lens' VdmAttributes (Maybe DashboardAttributes)
vdmAttributes_dashboardAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VdmAttributes' {Maybe DashboardAttributes
dashboardAttributes :: Maybe DashboardAttributes
$sel:dashboardAttributes:VdmAttributes' :: VdmAttributes -> Maybe DashboardAttributes
dashboardAttributes} -> Maybe DashboardAttributes
dashboardAttributes) (\s :: VdmAttributes
s@VdmAttributes' {} Maybe DashboardAttributes
a -> VdmAttributes
s {$sel:dashboardAttributes:VdmAttributes' :: Maybe DashboardAttributes
dashboardAttributes = Maybe DashboardAttributes
a} :: VdmAttributes)

-- | Specifies additional settings for your VDM configuration as applicable
-- to the Guardian.
vdmAttributes_guardianAttributes :: Lens.Lens' VdmAttributes (Prelude.Maybe GuardianAttributes)
vdmAttributes_guardianAttributes :: Lens' VdmAttributes (Maybe GuardianAttributes)
vdmAttributes_guardianAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VdmAttributes' {Maybe GuardianAttributes
guardianAttributes :: Maybe GuardianAttributes
$sel:guardianAttributes:VdmAttributes' :: VdmAttributes -> Maybe GuardianAttributes
guardianAttributes} -> Maybe GuardianAttributes
guardianAttributes) (\s :: VdmAttributes
s@VdmAttributes' {} Maybe GuardianAttributes
a -> VdmAttributes
s {$sel:guardianAttributes:VdmAttributes' :: Maybe GuardianAttributes
guardianAttributes = Maybe GuardianAttributes
a} :: VdmAttributes)

-- | Specifies the status of your VDM configuration. Can be one of the
-- following:
--
-- -   @ENABLED@ – Amazon SES enables VDM for your account.
--
-- -   @DISABLED@ – Amazon SES disables VDM for your account.
vdmAttributes_vdmEnabled :: Lens.Lens' VdmAttributes FeatureStatus
vdmAttributes_vdmEnabled :: Lens' VdmAttributes FeatureStatus
vdmAttributes_vdmEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VdmAttributes' {FeatureStatus
vdmEnabled :: FeatureStatus
$sel:vdmEnabled:VdmAttributes' :: VdmAttributes -> FeatureStatus
vdmEnabled} -> FeatureStatus
vdmEnabled) (\s :: VdmAttributes
s@VdmAttributes' {} FeatureStatus
a -> VdmAttributes
s {$sel:vdmEnabled:VdmAttributes' :: FeatureStatus
vdmEnabled = FeatureStatus
a} :: VdmAttributes)

instance Data.FromJSON VdmAttributes where
  parseJSON :: Value -> Parser VdmAttributes
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"VdmAttributes"
      ( \Object
x ->
          Maybe DashboardAttributes
-> Maybe GuardianAttributes -> FeatureStatus -> VdmAttributes
VdmAttributes'
            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
"DashboardAttributes")
            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
"GuardianAttributes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"VdmEnabled")
      )

instance Prelude.Hashable VdmAttributes where
  hashWithSalt :: Int -> VdmAttributes -> Int
hashWithSalt Int
_salt VdmAttributes' {Maybe DashboardAttributes
Maybe GuardianAttributes
FeatureStatus
vdmEnabled :: FeatureStatus
guardianAttributes :: Maybe GuardianAttributes
dashboardAttributes :: Maybe DashboardAttributes
$sel:vdmEnabled:VdmAttributes' :: VdmAttributes -> FeatureStatus
$sel:guardianAttributes:VdmAttributes' :: VdmAttributes -> Maybe GuardianAttributes
$sel:dashboardAttributes:VdmAttributes' :: VdmAttributes -> Maybe DashboardAttributes
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashboardAttributes
dashboardAttributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GuardianAttributes
guardianAttributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` FeatureStatus
vdmEnabled

instance Prelude.NFData VdmAttributes where
  rnf :: VdmAttributes -> ()
rnf VdmAttributes' {Maybe DashboardAttributes
Maybe GuardianAttributes
FeatureStatus
vdmEnabled :: FeatureStatus
guardianAttributes :: Maybe GuardianAttributes
dashboardAttributes :: Maybe DashboardAttributes
$sel:vdmEnabled:VdmAttributes' :: VdmAttributes -> FeatureStatus
$sel:guardianAttributes:VdmAttributes' :: VdmAttributes -> Maybe GuardianAttributes
$sel:dashboardAttributes:VdmAttributes' :: VdmAttributes -> Maybe DashboardAttributes
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DashboardAttributes
dashboardAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GuardianAttributes
guardianAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf FeatureStatus
vdmEnabled

instance Data.ToJSON VdmAttributes where
  toJSON :: VdmAttributes -> Value
toJSON VdmAttributes' {Maybe DashboardAttributes
Maybe GuardianAttributes
FeatureStatus
vdmEnabled :: FeatureStatus
guardianAttributes :: Maybe GuardianAttributes
dashboardAttributes :: Maybe DashboardAttributes
$sel:vdmEnabled:VdmAttributes' :: VdmAttributes -> FeatureStatus
$sel:guardianAttributes:VdmAttributes' :: VdmAttributes -> Maybe GuardianAttributes
$sel:dashboardAttributes:VdmAttributes' :: VdmAttributes -> Maybe DashboardAttributes
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DashboardAttributes" 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 DashboardAttributes
dashboardAttributes,
            (Key
"GuardianAttributes" 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 GuardianAttributes
guardianAttributes,
            forall a. a -> Maybe a
Prelude.Just (Key
"VdmEnabled" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= FeatureStatus
vdmEnabled)
          ]
      )