{-# 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.PinpointSmsVoiceV2.DeleteConfigurationSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an existing configuration set.
--
-- A configuration set is a set of rules that you apply to voice and SMS
-- messages that you send. In a configuration set, you can specify a
-- destination for specific types of events related to voice and SMS
-- messages.
module Amazonka.PinpointSmsVoiceV2.DeleteConfigurationSet
  ( -- * Creating a Request
    DeleteConfigurationSet (..),
    newDeleteConfigurationSet,

    -- * Request Lenses
    deleteConfigurationSet_configurationSetName,

    -- * Destructuring the Response
    DeleteConfigurationSetResponse (..),
    newDeleteConfigurationSetResponse,

    -- * Response Lenses
    deleteConfigurationSetResponse_configurationSetArn,
    deleteConfigurationSetResponse_configurationSetName,
    deleteConfigurationSetResponse_createdTimestamp,
    deleteConfigurationSetResponse_defaultMessageType,
    deleteConfigurationSetResponse_defaultSenderId,
    deleteConfigurationSetResponse_eventDestinations,
    deleteConfigurationSetResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.PinpointSmsVoiceV2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteConfigurationSet' smart constructor.
data DeleteConfigurationSet = DeleteConfigurationSet'
  { -- | The name of the configuration set or the configuration set ARN that you
    -- want to delete. The ConfigurationSetName and ConfigurationSetArn can be
    -- found using the DescribeConfigurationSets action.
    DeleteConfigurationSet -> Text
configurationSetName :: Prelude.Text
  }
  deriving (DeleteConfigurationSet -> DeleteConfigurationSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteConfigurationSet -> DeleteConfigurationSet -> Bool
$c/= :: DeleteConfigurationSet -> DeleteConfigurationSet -> Bool
== :: DeleteConfigurationSet -> DeleteConfigurationSet -> Bool
$c== :: DeleteConfigurationSet -> DeleteConfigurationSet -> Bool
Prelude.Eq, ReadPrec [DeleteConfigurationSet]
ReadPrec DeleteConfigurationSet
Int -> ReadS DeleteConfigurationSet
ReadS [DeleteConfigurationSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteConfigurationSet]
$creadListPrec :: ReadPrec [DeleteConfigurationSet]
readPrec :: ReadPrec DeleteConfigurationSet
$creadPrec :: ReadPrec DeleteConfigurationSet
readList :: ReadS [DeleteConfigurationSet]
$creadList :: ReadS [DeleteConfigurationSet]
readsPrec :: Int -> ReadS DeleteConfigurationSet
$creadsPrec :: Int -> ReadS DeleteConfigurationSet
Prelude.Read, Int -> DeleteConfigurationSet -> ShowS
[DeleteConfigurationSet] -> ShowS
DeleteConfigurationSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteConfigurationSet] -> ShowS
$cshowList :: [DeleteConfigurationSet] -> ShowS
show :: DeleteConfigurationSet -> String
$cshow :: DeleteConfigurationSet -> String
showsPrec :: Int -> DeleteConfigurationSet -> ShowS
$cshowsPrec :: Int -> DeleteConfigurationSet -> ShowS
Prelude.Show, forall x. Rep DeleteConfigurationSet x -> DeleteConfigurationSet
forall x. DeleteConfigurationSet -> Rep DeleteConfigurationSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteConfigurationSet x -> DeleteConfigurationSet
$cfrom :: forall x. DeleteConfigurationSet -> Rep DeleteConfigurationSet x
Prelude.Generic)

-- |
-- Create a value of 'DeleteConfigurationSet' 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:
--
-- 'configurationSetName', 'deleteConfigurationSet_configurationSetName' - The name of the configuration set or the configuration set ARN that you
-- want to delete. The ConfigurationSetName and ConfigurationSetArn can be
-- found using the DescribeConfigurationSets action.
newDeleteConfigurationSet ::
  -- | 'configurationSetName'
  Prelude.Text ->
  DeleteConfigurationSet
newDeleteConfigurationSet :: Text -> DeleteConfigurationSet
newDeleteConfigurationSet Text
pConfigurationSetName_ =
  DeleteConfigurationSet'
    { $sel:configurationSetName:DeleteConfigurationSet' :: Text
configurationSetName =
        Text
pConfigurationSetName_
    }

-- | The name of the configuration set or the configuration set ARN that you
-- want to delete. The ConfigurationSetName and ConfigurationSetArn can be
-- found using the DescribeConfigurationSets action.
deleteConfigurationSet_configurationSetName :: Lens.Lens' DeleteConfigurationSet Prelude.Text
deleteConfigurationSet_configurationSetName :: Lens' DeleteConfigurationSet Text
deleteConfigurationSet_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSet' :: DeleteConfigurationSet -> Text
configurationSetName} -> Text
configurationSetName) (\s :: DeleteConfigurationSet
s@DeleteConfigurationSet' {} Text
a -> DeleteConfigurationSet
s {$sel:configurationSetName:DeleteConfigurationSet' :: Text
configurationSetName = Text
a} :: DeleteConfigurationSet)

instance Core.AWSRequest DeleteConfigurationSet where
  type
    AWSResponse DeleteConfigurationSet =
      DeleteConfigurationSetResponse
  request :: (Service -> Service)
-> DeleteConfigurationSet -> Request DeleteConfigurationSet
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 DeleteConfigurationSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteConfigurationSet)))
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 Text
-> Maybe POSIX
-> Maybe MessageType
-> Maybe Text
-> Maybe [EventDestination]
-> Int
-> DeleteConfigurationSetResponse
DeleteConfigurationSetResponse'
            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
"ConfigurationSetArn")
            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
"ConfigurationSetName")
            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
"CreatedTimestamp")
            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
"DefaultMessageType")
            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
"DefaultSenderId")
            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
"EventDestinations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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 DeleteConfigurationSet where
  hashWithSalt :: Int -> DeleteConfigurationSet -> Int
hashWithSalt Int
_salt DeleteConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSet' :: DeleteConfigurationSet -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName

instance Prelude.NFData DeleteConfigurationSet where
  rnf :: DeleteConfigurationSet -> ()
rnf DeleteConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSet' :: DeleteConfigurationSet -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
configurationSetName

instance Data.ToHeaders DeleteConfigurationSet where
  toHeaders :: DeleteConfigurationSet -> 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
"PinpointSMSVoiceV2.DeleteConfigurationSet" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteConfigurationSet where
  toJSON :: DeleteConfigurationSet -> Value
toJSON DeleteConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSet' :: DeleteConfigurationSet -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"ConfigurationSetName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationSetName
              )
          ]
      )

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

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

-- | /See:/ 'newDeleteConfigurationSetResponse' smart constructor.
data DeleteConfigurationSetResponse = DeleteConfigurationSetResponse'
  { -- | The Amazon Resource Name (ARN) of the deleted configuration set.
    DeleteConfigurationSetResponse -> Maybe Text
configurationSetArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the deleted configuration set.
    DeleteConfigurationSetResponse -> Maybe Text
configurationSetName :: Prelude.Maybe Prelude.Text,
    -- | The time that the deleted configuration set was created in
    -- <https://www.epochconverter.com/ UNIX epoch time> format.
    DeleteConfigurationSetResponse -> Maybe POSIX
createdTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The default message type of the configuration set that was deleted.
    DeleteConfigurationSetResponse -> Maybe MessageType
defaultMessageType :: Prelude.Maybe MessageType,
    -- | The default Sender ID of the configuration set that was deleted.
    DeleteConfigurationSetResponse -> Maybe Text
defaultSenderId :: Prelude.Maybe Prelude.Text,
    -- | An array of any EventDestination objects that were associated with the
    -- deleted configuration set.
    DeleteConfigurationSetResponse -> Maybe [EventDestination]
eventDestinations :: Prelude.Maybe [EventDestination],
    -- | The response's http status code.
    DeleteConfigurationSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteConfigurationSetResponse
-> DeleteConfigurationSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteConfigurationSetResponse
-> DeleteConfigurationSetResponse -> Bool
$c/= :: DeleteConfigurationSetResponse
-> DeleteConfigurationSetResponse -> Bool
== :: DeleteConfigurationSetResponse
-> DeleteConfigurationSetResponse -> Bool
$c== :: DeleteConfigurationSetResponse
-> DeleteConfigurationSetResponse -> Bool
Prelude.Eq, ReadPrec [DeleteConfigurationSetResponse]
ReadPrec DeleteConfigurationSetResponse
Int -> ReadS DeleteConfigurationSetResponse
ReadS [DeleteConfigurationSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteConfigurationSetResponse]
$creadListPrec :: ReadPrec [DeleteConfigurationSetResponse]
readPrec :: ReadPrec DeleteConfigurationSetResponse
$creadPrec :: ReadPrec DeleteConfigurationSetResponse
readList :: ReadS [DeleteConfigurationSetResponse]
$creadList :: ReadS [DeleteConfigurationSetResponse]
readsPrec :: Int -> ReadS DeleteConfigurationSetResponse
$creadsPrec :: Int -> ReadS DeleteConfigurationSetResponse
Prelude.Read, Int -> DeleteConfigurationSetResponse -> ShowS
[DeleteConfigurationSetResponse] -> ShowS
DeleteConfigurationSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteConfigurationSetResponse] -> ShowS
$cshowList :: [DeleteConfigurationSetResponse] -> ShowS
show :: DeleteConfigurationSetResponse -> String
$cshow :: DeleteConfigurationSetResponse -> String
showsPrec :: Int -> DeleteConfigurationSetResponse -> ShowS
$cshowsPrec :: Int -> DeleteConfigurationSetResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteConfigurationSetResponse x
-> DeleteConfigurationSetResponse
forall x.
DeleteConfigurationSetResponse
-> Rep DeleteConfigurationSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteConfigurationSetResponse x
-> DeleteConfigurationSetResponse
$cfrom :: forall x.
DeleteConfigurationSetResponse
-> Rep DeleteConfigurationSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteConfigurationSetResponse' 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:
--
-- 'configurationSetArn', 'deleteConfigurationSetResponse_configurationSetArn' - The Amazon Resource Name (ARN) of the deleted configuration set.
--
-- 'configurationSetName', 'deleteConfigurationSetResponse_configurationSetName' - The name of the deleted configuration set.
--
-- 'createdTimestamp', 'deleteConfigurationSetResponse_createdTimestamp' - The time that the deleted configuration set was created in
-- <https://www.epochconverter.com/ UNIX epoch time> format.
--
-- 'defaultMessageType', 'deleteConfigurationSetResponse_defaultMessageType' - The default message type of the configuration set that was deleted.
--
-- 'defaultSenderId', 'deleteConfigurationSetResponse_defaultSenderId' - The default Sender ID of the configuration set that was deleted.
--
-- 'eventDestinations', 'deleteConfigurationSetResponse_eventDestinations' - An array of any EventDestination objects that were associated with the
-- deleted configuration set.
--
-- 'httpStatus', 'deleteConfigurationSetResponse_httpStatus' - The response's http status code.
newDeleteConfigurationSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteConfigurationSetResponse
newDeleteConfigurationSetResponse :: Int -> DeleteConfigurationSetResponse
newDeleteConfigurationSetResponse Int
pHttpStatus_ =
  DeleteConfigurationSetResponse'
    { $sel:configurationSetArn:DeleteConfigurationSetResponse' :: Maybe Text
configurationSetArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSetName:DeleteConfigurationSetResponse' :: Maybe Text
configurationSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTimestamp:DeleteConfigurationSetResponse' :: Maybe POSIX
createdTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultMessageType:DeleteConfigurationSetResponse' :: Maybe MessageType
defaultMessageType = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultSenderId:DeleteConfigurationSetResponse' :: Maybe Text
defaultSenderId = forall a. Maybe a
Prelude.Nothing,
      $sel:eventDestinations:DeleteConfigurationSetResponse' :: Maybe [EventDestination]
eventDestinations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteConfigurationSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the deleted configuration set.
deleteConfigurationSetResponse_configurationSetArn :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe Prelude.Text)
deleteConfigurationSetResponse_configurationSetArn :: Lens' DeleteConfigurationSetResponse (Maybe Text)
deleteConfigurationSetResponse_configurationSetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe Text
configurationSetArn :: Maybe Text
$sel:configurationSetArn:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
configurationSetArn} -> Maybe Text
configurationSetArn) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe Text
a -> DeleteConfigurationSetResponse
s {$sel:configurationSetArn:DeleteConfigurationSetResponse' :: Maybe Text
configurationSetArn = Maybe Text
a} :: DeleteConfigurationSetResponse)

-- | The name of the deleted configuration set.
deleteConfigurationSetResponse_configurationSetName :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe Prelude.Text)
deleteConfigurationSetResponse_configurationSetName :: Lens' DeleteConfigurationSetResponse (Maybe Text)
deleteConfigurationSetResponse_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe Text
configurationSetName :: Maybe Text
$sel:configurationSetName:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
configurationSetName} -> Maybe Text
configurationSetName) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe Text
a -> DeleteConfigurationSetResponse
s {$sel:configurationSetName:DeleteConfigurationSetResponse' :: Maybe Text
configurationSetName = Maybe Text
a} :: DeleteConfigurationSetResponse)

-- | The time that the deleted configuration set was created in
-- <https://www.epochconverter.com/ UNIX epoch time> format.
deleteConfigurationSetResponse_createdTimestamp :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe Prelude.UTCTime)
deleteConfigurationSetResponse_createdTimestamp :: Lens' DeleteConfigurationSetResponse (Maybe UTCTime)
deleteConfigurationSetResponse_createdTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe POSIX
createdTimestamp :: Maybe POSIX
$sel:createdTimestamp:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe POSIX
createdTimestamp} -> Maybe POSIX
createdTimestamp) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe POSIX
a -> DeleteConfigurationSetResponse
s {$sel:createdTimestamp:DeleteConfigurationSetResponse' :: Maybe POSIX
createdTimestamp = Maybe POSIX
a} :: DeleteConfigurationSetResponse) 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 default message type of the configuration set that was deleted.
deleteConfigurationSetResponse_defaultMessageType :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe MessageType)
deleteConfigurationSetResponse_defaultMessageType :: Lens' DeleteConfigurationSetResponse (Maybe MessageType)
deleteConfigurationSetResponse_defaultMessageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe MessageType
defaultMessageType :: Maybe MessageType
$sel:defaultMessageType:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe MessageType
defaultMessageType} -> Maybe MessageType
defaultMessageType) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe MessageType
a -> DeleteConfigurationSetResponse
s {$sel:defaultMessageType:DeleteConfigurationSetResponse' :: Maybe MessageType
defaultMessageType = Maybe MessageType
a} :: DeleteConfigurationSetResponse)

-- | The default Sender ID of the configuration set that was deleted.
deleteConfigurationSetResponse_defaultSenderId :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe Prelude.Text)
deleteConfigurationSetResponse_defaultSenderId :: Lens' DeleteConfigurationSetResponse (Maybe Text)
deleteConfigurationSetResponse_defaultSenderId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe Text
defaultSenderId :: Maybe Text
$sel:defaultSenderId:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
defaultSenderId} -> Maybe Text
defaultSenderId) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe Text
a -> DeleteConfigurationSetResponse
s {$sel:defaultSenderId:DeleteConfigurationSetResponse' :: Maybe Text
defaultSenderId = Maybe Text
a} :: DeleteConfigurationSetResponse)

-- | An array of any EventDestination objects that were associated with the
-- deleted configuration set.
deleteConfigurationSetResponse_eventDestinations :: Lens.Lens' DeleteConfigurationSetResponse (Prelude.Maybe [EventDestination])
deleteConfigurationSetResponse_eventDestinations :: Lens' DeleteConfigurationSetResponse (Maybe [EventDestination])
deleteConfigurationSetResponse_eventDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Maybe [EventDestination]
eventDestinations :: Maybe [EventDestination]
$sel:eventDestinations:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe [EventDestination]
eventDestinations} -> Maybe [EventDestination]
eventDestinations) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Maybe [EventDestination]
a -> DeleteConfigurationSetResponse
s {$sel:eventDestinations:DeleteConfigurationSetResponse' :: Maybe [EventDestination]
eventDestinations = Maybe [EventDestination]
a} :: DeleteConfigurationSetResponse) 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 response's http status code.
deleteConfigurationSetResponse_httpStatus :: Lens.Lens' DeleteConfigurationSetResponse Prelude.Int
deleteConfigurationSetResponse_httpStatus :: Lens' DeleteConfigurationSetResponse Int
deleteConfigurationSetResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteConfigurationSetResponse
s@DeleteConfigurationSetResponse' {} Int
a -> DeleteConfigurationSetResponse
s {$sel:httpStatus:DeleteConfigurationSetResponse' :: Int
httpStatus = Int
a} :: DeleteConfigurationSetResponse)

instance
  Prelude.NFData
    DeleteConfigurationSetResponse
  where
  rnf :: DeleteConfigurationSetResponse -> ()
rnf DeleteConfigurationSetResponse' {Int
Maybe [EventDestination]
Maybe Text
Maybe POSIX
Maybe MessageType
httpStatus :: Int
eventDestinations :: Maybe [EventDestination]
defaultSenderId :: Maybe Text
defaultMessageType :: Maybe MessageType
createdTimestamp :: Maybe POSIX
configurationSetName :: Maybe Text
configurationSetArn :: Maybe Text
$sel:httpStatus:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Int
$sel:eventDestinations:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe [EventDestination]
$sel:defaultSenderId:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
$sel:defaultMessageType:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe MessageType
$sel:createdTimestamp:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe POSIX
$sel:configurationSetName:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
$sel:configurationSetArn:DeleteConfigurationSetResponse' :: DeleteConfigurationSetResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configurationSetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configurationSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MessageType
defaultMessageType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultSenderId
      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 Int
httpStatus