{-# 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.DLM.DeleteLifecyclePolicy
-- 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 the specified lifecycle policy and halts the automated
-- operations that the policy specified.
--
-- For more information about deleting a policy, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/view-modify-delete.html#delete Delete lifecycle policies>.
module Amazonka.DLM.DeleteLifecyclePolicy
  ( -- * Creating a Request
    DeleteLifecyclePolicy (..),
    newDeleteLifecyclePolicy,

    -- * Request Lenses
    deleteLifecyclePolicy_policyId,

    -- * Destructuring the Response
    DeleteLifecyclePolicyResponse (..),
    newDeleteLifecyclePolicyResponse,

    -- * Response Lenses
    deleteLifecyclePolicyResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteLifecyclePolicy' 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:
--
-- 'policyId', 'deleteLifecyclePolicy_policyId' - The identifier of the lifecycle policy.
newDeleteLifecyclePolicy ::
  -- | 'policyId'
  Prelude.Text ->
  DeleteLifecyclePolicy
newDeleteLifecyclePolicy :: Text -> DeleteLifecyclePolicy
newDeleteLifecyclePolicy Text
pPolicyId_ =
  DeleteLifecyclePolicy' {$sel:policyId:DeleteLifecyclePolicy' :: Text
policyId = Text
pPolicyId_}

-- | The identifier of the lifecycle policy.
deleteLifecyclePolicy_policyId :: Lens.Lens' DeleteLifecyclePolicy Prelude.Text
deleteLifecyclePolicy_policyId :: Lens' DeleteLifecyclePolicy Text
deleteLifecyclePolicy_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:DeleteLifecyclePolicy' :: DeleteLifecyclePolicy -> Text
policyId} -> Text
policyId) (\s :: DeleteLifecyclePolicy
s@DeleteLifecyclePolicy' {} Text
a -> DeleteLifecyclePolicy
s {$sel:policyId:DeleteLifecyclePolicy' :: Text
policyId = Text
a} :: DeleteLifecyclePolicy)

instance Core.AWSRequest DeleteLifecyclePolicy where
  type
    AWSResponse DeleteLifecyclePolicy =
      DeleteLifecyclePolicyResponse
  request :: (Service -> Service)
-> DeleteLifecyclePolicy -> Request DeleteLifecyclePolicy
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 DeleteLifecyclePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteLifecyclePolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteLifecyclePolicyResponse
DeleteLifecyclePolicyResponse'
            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 DeleteLifecyclePolicy where
  hashWithSalt :: Int -> DeleteLifecyclePolicy -> Int
hashWithSalt Int
_salt DeleteLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:DeleteLifecyclePolicy' :: DeleteLifecyclePolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyId

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

instance Data.ToHeaders DeleteLifecyclePolicy where
  toHeaders :: DeleteLifecyclePolicy -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteLifecyclePolicy where
  toPath :: DeleteLifecyclePolicy -> ByteString
toPath DeleteLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:DeleteLifecyclePolicy' :: DeleteLifecyclePolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyId, ByteString
"/"]

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

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

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

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

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