{-# 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.DeleteConfigurationSetTrackingOptions
-- 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 association between a configuration set and a custom domain
-- for open and click event tracking.
--
-- By default, images and links used for tracking open and click events are
-- hosted on domains operated by Amazon SES. You can configure a subdomain
-- of your own to handle these events. For information about using custom
-- domains, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/configure-custom-open-click-domains.html Amazon SES Developer Guide>.
--
-- Deleting this kind of association will result in emails sent using the
-- specified configuration set to capture open and click events using the
-- standard, Amazon SES-operated domains.
module Amazonka.SES.DeleteConfigurationSetTrackingOptions
  ( -- * Creating a Request
    DeleteConfigurationSetTrackingOptions (..),
    newDeleteConfigurationSetTrackingOptions,

    -- * Request Lenses
    deleteConfigurationSetTrackingOptions_configurationSetName,

    -- * Destructuring the Response
    DeleteConfigurationSetTrackingOptionsResponse (..),
    newDeleteConfigurationSetTrackingOptionsResponse,

    -- * Response Lenses
    deleteConfigurationSetTrackingOptionsResponse_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 delete open and click tracking options in a
-- configuration set.
--
-- /See:/ 'newDeleteConfigurationSetTrackingOptions' smart constructor.
data DeleteConfigurationSetTrackingOptions = DeleteConfigurationSetTrackingOptions'
  { -- | The name of the configuration set from which you want to delete the
    -- tracking options.
    DeleteConfigurationSetTrackingOptions -> Text
configurationSetName :: Prelude.Text
  }
  deriving (DeleteConfigurationSetTrackingOptions
-> DeleteConfigurationSetTrackingOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteConfigurationSetTrackingOptions
-> DeleteConfigurationSetTrackingOptions -> Bool
$c/= :: DeleteConfigurationSetTrackingOptions
-> DeleteConfigurationSetTrackingOptions -> Bool
== :: DeleteConfigurationSetTrackingOptions
-> DeleteConfigurationSetTrackingOptions -> Bool
$c== :: DeleteConfigurationSetTrackingOptions
-> DeleteConfigurationSetTrackingOptions -> Bool
Prelude.Eq, ReadPrec [DeleteConfigurationSetTrackingOptions]
ReadPrec DeleteConfigurationSetTrackingOptions
Int -> ReadS DeleteConfigurationSetTrackingOptions
ReadS [DeleteConfigurationSetTrackingOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteConfigurationSetTrackingOptions]
$creadListPrec :: ReadPrec [DeleteConfigurationSetTrackingOptions]
readPrec :: ReadPrec DeleteConfigurationSetTrackingOptions
$creadPrec :: ReadPrec DeleteConfigurationSetTrackingOptions
readList :: ReadS [DeleteConfigurationSetTrackingOptions]
$creadList :: ReadS [DeleteConfigurationSetTrackingOptions]
readsPrec :: Int -> ReadS DeleteConfigurationSetTrackingOptions
$creadsPrec :: Int -> ReadS DeleteConfigurationSetTrackingOptions
Prelude.Read, Int -> DeleteConfigurationSetTrackingOptions -> ShowS
[DeleteConfigurationSetTrackingOptions] -> ShowS
DeleteConfigurationSetTrackingOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteConfigurationSetTrackingOptions] -> ShowS
$cshowList :: [DeleteConfigurationSetTrackingOptions] -> ShowS
show :: DeleteConfigurationSetTrackingOptions -> String
$cshow :: DeleteConfigurationSetTrackingOptions -> String
showsPrec :: Int -> DeleteConfigurationSetTrackingOptions -> ShowS
$cshowsPrec :: Int -> DeleteConfigurationSetTrackingOptions -> ShowS
Prelude.Show, forall x.
Rep DeleteConfigurationSetTrackingOptions x
-> DeleteConfigurationSetTrackingOptions
forall x.
DeleteConfigurationSetTrackingOptions
-> Rep DeleteConfigurationSetTrackingOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteConfigurationSetTrackingOptions x
-> DeleteConfigurationSetTrackingOptions
$cfrom :: forall x.
DeleteConfigurationSetTrackingOptions
-> Rep DeleteConfigurationSetTrackingOptions x
Prelude.Generic)

-- |
-- Create a value of 'DeleteConfigurationSetTrackingOptions' 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', 'deleteConfigurationSetTrackingOptions_configurationSetName' - The name of the configuration set from which you want to delete the
-- tracking options.
newDeleteConfigurationSetTrackingOptions ::
  -- | 'configurationSetName'
  Prelude.Text ->
  DeleteConfigurationSetTrackingOptions
newDeleteConfigurationSetTrackingOptions :: Text -> DeleteConfigurationSetTrackingOptions
newDeleteConfigurationSetTrackingOptions
  Text
pConfigurationSetName_ =
    DeleteConfigurationSetTrackingOptions'
      { $sel:configurationSetName:DeleteConfigurationSetTrackingOptions' :: Text
configurationSetName =
          Text
pConfigurationSetName_
      }

-- | The name of the configuration set from which you want to delete the
-- tracking options.
deleteConfigurationSetTrackingOptions_configurationSetName :: Lens.Lens' DeleteConfigurationSetTrackingOptions Prelude.Text
deleteConfigurationSetTrackingOptions_configurationSetName :: Lens' DeleteConfigurationSetTrackingOptions Text
deleteConfigurationSetTrackingOptions_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConfigurationSetTrackingOptions' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSetTrackingOptions' :: DeleteConfigurationSetTrackingOptions -> Text
configurationSetName} -> Text
configurationSetName) (\s :: DeleteConfigurationSetTrackingOptions
s@DeleteConfigurationSetTrackingOptions' {} Text
a -> DeleteConfigurationSetTrackingOptions
s {$sel:configurationSetName:DeleteConfigurationSetTrackingOptions' :: Text
configurationSetName = Text
a} :: DeleteConfigurationSetTrackingOptions)

instance
  Core.AWSRequest
    DeleteConfigurationSetTrackingOptions
  where
  type
    AWSResponse
      DeleteConfigurationSetTrackingOptions =
      DeleteConfigurationSetTrackingOptionsResponse
  request :: (Service -> Service)
-> DeleteConfigurationSetTrackingOptions
-> Request DeleteConfigurationSetTrackingOptions
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 DeleteConfigurationSetTrackingOptions
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DeleteConfigurationSetTrackingOptions)))
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
"DeleteConfigurationSetTrackingOptionsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> DeleteConfigurationSetTrackingOptionsResponse
DeleteConfigurationSetTrackingOptionsResponse'
            forall (f :: * -> *) a b. Functor 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
    DeleteConfigurationSetTrackingOptions
  where
  hashWithSalt :: Int -> DeleteConfigurationSetTrackingOptions -> Int
hashWithSalt
    Int
_salt
    DeleteConfigurationSetTrackingOptions' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSetTrackingOptions' :: DeleteConfigurationSetTrackingOptions -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName

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

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

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

instance
  Data.ToQuery
    DeleteConfigurationSetTrackingOptions
  where
  toQuery :: DeleteConfigurationSetTrackingOptions -> QueryString
toQuery DeleteConfigurationSetTrackingOptions' {Text
configurationSetName :: Text
$sel:configurationSetName:DeleteConfigurationSetTrackingOptions' :: DeleteConfigurationSetTrackingOptions -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteConfigurationSetTrackingOptions" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"ConfigurationSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
configurationSetName
      ]

-- | An empty element returned on a successful request.
--
-- /See:/ 'newDeleteConfigurationSetTrackingOptionsResponse' smart constructor.
data DeleteConfigurationSetTrackingOptionsResponse = DeleteConfigurationSetTrackingOptionsResponse'
  { -- | The response's http status code.
    DeleteConfigurationSetTrackingOptionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteConfigurationSetTrackingOptionsResponse
-> DeleteConfigurationSetTrackingOptionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteConfigurationSetTrackingOptionsResponse
-> DeleteConfigurationSetTrackingOptionsResponse -> Bool
$c/= :: DeleteConfigurationSetTrackingOptionsResponse
-> DeleteConfigurationSetTrackingOptionsResponse -> Bool
== :: DeleteConfigurationSetTrackingOptionsResponse
-> DeleteConfigurationSetTrackingOptionsResponse -> Bool
$c== :: DeleteConfigurationSetTrackingOptionsResponse
-> DeleteConfigurationSetTrackingOptionsResponse -> Bool
Prelude.Eq, ReadPrec [DeleteConfigurationSetTrackingOptionsResponse]
ReadPrec DeleteConfigurationSetTrackingOptionsResponse
Int -> ReadS DeleteConfigurationSetTrackingOptionsResponse
ReadS [DeleteConfigurationSetTrackingOptionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteConfigurationSetTrackingOptionsResponse]
$creadListPrec :: ReadPrec [DeleteConfigurationSetTrackingOptionsResponse]
readPrec :: ReadPrec DeleteConfigurationSetTrackingOptionsResponse
$creadPrec :: ReadPrec DeleteConfigurationSetTrackingOptionsResponse
readList :: ReadS [DeleteConfigurationSetTrackingOptionsResponse]
$creadList :: ReadS [DeleteConfigurationSetTrackingOptionsResponse]
readsPrec :: Int -> ReadS DeleteConfigurationSetTrackingOptionsResponse
$creadsPrec :: Int -> ReadS DeleteConfigurationSetTrackingOptionsResponse
Prelude.Read, Int -> DeleteConfigurationSetTrackingOptionsResponse -> ShowS
[DeleteConfigurationSetTrackingOptionsResponse] -> ShowS
DeleteConfigurationSetTrackingOptionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteConfigurationSetTrackingOptionsResponse] -> ShowS
$cshowList :: [DeleteConfigurationSetTrackingOptionsResponse] -> ShowS
show :: DeleteConfigurationSetTrackingOptionsResponse -> String
$cshow :: DeleteConfigurationSetTrackingOptionsResponse -> String
showsPrec :: Int -> DeleteConfigurationSetTrackingOptionsResponse -> ShowS
$cshowsPrec :: Int -> DeleteConfigurationSetTrackingOptionsResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteConfigurationSetTrackingOptionsResponse x
-> DeleteConfigurationSetTrackingOptionsResponse
forall x.
DeleteConfigurationSetTrackingOptionsResponse
-> Rep DeleteConfigurationSetTrackingOptionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteConfigurationSetTrackingOptionsResponse x
-> DeleteConfigurationSetTrackingOptionsResponse
$cfrom :: forall x.
DeleteConfigurationSetTrackingOptionsResponse
-> Rep DeleteConfigurationSetTrackingOptionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteConfigurationSetTrackingOptionsResponse' 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:
--
-- 'httpStatus', 'deleteConfigurationSetTrackingOptionsResponse_httpStatus' - The response's http status code.
newDeleteConfigurationSetTrackingOptionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteConfigurationSetTrackingOptionsResponse
newDeleteConfigurationSetTrackingOptionsResponse :: Int -> DeleteConfigurationSetTrackingOptionsResponse
newDeleteConfigurationSetTrackingOptionsResponse
  Int
pHttpStatus_ =
    DeleteConfigurationSetTrackingOptionsResponse'
      { $sel:httpStatus:DeleteConfigurationSetTrackingOptionsResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

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

instance
  Prelude.NFData
    DeleteConfigurationSetTrackingOptionsResponse
  where
  rnf :: DeleteConfigurationSetTrackingOptionsResponse -> ()
rnf
    DeleteConfigurationSetTrackingOptionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteConfigurationSetTrackingOptionsResponse' :: DeleteConfigurationSetTrackingOptionsResponse -> Int
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus