{-# 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.DeleteEventDestination
-- 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 event destination.
--
-- An event destination is a location where you send response information
-- about the messages that you send. For example, when a message is
-- delivered successfully, you can send information about that event to an
-- Amazon CloudWatch destination, or send notifications to endpoints that
-- are subscribed to an Amazon SNS topic.
module Amazonka.PinpointSmsVoiceV2.DeleteEventDestination
  ( -- * Creating a Request
    DeleteEventDestination (..),
    newDeleteEventDestination,

    -- * Request Lenses
    deleteEventDestination_configurationSetName,
    deleteEventDestination_eventDestinationName,

    -- * Destructuring the Response
    DeleteEventDestinationResponse (..),
    newDeleteEventDestinationResponse,

    -- * Response Lenses
    deleteEventDestinationResponse_configurationSetArn,
    deleteEventDestinationResponse_configurationSetName,
    deleteEventDestinationResponse_eventDestination,
    deleteEventDestinationResponse_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:/ 'newDeleteEventDestination' smart constructor.
data DeleteEventDestination = DeleteEventDestination'
  { -- | The name of the configuration set or the configuration set\'s Amazon
    -- Resource Name (ARN) to remove the event destination from. The
    -- ConfigurateSetName and ConfigurationSetArn can be found using the
    -- DescribeConfigurationSets action.
    DeleteEventDestination -> Text
configurationSetName :: Prelude.Text,
    -- | The name of the event destination to delete.
    DeleteEventDestination -> Text
eventDestinationName :: Prelude.Text
  }
  deriving (DeleteEventDestination -> DeleteEventDestination -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEventDestination -> DeleteEventDestination -> Bool
$c/= :: DeleteEventDestination -> DeleteEventDestination -> Bool
== :: DeleteEventDestination -> DeleteEventDestination -> Bool
$c== :: DeleteEventDestination -> DeleteEventDestination -> Bool
Prelude.Eq, ReadPrec [DeleteEventDestination]
ReadPrec DeleteEventDestination
Int -> ReadS DeleteEventDestination
ReadS [DeleteEventDestination]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEventDestination]
$creadListPrec :: ReadPrec [DeleteEventDestination]
readPrec :: ReadPrec DeleteEventDestination
$creadPrec :: ReadPrec DeleteEventDestination
readList :: ReadS [DeleteEventDestination]
$creadList :: ReadS [DeleteEventDestination]
readsPrec :: Int -> ReadS DeleteEventDestination
$creadsPrec :: Int -> ReadS DeleteEventDestination
Prelude.Read, Int -> DeleteEventDestination -> ShowS
[DeleteEventDestination] -> ShowS
DeleteEventDestination -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEventDestination] -> ShowS
$cshowList :: [DeleteEventDestination] -> ShowS
show :: DeleteEventDestination -> String
$cshow :: DeleteEventDestination -> String
showsPrec :: Int -> DeleteEventDestination -> ShowS
$cshowsPrec :: Int -> DeleteEventDestination -> ShowS
Prelude.Show, forall x. Rep DeleteEventDestination x -> DeleteEventDestination
forall x. DeleteEventDestination -> Rep DeleteEventDestination x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteEventDestination x -> DeleteEventDestination
$cfrom :: forall x. DeleteEventDestination -> Rep DeleteEventDestination x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEventDestination' 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', 'deleteEventDestination_configurationSetName' - The name of the configuration set or the configuration set\'s Amazon
-- Resource Name (ARN) to remove the event destination from. The
-- ConfigurateSetName and ConfigurationSetArn can be found using the
-- DescribeConfigurationSets action.
--
-- 'eventDestinationName', 'deleteEventDestination_eventDestinationName' - The name of the event destination to delete.
newDeleteEventDestination ::
  -- | 'configurationSetName'
  Prelude.Text ->
  -- | 'eventDestinationName'
  Prelude.Text ->
  DeleteEventDestination
newDeleteEventDestination :: Text -> Text -> DeleteEventDestination
newDeleteEventDestination
  Text
pConfigurationSetName_
  Text
pEventDestinationName_ =
    DeleteEventDestination'
      { $sel:configurationSetName:DeleteEventDestination' :: Text
configurationSetName =
          Text
pConfigurationSetName_,
        $sel:eventDestinationName:DeleteEventDestination' :: Text
eventDestinationName = Text
pEventDestinationName_
      }

-- | The name of the configuration set or the configuration set\'s Amazon
-- Resource Name (ARN) to remove the event destination from. The
-- ConfigurateSetName and ConfigurationSetArn can be found using the
-- DescribeConfigurationSets action.
deleteEventDestination_configurationSetName :: Lens.Lens' DeleteEventDestination Prelude.Text
deleteEventDestination_configurationSetName :: Lens' DeleteEventDestination Text
deleteEventDestination_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEventDestination' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteEventDestination' :: DeleteEventDestination -> Text
configurationSetName} -> Text
configurationSetName) (\s :: DeleteEventDestination
s@DeleteEventDestination' {} Text
a -> DeleteEventDestination
s {$sel:configurationSetName:DeleteEventDestination' :: Text
configurationSetName = Text
a} :: DeleteEventDestination)

-- | The name of the event destination to delete.
deleteEventDestination_eventDestinationName :: Lens.Lens' DeleteEventDestination Prelude.Text
deleteEventDestination_eventDestinationName :: Lens' DeleteEventDestination Text
deleteEventDestination_eventDestinationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEventDestination' {Text
eventDestinationName :: Text
$sel:eventDestinationName:DeleteEventDestination' :: DeleteEventDestination -> Text
eventDestinationName} -> Text
eventDestinationName) (\s :: DeleteEventDestination
s@DeleteEventDestination' {} Text
a -> DeleteEventDestination
s {$sel:eventDestinationName:DeleteEventDestination' :: Text
eventDestinationName = Text
a} :: DeleteEventDestination)

instance Core.AWSRequest DeleteEventDestination where
  type
    AWSResponse DeleteEventDestination =
      DeleteEventDestinationResponse
  request :: (Service -> Service)
-> DeleteEventDestination -> Request DeleteEventDestination
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 DeleteEventDestination
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteEventDestination)))
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 EventDestination
-> Int
-> DeleteEventDestinationResponse
DeleteEventDestinationResponse'
            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
"EventDestination")
            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 DeleteEventDestination where
  hashWithSalt :: Int -> DeleteEventDestination -> Int
hashWithSalt Int
_salt DeleteEventDestination' {Text
eventDestinationName :: Text
configurationSetName :: Text
$sel:eventDestinationName:DeleteEventDestination' :: DeleteEventDestination -> Text
$sel:configurationSetName:DeleteEventDestination' :: DeleteEventDestination -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
eventDestinationName

instance Prelude.NFData DeleteEventDestination where
  rnf :: DeleteEventDestination -> ()
rnf DeleteEventDestination' {Text
eventDestinationName :: Text
configurationSetName :: Text
$sel:eventDestinationName:DeleteEventDestination' :: DeleteEventDestination -> Text
$sel:configurationSetName:DeleteEventDestination' :: DeleteEventDestination -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
configurationSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
eventDestinationName

instance Data.ToHeaders DeleteEventDestination where
  toHeaders :: DeleteEventDestination -> 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.DeleteEventDestination" ::
                          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 DeleteEventDestination where
  toJSON :: DeleteEventDestination -> Value
toJSON DeleteEventDestination' {Text
eventDestinationName :: Text
configurationSetName :: Text
$sel:eventDestinationName:DeleteEventDestination' :: DeleteEventDestination -> Text
$sel:configurationSetName:DeleteEventDestination' :: DeleteEventDestination -> 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
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"EventDestinationName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
eventDestinationName
              )
          ]
      )

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

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

-- | /See:/ 'newDeleteEventDestinationResponse' smart constructor.
data DeleteEventDestinationResponse = DeleteEventDestinationResponse'
  { -- | The Amazon Resource Name (ARN) of the configuration set.
    DeleteEventDestinationResponse -> Maybe Text
configurationSetArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the configuration set the event destination was deleted
    -- from.
    DeleteEventDestinationResponse -> Maybe Text
configurationSetName :: Prelude.Maybe Prelude.Text,
    -- | The event destination object that was deleted.
    DeleteEventDestinationResponse -> Maybe EventDestination
eventDestination :: Prelude.Maybe EventDestination,
    -- | The response's http status code.
    DeleteEventDestinationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteEventDestinationResponse
-> DeleteEventDestinationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEventDestinationResponse
-> DeleteEventDestinationResponse -> Bool
$c/= :: DeleteEventDestinationResponse
-> DeleteEventDestinationResponse -> Bool
== :: DeleteEventDestinationResponse
-> DeleteEventDestinationResponse -> Bool
$c== :: DeleteEventDestinationResponse
-> DeleteEventDestinationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteEventDestinationResponse]
ReadPrec DeleteEventDestinationResponse
Int -> ReadS DeleteEventDestinationResponse
ReadS [DeleteEventDestinationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEventDestinationResponse]
$creadListPrec :: ReadPrec [DeleteEventDestinationResponse]
readPrec :: ReadPrec DeleteEventDestinationResponse
$creadPrec :: ReadPrec DeleteEventDestinationResponse
readList :: ReadS [DeleteEventDestinationResponse]
$creadList :: ReadS [DeleteEventDestinationResponse]
readsPrec :: Int -> ReadS DeleteEventDestinationResponse
$creadsPrec :: Int -> ReadS DeleteEventDestinationResponse
Prelude.Read, Int -> DeleteEventDestinationResponse -> ShowS
[DeleteEventDestinationResponse] -> ShowS
DeleteEventDestinationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEventDestinationResponse] -> ShowS
$cshowList :: [DeleteEventDestinationResponse] -> ShowS
show :: DeleteEventDestinationResponse -> String
$cshow :: DeleteEventDestinationResponse -> String
showsPrec :: Int -> DeleteEventDestinationResponse -> ShowS
$cshowsPrec :: Int -> DeleteEventDestinationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteEventDestinationResponse x
-> DeleteEventDestinationResponse
forall x.
DeleteEventDestinationResponse
-> Rep DeleteEventDestinationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteEventDestinationResponse x
-> DeleteEventDestinationResponse
$cfrom :: forall x.
DeleteEventDestinationResponse
-> Rep DeleteEventDestinationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEventDestinationResponse' 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', 'deleteEventDestinationResponse_configurationSetArn' - The Amazon Resource Name (ARN) of the configuration set.
--
-- 'configurationSetName', 'deleteEventDestinationResponse_configurationSetName' - The name of the configuration set the event destination was deleted
-- from.
--
-- 'eventDestination', 'deleteEventDestinationResponse_eventDestination' - The event destination object that was deleted.
--
-- 'httpStatus', 'deleteEventDestinationResponse_httpStatus' - The response's http status code.
newDeleteEventDestinationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteEventDestinationResponse
newDeleteEventDestinationResponse :: Int -> DeleteEventDestinationResponse
newDeleteEventDestinationResponse Int
pHttpStatus_ =
  DeleteEventDestinationResponse'
    { $sel:configurationSetArn:DeleteEventDestinationResponse' :: Maybe Text
configurationSetArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSetName:DeleteEventDestinationResponse' :: Maybe Text
configurationSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:eventDestination:DeleteEventDestinationResponse' :: Maybe EventDestination
eventDestination = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteEventDestinationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | The event destination object that was deleted.
deleteEventDestinationResponse_eventDestination :: Lens.Lens' DeleteEventDestinationResponse (Prelude.Maybe EventDestination)
deleteEventDestinationResponse_eventDestination :: Lens' DeleteEventDestinationResponse (Maybe EventDestination)
deleteEventDestinationResponse_eventDestination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEventDestinationResponse' {Maybe EventDestination
eventDestination :: Maybe EventDestination
$sel:eventDestination:DeleteEventDestinationResponse' :: DeleteEventDestinationResponse -> Maybe EventDestination
eventDestination} -> Maybe EventDestination
eventDestination) (\s :: DeleteEventDestinationResponse
s@DeleteEventDestinationResponse' {} Maybe EventDestination
a -> DeleteEventDestinationResponse
s {$sel:eventDestination:DeleteEventDestinationResponse' :: Maybe EventDestination
eventDestination = Maybe EventDestination
a} :: DeleteEventDestinationResponse)

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

instance
  Prelude.NFData
    DeleteEventDestinationResponse
  where
  rnf :: DeleteEventDestinationResponse -> ()
rnf DeleteEventDestinationResponse' {Int
Maybe Text
Maybe EventDestination
httpStatus :: Int
eventDestination :: Maybe EventDestination
configurationSetName :: Maybe Text
configurationSetArn :: Maybe Text
$sel:httpStatus:DeleteEventDestinationResponse' :: DeleteEventDestinationResponse -> Int
$sel:eventDestination:DeleteEventDestinationResponse' :: DeleteEventDestinationResponse -> Maybe EventDestination
$sel:configurationSetName:DeleteEventDestinationResponse' :: DeleteEventDestinationResponse -> Maybe Text
$sel:configurationSetArn:DeleteEventDestinationResponse' :: DeleteEventDestinationResponse -> 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 EventDestination
eventDestination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus