{-# 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.AttachRolePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches the specified managed policy to the specified IAM role. When
-- you attach a managed policy to a role, the managed policy becomes part
-- of the role\'s permission (access) policy.
--
-- You cannot use a managed policy as the role\'s trust policy. The role\'s
-- trust policy is created at the same time as the role, using CreateRole.
-- You can update a role\'s trust policy using UpdateAssumeRolePolicy.
--
-- Use this operation to attach a /managed/ policy to a role. To embed an
-- inline policy in a role, use PutRolePolicy. For more information about
-- 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/.
--
-- As a best practice, you can validate your IAM policies. To learn more,
-- see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_policy-validator.html Validating IAM policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.AttachRolePolicy
  ( -- * Creating a Request
    AttachRolePolicy (..),
    newAttachRolePolicy,

    -- * Request Lenses
    attachRolePolicy_roleName,
    attachRolePolicy_policyArn,

    -- * Destructuring the Response
    AttachRolePolicyResponse (..),
    newAttachRolePolicyResponse,
  )
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:/ 'newAttachRolePolicy' smart constructor.
data AttachRolePolicy = AttachRolePolicy'
  { -- | The name (friendly name, not ARN) of the role to attach the policy to.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    AttachRolePolicy -> Text
roleName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM policy you want to attach.
    --
    -- 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/.
    AttachRolePolicy -> Text
policyArn :: Prelude.Text
  }
  deriving (AttachRolePolicy -> AttachRolePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachRolePolicy -> AttachRolePolicy -> Bool
$c/= :: AttachRolePolicy -> AttachRolePolicy -> Bool
== :: AttachRolePolicy -> AttachRolePolicy -> Bool
$c== :: AttachRolePolicy -> AttachRolePolicy -> Bool
Prelude.Eq, ReadPrec [AttachRolePolicy]
ReadPrec AttachRolePolicy
Int -> ReadS AttachRolePolicy
ReadS [AttachRolePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachRolePolicy]
$creadListPrec :: ReadPrec [AttachRolePolicy]
readPrec :: ReadPrec AttachRolePolicy
$creadPrec :: ReadPrec AttachRolePolicy
readList :: ReadS [AttachRolePolicy]
$creadList :: ReadS [AttachRolePolicy]
readsPrec :: Int -> ReadS AttachRolePolicy
$creadsPrec :: Int -> ReadS AttachRolePolicy
Prelude.Read, Int -> AttachRolePolicy -> ShowS
[AttachRolePolicy] -> ShowS
AttachRolePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachRolePolicy] -> ShowS
$cshowList :: [AttachRolePolicy] -> ShowS
show :: AttachRolePolicy -> String
$cshow :: AttachRolePolicy -> String
showsPrec :: Int -> AttachRolePolicy -> ShowS
$cshowsPrec :: Int -> AttachRolePolicy -> ShowS
Prelude.Show, forall x. Rep AttachRolePolicy x -> AttachRolePolicy
forall x. AttachRolePolicy -> Rep AttachRolePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachRolePolicy x -> AttachRolePolicy
$cfrom :: forall x. AttachRolePolicy -> Rep AttachRolePolicy x
Prelude.Generic)

-- |
-- Create a value of 'AttachRolePolicy' 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:
--
-- 'roleName', 'attachRolePolicy_roleName' - The name (friendly name, not ARN) of the role to attach the policy to.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
--
-- 'policyArn', 'attachRolePolicy_policyArn' - The Amazon Resource Name (ARN) of the IAM policy you want to attach.
--
-- 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/.
newAttachRolePolicy ::
  -- | 'roleName'
  Prelude.Text ->
  -- | 'policyArn'
  Prelude.Text ->
  AttachRolePolicy
newAttachRolePolicy :: Text -> Text -> AttachRolePolicy
newAttachRolePolicy Text
pRoleName_ Text
pPolicyArn_ =
  AttachRolePolicy'
    { $sel:roleName:AttachRolePolicy' :: Text
roleName = Text
pRoleName_,
      $sel:policyArn:AttachRolePolicy' :: Text
policyArn = Text
pPolicyArn_
    }

-- | The name (friendly name, not ARN) of the role to attach the policy to.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
attachRolePolicy_roleName :: Lens.Lens' AttachRolePolicy Prelude.Text
attachRolePolicy_roleName :: Lens' AttachRolePolicy Text
attachRolePolicy_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachRolePolicy' {Text
roleName :: Text
$sel:roleName:AttachRolePolicy' :: AttachRolePolicy -> Text
roleName} -> Text
roleName) (\s :: AttachRolePolicy
s@AttachRolePolicy' {} Text
a -> AttachRolePolicy
s {$sel:roleName:AttachRolePolicy' :: Text
roleName = Text
a} :: AttachRolePolicy)

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

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

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

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

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

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

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

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

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

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