{-# 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.SES.DescribeConfigurationSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the details of the specified configuration set. For information
-- about using configuration sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Amazon SES Developer Guide>.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.DescribeConfigurationSet
  ( -- * Creating a Request
    DescribeConfigurationSet (..),
    newDescribeConfigurationSet,

    -- * Request Lenses
    describeConfigurationSet_configurationSetAttributeNames,
    describeConfigurationSet_configurationSetName,

    -- * Destructuring the Response
    DescribeConfigurationSetResponse (..),
    newDescribeConfigurationSetResponse,

    -- * Response Lenses
    describeConfigurationSetResponse_configurationSet,
    describeConfigurationSetResponse_deliveryOptions,
    describeConfigurationSetResponse_eventDestinations,
    describeConfigurationSetResponse_reputationOptions,
    describeConfigurationSetResponse_trackingOptions,
    describeConfigurationSetResponse_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.SES.Types

-- | Represents a request to return the details of a configuration set.
-- Configuration sets enable you to publish email sending events. For
-- information about using configuration sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Amazon SES Developer Guide>.
--
-- /See:/ 'newDescribeConfigurationSet' smart constructor.
data DescribeConfigurationSet = DescribeConfigurationSet'
  { -- | A list of configuration set attributes to return.
    DescribeConfigurationSet -> Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames :: Prelude.Maybe [ConfigurationSetAttribute],
    -- | The name of the configuration set to describe.
    DescribeConfigurationSet -> Text
configurationSetName :: Prelude.Text
  }
  deriving (DescribeConfigurationSet -> DescribeConfigurationSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfigurationSet -> DescribeConfigurationSet -> Bool
$c/= :: DescribeConfigurationSet -> DescribeConfigurationSet -> Bool
== :: DescribeConfigurationSet -> DescribeConfigurationSet -> Bool
$c== :: DescribeConfigurationSet -> DescribeConfigurationSet -> Bool
Prelude.Eq, ReadPrec [DescribeConfigurationSet]
ReadPrec DescribeConfigurationSet
Int -> ReadS DescribeConfigurationSet
ReadS [DescribeConfigurationSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfigurationSet]
$creadListPrec :: ReadPrec [DescribeConfigurationSet]
readPrec :: ReadPrec DescribeConfigurationSet
$creadPrec :: ReadPrec DescribeConfigurationSet
readList :: ReadS [DescribeConfigurationSet]
$creadList :: ReadS [DescribeConfigurationSet]
readsPrec :: Int -> ReadS DescribeConfigurationSet
$creadsPrec :: Int -> ReadS DescribeConfigurationSet
Prelude.Read, Int -> DescribeConfigurationSet -> ShowS
[DescribeConfigurationSet] -> ShowS
DescribeConfigurationSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfigurationSet] -> ShowS
$cshowList :: [DescribeConfigurationSet] -> ShowS
show :: DescribeConfigurationSet -> String
$cshow :: DescribeConfigurationSet -> String
showsPrec :: Int -> DescribeConfigurationSet -> ShowS
$cshowsPrec :: Int -> DescribeConfigurationSet -> ShowS
Prelude.Show, forall x.
Rep DescribeConfigurationSet x -> DescribeConfigurationSet
forall x.
DescribeConfigurationSet -> Rep DescribeConfigurationSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConfigurationSet x -> DescribeConfigurationSet
$cfrom :: forall x.
DescribeConfigurationSet -> Rep DescribeConfigurationSet x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfigurationSet' 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:
--
-- 'configurationSetAttributeNames', 'describeConfigurationSet_configurationSetAttributeNames' - A list of configuration set attributes to return.
--
-- 'configurationSetName', 'describeConfigurationSet_configurationSetName' - The name of the configuration set to describe.
newDescribeConfigurationSet ::
  -- | 'configurationSetName'
  Prelude.Text ->
  DescribeConfigurationSet
newDescribeConfigurationSet :: Text -> DescribeConfigurationSet
newDescribeConfigurationSet Text
pConfigurationSetName_ =
  DescribeConfigurationSet'
    { $sel:configurationSetAttributeNames:DescribeConfigurationSet' :: Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSetName:DescribeConfigurationSet' :: Text
configurationSetName = Text
pConfigurationSetName_
    }

-- | A list of configuration set attributes to return.
describeConfigurationSet_configurationSetAttributeNames :: Lens.Lens' DescribeConfigurationSet (Prelude.Maybe [ConfigurationSetAttribute])
describeConfigurationSet_configurationSetAttributeNames :: Lens' DescribeConfigurationSet (Maybe [ConfigurationSetAttribute])
describeConfigurationSet_configurationSetAttributeNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSet' {Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames :: Maybe [ConfigurationSetAttribute]
$sel:configurationSetAttributeNames:DescribeConfigurationSet' :: DescribeConfigurationSet -> Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames} -> Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames) (\s :: DescribeConfigurationSet
s@DescribeConfigurationSet' {} Maybe [ConfigurationSetAttribute]
a -> DescribeConfigurationSet
s {$sel:configurationSetAttributeNames:DescribeConfigurationSet' :: Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames = Maybe [ConfigurationSetAttribute]
a} :: DescribeConfigurationSet) 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 name of the configuration set to describe.
describeConfigurationSet_configurationSetName :: Lens.Lens' DescribeConfigurationSet Prelude.Text
describeConfigurationSet_configurationSetName :: Lens' DescribeConfigurationSet Text
describeConfigurationSet_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:DescribeConfigurationSet' :: DescribeConfigurationSet -> Text
configurationSetName} -> Text
configurationSetName) (\s :: DescribeConfigurationSet
s@DescribeConfigurationSet' {} Text
a -> DescribeConfigurationSet
s {$sel:configurationSetName:DescribeConfigurationSet' :: Text
configurationSetName = Text
a} :: DescribeConfigurationSet)

instance Core.AWSRequest DescribeConfigurationSet where
  type
    AWSResponse DescribeConfigurationSet =
      DescribeConfigurationSetResponse
  request :: (Service -> Service)
-> DescribeConfigurationSet -> Request DescribeConfigurationSet
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeConfigurationSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConfigurationSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeConfigurationSetResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ConfigurationSet
-> Maybe DeliveryOptions
-> Maybe [EventDestination]
-> Maybe ReputationOptions
-> Maybe TrackingOptions
-> Int
-> DescribeConfigurationSetResponse
DescribeConfigurationSetResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ConfigurationSet")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DeliveryOptions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EventDestinations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReputationOptions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TrackingOptions")
            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 DescribeConfigurationSet where
  hashWithSalt :: Int -> DescribeConfigurationSet -> Int
hashWithSalt Int
_salt DescribeConfigurationSet' {Maybe [ConfigurationSetAttribute]
Text
configurationSetName :: Text
configurationSetAttributeNames :: Maybe [ConfigurationSetAttribute]
$sel:configurationSetName:DescribeConfigurationSet' :: DescribeConfigurationSet -> Text
$sel:configurationSetAttributeNames:DescribeConfigurationSet' :: DescribeConfigurationSet -> Maybe [ConfigurationSetAttribute]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName

instance Prelude.NFData DescribeConfigurationSet where
  rnf :: DescribeConfigurationSet -> ()
rnf DescribeConfigurationSet' {Maybe [ConfigurationSetAttribute]
Text
configurationSetName :: Text
configurationSetAttributeNames :: Maybe [ConfigurationSetAttribute]
$sel:configurationSetName:DescribeConfigurationSet' :: DescribeConfigurationSet -> Text
$sel:configurationSetAttributeNames:DescribeConfigurationSet' :: DescribeConfigurationSet -> Maybe [ConfigurationSetAttribute]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationSetName

instance Data.ToHeaders DescribeConfigurationSet where
  toHeaders :: DescribeConfigurationSet -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeConfigurationSet where
  toQuery :: DescribeConfigurationSet -> QueryString
toQuery DescribeConfigurationSet' {Maybe [ConfigurationSetAttribute]
Text
configurationSetName :: Text
configurationSetAttributeNames :: Maybe [ConfigurationSetAttribute]
$sel:configurationSetName:DescribeConfigurationSet' :: DescribeConfigurationSet -> Text
$sel:configurationSetAttributeNames:DescribeConfigurationSet' :: DescribeConfigurationSet -> Maybe [ConfigurationSetAttribute]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeConfigurationSet" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"ConfigurationSetAttributeNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ConfigurationSetAttribute]
configurationSetAttributeNames
            ),
        ByteString
"ConfigurationSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
configurationSetName
      ]

-- | Represents the details of a configuration set. Configuration sets enable
-- you to publish email sending events. For information about using
-- configuration sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Amazon SES Developer Guide>.
--
-- /See:/ 'newDescribeConfigurationSetResponse' smart constructor.
data DescribeConfigurationSetResponse = DescribeConfigurationSetResponse'
  { -- | The configuration set object associated with the specified configuration
    -- set.
    DescribeConfigurationSetResponse -> Maybe ConfigurationSet
configurationSet :: Prelude.Maybe ConfigurationSet,
    DescribeConfigurationSetResponse -> Maybe DeliveryOptions
deliveryOptions :: Prelude.Maybe DeliveryOptions,
    -- | A list of event destinations associated with the configuration set.
    DescribeConfigurationSetResponse -> Maybe [EventDestination]
eventDestinations :: Prelude.Maybe [EventDestination],
    -- | An object that represents the reputation settings for the configuration
    -- set.
    DescribeConfigurationSetResponse -> Maybe ReputationOptions
reputationOptions :: Prelude.Maybe ReputationOptions,
    -- | The name of the custom open and click tracking domain associated with
    -- the configuration set.
    DescribeConfigurationSetResponse -> Maybe TrackingOptions
trackingOptions :: Prelude.Maybe TrackingOptions,
    -- | The response's http status code.
    DescribeConfigurationSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConfigurationSetResponse
-> DescribeConfigurationSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfigurationSetResponse
-> DescribeConfigurationSetResponse -> Bool
$c/= :: DescribeConfigurationSetResponse
-> DescribeConfigurationSetResponse -> Bool
== :: DescribeConfigurationSetResponse
-> DescribeConfigurationSetResponse -> Bool
$c== :: DescribeConfigurationSetResponse
-> DescribeConfigurationSetResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConfigurationSetResponse]
ReadPrec DescribeConfigurationSetResponse
Int -> ReadS DescribeConfigurationSetResponse
ReadS [DescribeConfigurationSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfigurationSetResponse]
$creadListPrec :: ReadPrec [DescribeConfigurationSetResponse]
readPrec :: ReadPrec DescribeConfigurationSetResponse
$creadPrec :: ReadPrec DescribeConfigurationSetResponse
readList :: ReadS [DescribeConfigurationSetResponse]
$creadList :: ReadS [DescribeConfigurationSetResponse]
readsPrec :: Int -> ReadS DescribeConfigurationSetResponse
$creadsPrec :: Int -> ReadS DescribeConfigurationSetResponse
Prelude.Read, Int -> DescribeConfigurationSetResponse -> ShowS
[DescribeConfigurationSetResponse] -> ShowS
DescribeConfigurationSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfigurationSetResponse] -> ShowS
$cshowList :: [DescribeConfigurationSetResponse] -> ShowS
show :: DescribeConfigurationSetResponse -> String
$cshow :: DescribeConfigurationSetResponse -> String
showsPrec :: Int -> DescribeConfigurationSetResponse -> ShowS
$cshowsPrec :: Int -> DescribeConfigurationSetResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConfigurationSetResponse x
-> DescribeConfigurationSetResponse
forall x.
DescribeConfigurationSetResponse
-> Rep DescribeConfigurationSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConfigurationSetResponse x
-> DescribeConfigurationSetResponse
$cfrom :: forall x.
DescribeConfigurationSetResponse
-> Rep DescribeConfigurationSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfigurationSetResponse' 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:
--
-- 'configurationSet', 'describeConfigurationSetResponse_configurationSet' - The configuration set object associated with the specified configuration
-- set.
--
-- 'deliveryOptions', 'describeConfigurationSetResponse_deliveryOptions' - Undocumented member.
--
-- 'eventDestinations', 'describeConfigurationSetResponse_eventDestinations' - A list of event destinations associated with the configuration set.
--
-- 'reputationOptions', 'describeConfigurationSetResponse_reputationOptions' - An object that represents the reputation settings for the configuration
-- set.
--
-- 'trackingOptions', 'describeConfigurationSetResponse_trackingOptions' - The name of the custom open and click tracking domain associated with
-- the configuration set.
--
-- 'httpStatus', 'describeConfigurationSetResponse_httpStatus' - The response's http status code.
newDescribeConfigurationSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConfigurationSetResponse
newDescribeConfigurationSetResponse :: Int -> DescribeConfigurationSetResponse
newDescribeConfigurationSetResponse Int
pHttpStatus_ =
  DescribeConfigurationSetResponse'
    { $sel:configurationSet:DescribeConfigurationSetResponse' :: Maybe ConfigurationSet
configurationSet =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deliveryOptions:DescribeConfigurationSetResponse' :: Maybe DeliveryOptions
deliveryOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:eventDestinations:DescribeConfigurationSetResponse' :: Maybe [EventDestination]
eventDestinations = forall a. Maybe a
Prelude.Nothing,
      $sel:reputationOptions:DescribeConfigurationSetResponse' :: Maybe ReputationOptions
reputationOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:trackingOptions:DescribeConfigurationSetResponse' :: Maybe TrackingOptions
trackingOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConfigurationSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The configuration set object associated with the specified configuration
-- set.
describeConfigurationSetResponse_configurationSet :: Lens.Lens' DescribeConfigurationSetResponse (Prelude.Maybe ConfigurationSet)
describeConfigurationSetResponse_configurationSet :: Lens' DescribeConfigurationSetResponse (Maybe ConfigurationSet)
describeConfigurationSetResponse_configurationSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSetResponse' {Maybe ConfigurationSet
configurationSet :: Maybe ConfigurationSet
$sel:configurationSet:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe ConfigurationSet
configurationSet} -> Maybe ConfigurationSet
configurationSet) (\s :: DescribeConfigurationSetResponse
s@DescribeConfigurationSetResponse' {} Maybe ConfigurationSet
a -> DescribeConfigurationSetResponse
s {$sel:configurationSet:DescribeConfigurationSetResponse' :: Maybe ConfigurationSet
configurationSet = Maybe ConfigurationSet
a} :: DescribeConfigurationSetResponse)

-- | Undocumented member.
describeConfigurationSetResponse_deliveryOptions :: Lens.Lens' DescribeConfigurationSetResponse (Prelude.Maybe DeliveryOptions)
describeConfigurationSetResponse_deliveryOptions :: Lens' DescribeConfigurationSetResponse (Maybe DeliveryOptions)
describeConfigurationSetResponse_deliveryOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSetResponse' {Maybe DeliveryOptions
deliveryOptions :: Maybe DeliveryOptions
$sel:deliveryOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe DeliveryOptions
deliveryOptions} -> Maybe DeliveryOptions
deliveryOptions) (\s :: DescribeConfigurationSetResponse
s@DescribeConfigurationSetResponse' {} Maybe DeliveryOptions
a -> DescribeConfigurationSetResponse
s {$sel:deliveryOptions:DescribeConfigurationSetResponse' :: Maybe DeliveryOptions
deliveryOptions = Maybe DeliveryOptions
a} :: DescribeConfigurationSetResponse)

-- | A list of event destinations associated with the configuration set.
describeConfigurationSetResponse_eventDestinations :: Lens.Lens' DescribeConfigurationSetResponse (Prelude.Maybe [EventDestination])
describeConfigurationSetResponse_eventDestinations :: Lens' DescribeConfigurationSetResponse (Maybe [EventDestination])
describeConfigurationSetResponse_eventDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSetResponse' {Maybe [EventDestination]
eventDestinations :: Maybe [EventDestination]
$sel:eventDestinations:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe [EventDestination]
eventDestinations} -> Maybe [EventDestination]
eventDestinations) (\s :: DescribeConfigurationSetResponse
s@DescribeConfigurationSetResponse' {} Maybe [EventDestination]
a -> DescribeConfigurationSetResponse
s {$sel:eventDestinations:DescribeConfigurationSetResponse' :: Maybe [EventDestination]
eventDestinations = Maybe [EventDestination]
a} :: DescribeConfigurationSetResponse) 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

-- | An object that represents the reputation settings for the configuration
-- set.
describeConfigurationSetResponse_reputationOptions :: Lens.Lens' DescribeConfigurationSetResponse (Prelude.Maybe ReputationOptions)
describeConfigurationSetResponse_reputationOptions :: Lens' DescribeConfigurationSetResponse (Maybe ReputationOptions)
describeConfigurationSetResponse_reputationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSetResponse' {Maybe ReputationOptions
reputationOptions :: Maybe ReputationOptions
$sel:reputationOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe ReputationOptions
reputationOptions} -> Maybe ReputationOptions
reputationOptions) (\s :: DescribeConfigurationSetResponse
s@DescribeConfigurationSetResponse' {} Maybe ReputationOptions
a -> DescribeConfigurationSetResponse
s {$sel:reputationOptions:DescribeConfigurationSetResponse' :: Maybe ReputationOptions
reputationOptions = Maybe ReputationOptions
a} :: DescribeConfigurationSetResponse)

-- | The name of the custom open and click tracking domain associated with
-- the configuration set.
describeConfigurationSetResponse_trackingOptions :: Lens.Lens' DescribeConfigurationSetResponse (Prelude.Maybe TrackingOptions)
describeConfigurationSetResponse_trackingOptions :: Lens' DescribeConfigurationSetResponse (Maybe TrackingOptions)
describeConfigurationSetResponse_trackingOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationSetResponse' {Maybe TrackingOptions
trackingOptions :: Maybe TrackingOptions
$sel:trackingOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe TrackingOptions
trackingOptions} -> Maybe TrackingOptions
trackingOptions) (\s :: DescribeConfigurationSetResponse
s@DescribeConfigurationSetResponse' {} Maybe TrackingOptions
a -> DescribeConfigurationSetResponse
s {$sel:trackingOptions:DescribeConfigurationSetResponse' :: Maybe TrackingOptions
trackingOptions = Maybe TrackingOptions
a} :: DescribeConfigurationSetResponse)

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

instance
  Prelude.NFData
    DescribeConfigurationSetResponse
  where
  rnf :: DescribeConfigurationSetResponse -> ()
rnf DescribeConfigurationSetResponse' {Int
Maybe [EventDestination]
Maybe ConfigurationSet
Maybe ReputationOptions
Maybe DeliveryOptions
Maybe TrackingOptions
httpStatus :: Int
trackingOptions :: Maybe TrackingOptions
reputationOptions :: Maybe ReputationOptions
eventDestinations :: Maybe [EventDestination]
deliveryOptions :: Maybe DeliveryOptions
configurationSet :: Maybe ConfigurationSet
$sel:httpStatus:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Int
$sel:trackingOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe TrackingOptions
$sel:reputationOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe ReputationOptions
$sel:eventDestinations:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe [EventDestination]
$sel:deliveryOptions:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe DeliveryOptions
$sel:configurationSet:DescribeConfigurationSetResponse' :: DescribeConfigurationSetResponse -> Maybe ConfigurationSet
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfigurationSet
configurationSet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliveryOptions
deliveryOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [EventDestination]
eventDestinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReputationOptions
reputationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrackingOptions
trackingOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus