{-# 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.CloudFront.DeleteDistribution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete a distribution.
module Amazonka.CloudFront.DeleteDistribution
  ( -- * Creating a Request
    DeleteDistribution (..),
    newDeleteDistribution,

    -- * Request Lenses
    deleteDistribution_ifMatch,
    deleteDistribution_id,

    -- * Destructuring the Response
    DeleteDistributionResponse (..),
    newDeleteDistributionResponse,
  )
where

import Amazonka.CloudFront.Types
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

-- | This action deletes a web distribution. To delete a web distribution
-- using the CloudFront API, perform the following steps.
--
-- __To delete a web distribution using the CloudFront API:__
--
-- 1.  Disable the web distribution
--
-- 2.  Submit a @GET Distribution Config@ request to get the current
--     configuration and the @Etag@ header for the distribution.
--
-- 3.  Update the XML document that was returned in the response to your
--     @GET Distribution Config@ request to change the value of @Enabled@
--     to @false@.
--
-- 4.  Submit a @PUT Distribution Config@ request to update the
--     configuration for your distribution. In the request body, include
--     the XML document that you updated in Step 3. Set the value of the
--     HTTP @If-Match@ header to the value of the @ETag@ header that
--     CloudFront returned when you submitted the @GET Distribution Config@
--     request in Step 2.
--
-- 5.  Review the response to the @PUT Distribution Config@ request to
--     confirm that the distribution was successfully disabled.
--
-- 6.  Submit a @GET Distribution@ request to confirm that your changes
--     have propagated. When propagation is complete, the value of @Status@
--     is @Deployed@.
--
-- 7.  Submit a @DELETE Distribution@ request. Set the value of the HTTP
--     @If-Match@ header to the value of the @ETag@ header that CloudFront
--     returned when you submitted the @GET Distribution Config@ request in
--     Step 6.
--
-- 8.  Review the response to your @DELETE Distribution@ request to confirm
--     that the distribution was successfully deleted.
--
-- For information about deleting a distribution using the CloudFront
-- console, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/HowToDeleteDistribution.html Deleting a Distribution>
-- in the /Amazon CloudFront Developer Guide/.
--
-- /See:/ 'newDeleteDistribution' smart constructor.
data DeleteDistribution = DeleteDistribution'
  { -- | The value of the @ETag@ header that you received when you disabled the
    -- distribution. For example: @E2QWRUHAPOMQZL@.
    DeleteDistribution -> Maybe Text
ifMatch :: Prelude.Maybe Prelude.Text,
    -- | The distribution ID.
    DeleteDistribution -> Text
id :: Prelude.Text
  }
  deriving (DeleteDistribution -> DeleteDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDistribution -> DeleteDistribution -> Bool
$c/= :: DeleteDistribution -> DeleteDistribution -> Bool
== :: DeleteDistribution -> DeleteDistribution -> Bool
$c== :: DeleteDistribution -> DeleteDistribution -> Bool
Prelude.Eq, ReadPrec [DeleteDistribution]
ReadPrec DeleteDistribution
Int -> ReadS DeleteDistribution
ReadS [DeleteDistribution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDistribution]
$creadListPrec :: ReadPrec [DeleteDistribution]
readPrec :: ReadPrec DeleteDistribution
$creadPrec :: ReadPrec DeleteDistribution
readList :: ReadS [DeleteDistribution]
$creadList :: ReadS [DeleteDistribution]
readsPrec :: Int -> ReadS DeleteDistribution
$creadsPrec :: Int -> ReadS DeleteDistribution
Prelude.Read, Int -> DeleteDistribution -> ShowS
[DeleteDistribution] -> ShowS
DeleteDistribution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDistribution] -> ShowS
$cshowList :: [DeleteDistribution] -> ShowS
show :: DeleteDistribution -> String
$cshow :: DeleteDistribution -> String
showsPrec :: Int -> DeleteDistribution -> ShowS
$cshowsPrec :: Int -> DeleteDistribution -> ShowS
Prelude.Show, forall x. Rep DeleteDistribution x -> DeleteDistribution
forall x. DeleteDistribution -> Rep DeleteDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDistribution x -> DeleteDistribution
$cfrom :: forall x. DeleteDistribution -> Rep DeleteDistribution x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDistribution' 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:
--
-- 'ifMatch', 'deleteDistribution_ifMatch' - The value of the @ETag@ header that you received when you disabled the
-- distribution. For example: @E2QWRUHAPOMQZL@.
--
-- 'id', 'deleteDistribution_id' - The distribution ID.
newDeleteDistribution ::
  -- | 'id'
  Prelude.Text ->
  DeleteDistribution
newDeleteDistribution :: Text -> DeleteDistribution
newDeleteDistribution Text
pId_ =
  DeleteDistribution'
    { $sel:ifMatch:DeleteDistribution' :: Maybe Text
ifMatch = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DeleteDistribution' :: Text
id = Text
pId_
    }

-- | The value of the @ETag@ header that you received when you disabled the
-- distribution. For example: @E2QWRUHAPOMQZL@.
deleteDistribution_ifMatch :: Lens.Lens' DeleteDistribution (Prelude.Maybe Prelude.Text)
deleteDistribution_ifMatch :: Lens' DeleteDistribution (Maybe Text)
deleteDistribution_ifMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDistribution' {Maybe Text
ifMatch :: Maybe Text
$sel:ifMatch:DeleteDistribution' :: DeleteDistribution -> Maybe Text
ifMatch} -> Maybe Text
ifMatch) (\s :: DeleteDistribution
s@DeleteDistribution' {} Maybe Text
a -> DeleteDistribution
s {$sel:ifMatch:DeleteDistribution' :: Maybe Text
ifMatch = Maybe Text
a} :: DeleteDistribution)

-- | The distribution ID.
deleteDistribution_id :: Lens.Lens' DeleteDistribution Prelude.Text
deleteDistribution_id :: Lens' DeleteDistribution Text
deleteDistribution_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDistribution' {Text
id :: Text
$sel:id:DeleteDistribution' :: DeleteDistribution -> Text
id} -> Text
id) (\s :: DeleteDistribution
s@DeleteDistribution' {} Text
a -> DeleteDistribution
s {$sel:id:DeleteDistribution' :: Text
id = Text
a} :: DeleteDistribution)

instance Core.AWSRequest DeleteDistribution where
  type
    AWSResponse DeleteDistribution =
      DeleteDistributionResponse
  request :: (Service -> Service)
-> DeleteDistribution -> Request DeleteDistribution
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteDistribution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDistribution)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteDistributionResponse
DeleteDistributionResponse'

instance Prelude.Hashable DeleteDistribution where
  hashWithSalt :: Int -> DeleteDistribution -> Int
hashWithSalt Int
_salt DeleteDistribution' {Maybe Text
Text
id :: Text
ifMatch :: Maybe Text
$sel:id:DeleteDistribution' :: DeleteDistribution -> Text
$sel:ifMatch:DeleteDistribution' :: DeleteDistribution -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ifMatch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData DeleteDistribution where
  rnf :: DeleteDistribution -> ()
rnf DeleteDistribution' {Maybe Text
Text
id :: Text
ifMatch :: Maybe Text
$sel:id:DeleteDistribution' :: DeleteDistribution -> Text
$sel:ifMatch:DeleteDistribution' :: DeleteDistribution -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ifMatch seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders DeleteDistribution where
  toHeaders :: DeleteDistribution -> [Header]
toHeaders DeleteDistribution' {Maybe Text
Text
id :: Text
ifMatch :: Maybe Text
$sel:id:DeleteDistribution' :: DeleteDistribution -> Text
$sel:ifMatch:DeleteDistribution' :: DeleteDistribution -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [HeaderName
"If-Match" forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
ifMatch]

instance Data.ToPath DeleteDistribution where
  toPath :: DeleteDistribution -> ByteString
toPath DeleteDistribution' {Maybe Text
Text
id :: Text
ifMatch :: Maybe Text
$sel:id:DeleteDistribution' :: DeleteDistribution -> Text
$sel:ifMatch:DeleteDistribution' :: DeleteDistribution -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2020-05-31/distribution/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | /See:/ 'newDeleteDistributionResponse' smart constructor.
data DeleteDistributionResponse = DeleteDistributionResponse'
  {
  }
  deriving (DeleteDistributionResponse -> DeleteDistributionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDistributionResponse -> DeleteDistributionResponse -> Bool
$c/= :: DeleteDistributionResponse -> DeleteDistributionResponse -> Bool
== :: DeleteDistributionResponse -> DeleteDistributionResponse -> Bool
$c== :: DeleteDistributionResponse -> DeleteDistributionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteDistributionResponse]
ReadPrec DeleteDistributionResponse
Int -> ReadS DeleteDistributionResponse
ReadS [DeleteDistributionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDistributionResponse]
$creadListPrec :: ReadPrec [DeleteDistributionResponse]
readPrec :: ReadPrec DeleteDistributionResponse
$creadPrec :: ReadPrec DeleteDistributionResponse
readList :: ReadS [DeleteDistributionResponse]
$creadList :: ReadS [DeleteDistributionResponse]
readsPrec :: Int -> ReadS DeleteDistributionResponse
$creadsPrec :: Int -> ReadS DeleteDistributionResponse
Prelude.Read, Int -> DeleteDistributionResponse -> ShowS
[DeleteDistributionResponse] -> ShowS
DeleteDistributionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDistributionResponse] -> ShowS
$cshowList :: [DeleteDistributionResponse] -> ShowS
show :: DeleteDistributionResponse -> String
$cshow :: DeleteDistributionResponse -> String
showsPrec :: Int -> DeleteDistributionResponse -> ShowS
$cshowsPrec :: Int -> DeleteDistributionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteDistributionResponse x -> DeleteDistributionResponse
forall x.
DeleteDistributionResponse -> Rep DeleteDistributionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDistributionResponse x -> DeleteDistributionResponse
$cfrom :: forall x.
DeleteDistributionResponse -> Rep DeleteDistributionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDistributionResponse' 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.
newDeleteDistributionResponse ::
  DeleteDistributionResponse
newDeleteDistributionResponse :: DeleteDistributionResponse
newDeleteDistributionResponse =
  DeleteDistributionResponse
DeleteDistributionResponse'

instance Prelude.NFData DeleteDistributionResponse where
  rnf :: DeleteDistributionResponse -> ()
rnf DeleteDistributionResponse
_ = ()