{-# 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.IAM.DeletePolicyVersion
-- 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 version from the specified managed policy.
--
-- You cannot delete the default version from a policy using this
-- operation. To delete the default version from a policy, use
-- DeletePolicy. To find out which version of a policy is marked as the
-- default version, use ListPolicyVersions.
--
-- For information about versions for managed policies, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-versions.html Versioning for managed policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.DeletePolicyVersion
  ( -- * Creating a Request
    DeletePolicyVersion (..),
    newDeletePolicyVersion,

    -- * Request Lenses
    deletePolicyVersion_policyArn,
    deletePolicyVersion_versionId,

    -- * Destructuring the Response
    DeletePolicyVersionResponse (..),
    newDeletePolicyVersionResponse,
  )
where

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

-- | /See:/ 'newDeletePolicyVersion' smart constructor.
data DeletePolicyVersion = DeletePolicyVersion'
  { -- | The Amazon Resource Name (ARN) of the IAM policy from which you want to
    -- delete a version.
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    DeletePolicyVersion -> Text
policyArn :: Prelude.Text,
    -- | The policy version to delete.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- that consists of the lowercase letter \'v\' followed by one or two
    -- digits, and optionally followed by a period \'.\' and a string of
    -- letters and digits.
    --
    -- For more information about managed policy versions, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-versions.html Versioning for managed policies>
    -- in the /IAM User Guide/.
    DeletePolicyVersion -> Text
versionId :: Prelude.Text
  }
  deriving (DeletePolicyVersion -> DeletePolicyVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
$c/= :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
== :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
$c== :: DeletePolicyVersion -> DeletePolicyVersion -> Bool
Prelude.Eq, ReadPrec [DeletePolicyVersion]
ReadPrec DeletePolicyVersion
Int -> ReadS DeletePolicyVersion
ReadS [DeletePolicyVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePolicyVersion]
$creadListPrec :: ReadPrec [DeletePolicyVersion]
readPrec :: ReadPrec DeletePolicyVersion
$creadPrec :: ReadPrec DeletePolicyVersion
readList :: ReadS [DeletePolicyVersion]
$creadList :: ReadS [DeletePolicyVersion]
readsPrec :: Int -> ReadS DeletePolicyVersion
$creadsPrec :: Int -> ReadS DeletePolicyVersion
Prelude.Read, Int -> DeletePolicyVersion -> ShowS
[DeletePolicyVersion] -> ShowS
DeletePolicyVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePolicyVersion] -> ShowS
$cshowList :: [DeletePolicyVersion] -> ShowS
show :: DeletePolicyVersion -> String
$cshow :: DeletePolicyVersion -> String
showsPrec :: Int -> DeletePolicyVersion -> ShowS
$cshowsPrec :: Int -> DeletePolicyVersion -> ShowS
Prelude.Show, forall x. Rep DeletePolicyVersion x -> DeletePolicyVersion
forall x. DeletePolicyVersion -> Rep DeletePolicyVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePolicyVersion x -> DeletePolicyVersion
$cfrom :: forall x. DeletePolicyVersion -> Rep DeletePolicyVersion x
Prelude.Generic)

-- |
-- Create a value of 'DeletePolicyVersion' 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:
--
-- 'policyArn', 'deletePolicyVersion_policyArn' - The Amazon Resource Name (ARN) of the IAM policy from which you want to
-- delete a version.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
--
-- 'versionId', 'deletePolicyVersion_versionId' - The policy version to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that consists of the lowercase letter \'v\' followed by one or two
-- digits, and optionally followed by a period \'.\' and a string of
-- letters and digits.
--
-- For more information about managed policy versions, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-versions.html Versioning for managed policies>
-- in the /IAM User Guide/.
newDeletePolicyVersion ::
  -- | 'policyArn'
  Prelude.Text ->
  -- | 'versionId'
  Prelude.Text ->
  DeletePolicyVersion
newDeletePolicyVersion :: Text -> Text -> DeletePolicyVersion
newDeletePolicyVersion Text
pPolicyArn_ Text
pVersionId_ =
  DeletePolicyVersion'
    { $sel:policyArn:DeletePolicyVersion' :: Text
policyArn = Text
pPolicyArn_,
      $sel:versionId:DeletePolicyVersion' :: Text
versionId = Text
pVersionId_
    }

-- | The Amazon Resource Name (ARN) of the IAM policy from which you want to
-- delete a version.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
deletePolicyVersion_policyArn :: Lens.Lens' DeletePolicyVersion Prelude.Text
deletePolicyVersion_policyArn :: Lens' DeletePolicyVersion Text
deletePolicyVersion_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePolicyVersion' {Text
policyArn :: Text
$sel:policyArn:DeletePolicyVersion' :: DeletePolicyVersion -> Text
policyArn} -> Text
policyArn) (\s :: DeletePolicyVersion
s@DeletePolicyVersion' {} Text
a -> DeletePolicyVersion
s {$sel:policyArn:DeletePolicyVersion' :: Text
policyArn = Text
a} :: DeletePolicyVersion)

-- | The policy version to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that consists of the lowercase letter \'v\' followed by one or two
-- digits, and optionally followed by a period \'.\' and a string of
-- letters and digits.
--
-- For more information about managed policy versions, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-versions.html Versioning for managed policies>
-- in the /IAM User Guide/.
deletePolicyVersion_versionId :: Lens.Lens' DeletePolicyVersion Prelude.Text
deletePolicyVersion_versionId :: Lens' DeletePolicyVersion Text
deletePolicyVersion_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePolicyVersion' {Text
versionId :: Text
$sel:versionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
versionId} -> Text
versionId) (\s :: DeletePolicyVersion
s@DeletePolicyVersion' {} Text
a -> DeletePolicyVersion
s {$sel:versionId:DeletePolicyVersion' :: Text
versionId = Text
a} :: DeletePolicyVersion)

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

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

instance Prelude.NFData DeletePolicyVersion where
  rnf :: DeletePolicyVersion -> ()
rnf DeletePolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
$sel:policyArn:DeletePolicyVersion' :: DeletePolicyVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
versionId

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

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

instance Data.ToQuery DeletePolicyVersion where
  toQuery :: DeletePolicyVersion -> QueryString
toQuery DeletePolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:DeletePolicyVersion' :: DeletePolicyVersion -> Text
$sel:policyArn:DeletePolicyVersion' :: DeletePolicyVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeletePolicyVersion" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"PolicyArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyArn,
        ByteString
"VersionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
versionId
      ]

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

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

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