{-# 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.IoT.DeletePolicy
-- 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 policy.
--
-- A policy cannot be deleted if it has non-default versions or it is
-- attached to any certificate.
--
-- To delete a policy, use the DeletePolicyVersion action to delete all
-- non-default versions of the policy; use the DetachPolicy action to
-- detach the policy from any certificate; and then use the DeletePolicy
-- action to delete the policy.
--
-- When a policy is deleted using DeletePolicy, its default version is
-- deleted with it.
--
-- Because of the distributed nature of Amazon Web Services, it can take up
-- to five minutes after a policy is detached before it\'s ready to be
-- deleted.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DeletePolicy>
-- action.
module Amazonka.IoT.DeletePolicy
  ( -- * Creating a Request
    DeletePolicy (..),
    newDeletePolicy,

    -- * Request Lenses
    deletePolicy_policyName,

    -- * Destructuring the Response
    DeletePolicyResponse (..),
    newDeletePolicyResponse,
  )
where

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

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

-- |
-- Create a value of 'DeletePolicy' 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:
--
-- 'policyName', 'deletePolicy_policyName' - The name of the policy to delete.
newDeletePolicy ::
  -- | 'policyName'
  Prelude.Text ->
  DeletePolicy
newDeletePolicy :: Text -> DeletePolicy
newDeletePolicy Text
pPolicyName_ =
  DeletePolicy' {$sel:policyName:DeletePolicy' :: Text
policyName = Text
pPolicyName_}

-- | The name of the policy to delete.
deletePolicy_policyName :: Lens.Lens' DeletePolicy Prelude.Text
deletePolicy_policyName :: Lens' DeletePolicy Text
deletePolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePolicy' {Text
policyName :: Text
$sel:policyName:DeletePolicy' :: DeletePolicy -> Text
policyName} -> Text
policyName) (\s :: DeletePolicy
s@DeletePolicy' {} Text
a -> DeletePolicy
s {$sel:policyName:DeletePolicy' :: Text
policyName = Text
a} :: DeletePolicy)

instance Core.AWSRequest DeletePolicy where
  type AWSResponse DeletePolicy = DeletePolicyResponse
  request :: (Service -> Service) -> DeletePolicy -> Request DeletePolicy
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 DeletePolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeletePolicy)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeletePolicyResponse
DeletePolicyResponse'

instance Prelude.Hashable DeletePolicy where
  hashWithSalt :: Int -> DeletePolicy -> Int
hashWithSalt Int
_salt DeletePolicy' {Text
policyName :: Text
$sel:policyName:DeletePolicy' :: DeletePolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName

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

instance Data.ToHeaders DeletePolicy where
  toHeaders :: DeletePolicy -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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

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

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