{-# 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.SetDefaultPolicyVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets the specified version of the specified policy as the policy\'s
-- default (operative) version.
--
-- This operation affects all users, groups, and roles that the policy is
-- attached to. To list the users, groups, and roles that the policy is
-- attached to, use ListEntitiesForPolicy.
--
-- For information about managed policies, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.SetDefaultPolicyVersion
  ( -- * Creating a Request
    SetDefaultPolicyVersion (..),
    newSetDefaultPolicyVersion,

    -- * Request Lenses
    setDefaultPolicyVersion_policyArn,
    setDefaultPolicyVersion_versionId,

    -- * Destructuring the Response
    SetDefaultPolicyVersionResponse (..),
    newSetDefaultPolicyVersionResponse,
  )
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:/ 'newSetDefaultPolicyVersion' smart constructor.
data SetDefaultPolicyVersion = SetDefaultPolicyVersion'
  { -- | The Amazon Resource Name (ARN) of the IAM policy whose default version
    -- you want to set.
    --
    -- 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/.
    SetDefaultPolicyVersion -> Text
policyArn :: Prelude.Text,
    -- | The version of the policy to set as the default (operative) version.
    --
    -- 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/.
    SetDefaultPolicyVersion -> Text
versionId :: Prelude.Text
  }
  deriving (SetDefaultPolicyVersion -> SetDefaultPolicyVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetDefaultPolicyVersion -> SetDefaultPolicyVersion -> Bool
$c/= :: SetDefaultPolicyVersion -> SetDefaultPolicyVersion -> Bool
== :: SetDefaultPolicyVersion -> SetDefaultPolicyVersion -> Bool
$c== :: SetDefaultPolicyVersion -> SetDefaultPolicyVersion -> Bool
Prelude.Eq, ReadPrec [SetDefaultPolicyVersion]
ReadPrec SetDefaultPolicyVersion
Int -> ReadS SetDefaultPolicyVersion
ReadS [SetDefaultPolicyVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetDefaultPolicyVersion]
$creadListPrec :: ReadPrec [SetDefaultPolicyVersion]
readPrec :: ReadPrec SetDefaultPolicyVersion
$creadPrec :: ReadPrec SetDefaultPolicyVersion
readList :: ReadS [SetDefaultPolicyVersion]
$creadList :: ReadS [SetDefaultPolicyVersion]
readsPrec :: Int -> ReadS SetDefaultPolicyVersion
$creadsPrec :: Int -> ReadS SetDefaultPolicyVersion
Prelude.Read, Int -> SetDefaultPolicyVersion -> ShowS
[SetDefaultPolicyVersion] -> ShowS
SetDefaultPolicyVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetDefaultPolicyVersion] -> ShowS
$cshowList :: [SetDefaultPolicyVersion] -> ShowS
show :: SetDefaultPolicyVersion -> String
$cshow :: SetDefaultPolicyVersion -> String
showsPrec :: Int -> SetDefaultPolicyVersion -> ShowS
$cshowsPrec :: Int -> SetDefaultPolicyVersion -> ShowS
Prelude.Show, forall x. Rep SetDefaultPolicyVersion x -> SetDefaultPolicyVersion
forall x. SetDefaultPolicyVersion -> Rep SetDefaultPolicyVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetDefaultPolicyVersion x -> SetDefaultPolicyVersion
$cfrom :: forall x. SetDefaultPolicyVersion -> Rep SetDefaultPolicyVersion x
Prelude.Generic)

-- |
-- Create a value of 'SetDefaultPolicyVersion' 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', 'setDefaultPolicyVersion_policyArn' - The Amazon Resource Name (ARN) of the IAM policy whose default version
-- you want to set.
--
-- 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', 'setDefaultPolicyVersion_versionId' - The version of the policy to set as the default (operative) version.
--
-- 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/.
newSetDefaultPolicyVersion ::
  -- | 'policyArn'
  Prelude.Text ->
  -- | 'versionId'
  Prelude.Text ->
  SetDefaultPolicyVersion
newSetDefaultPolicyVersion :: Text -> Text -> SetDefaultPolicyVersion
newSetDefaultPolicyVersion Text
pPolicyArn_ Text
pVersionId_ =
  SetDefaultPolicyVersion'
    { $sel:policyArn:SetDefaultPolicyVersion' :: Text
policyArn = Text
pPolicyArn_,
      $sel:versionId:SetDefaultPolicyVersion' :: Text
versionId = Text
pVersionId_
    }

-- | The Amazon Resource Name (ARN) of the IAM policy whose default version
-- you want to set.
--
-- 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/.
setDefaultPolicyVersion_policyArn :: Lens.Lens' SetDefaultPolicyVersion Prelude.Text
setDefaultPolicyVersion_policyArn :: Lens' SetDefaultPolicyVersion Text
setDefaultPolicyVersion_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetDefaultPolicyVersion' {Text
policyArn :: Text
$sel:policyArn:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
policyArn} -> Text
policyArn) (\s :: SetDefaultPolicyVersion
s@SetDefaultPolicyVersion' {} Text
a -> SetDefaultPolicyVersion
s {$sel:policyArn:SetDefaultPolicyVersion' :: Text
policyArn = Text
a} :: SetDefaultPolicyVersion)

-- | The version of the policy to set as the default (operative) version.
--
-- 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/.
setDefaultPolicyVersion_versionId :: Lens.Lens' SetDefaultPolicyVersion Prelude.Text
setDefaultPolicyVersion_versionId :: Lens' SetDefaultPolicyVersion Text
setDefaultPolicyVersion_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetDefaultPolicyVersion' {Text
versionId :: Text
$sel:versionId:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
versionId} -> Text
versionId) (\s :: SetDefaultPolicyVersion
s@SetDefaultPolicyVersion' {} Text
a -> SetDefaultPolicyVersion
s {$sel:versionId:SetDefaultPolicyVersion' :: Text
versionId = Text
a} :: SetDefaultPolicyVersion)

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

instance Prelude.Hashable SetDefaultPolicyVersion where
  hashWithSalt :: Int -> SetDefaultPolicyVersion -> Int
hashWithSalt Int
_salt SetDefaultPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
$sel:policyArn:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> 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 SetDefaultPolicyVersion where
  rnf :: SetDefaultPolicyVersion -> ()
rnf SetDefaultPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
$sel:policyArn:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> 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 SetDefaultPolicyVersion where
  toHeaders :: SetDefaultPolicyVersion -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery SetDefaultPolicyVersion where
  toQuery :: SetDefaultPolicyVersion -> QueryString
toQuery SetDefaultPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
$sel:policyArn:SetDefaultPolicyVersion' :: SetDefaultPolicyVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"SetDefaultPolicyVersion" :: 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:/ 'newSetDefaultPolicyVersionResponse' smart constructor.
data SetDefaultPolicyVersionResponse = SetDefaultPolicyVersionResponse'
  {
  }
  deriving (SetDefaultPolicyVersionResponse
-> SetDefaultPolicyVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetDefaultPolicyVersionResponse
-> SetDefaultPolicyVersionResponse -> Bool
$c/= :: SetDefaultPolicyVersionResponse
-> SetDefaultPolicyVersionResponse -> Bool
== :: SetDefaultPolicyVersionResponse
-> SetDefaultPolicyVersionResponse -> Bool
$c== :: SetDefaultPolicyVersionResponse
-> SetDefaultPolicyVersionResponse -> Bool
Prelude.Eq, ReadPrec [SetDefaultPolicyVersionResponse]
ReadPrec SetDefaultPolicyVersionResponse
Int -> ReadS SetDefaultPolicyVersionResponse
ReadS [SetDefaultPolicyVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetDefaultPolicyVersionResponse]
$creadListPrec :: ReadPrec [SetDefaultPolicyVersionResponse]
readPrec :: ReadPrec SetDefaultPolicyVersionResponse
$creadPrec :: ReadPrec SetDefaultPolicyVersionResponse
readList :: ReadS [SetDefaultPolicyVersionResponse]
$creadList :: ReadS [SetDefaultPolicyVersionResponse]
readsPrec :: Int -> ReadS SetDefaultPolicyVersionResponse
$creadsPrec :: Int -> ReadS SetDefaultPolicyVersionResponse
Prelude.Read, Int -> SetDefaultPolicyVersionResponse -> ShowS
[SetDefaultPolicyVersionResponse] -> ShowS
SetDefaultPolicyVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetDefaultPolicyVersionResponse] -> ShowS
$cshowList :: [SetDefaultPolicyVersionResponse] -> ShowS
show :: SetDefaultPolicyVersionResponse -> String
$cshow :: SetDefaultPolicyVersionResponse -> String
showsPrec :: Int -> SetDefaultPolicyVersionResponse -> ShowS
$cshowsPrec :: Int -> SetDefaultPolicyVersionResponse -> ShowS
Prelude.Show, forall x.
Rep SetDefaultPolicyVersionResponse x
-> SetDefaultPolicyVersionResponse
forall x.
SetDefaultPolicyVersionResponse
-> Rep SetDefaultPolicyVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetDefaultPolicyVersionResponse x
-> SetDefaultPolicyVersionResponse
$cfrom :: forall x.
SetDefaultPolicyVersionResponse
-> Rep SetDefaultPolicyVersionResponse x
Prelude.Generic)

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

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