{-# 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.GetRolePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the specified inline policy document that is embedded with the
-- specified IAM role.
--
-- Policies returned by this operation are URL-encoded compliant with
-- <https://tools.ietf.org/html/rfc3986 RFC 3986>. You can use a URL
-- decoding method to convert the policy back to plain JSON text. For
-- example, if you use Java, you can use the @decode@ method of the
-- @java.net.URLDecoder@ utility class in the Java SDK. Other languages and
-- SDKs provide similar functionality.
--
-- An IAM role can also have managed policies attached to it. To retrieve a
-- managed policy document that is attached to a role, use GetPolicy to
-- determine the policy\'s default version, then use GetPolicyVersion to
-- retrieve the policy document.
--
-- 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/.
--
-- For more information about roles, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/roles-toplevel.html Using roles to delegate permissions and federate identities>.
module Amazonka.IAM.GetRolePolicy
  ( -- * Creating a Request
    GetRolePolicy (..),
    newGetRolePolicy,

    -- * Request Lenses
    getRolePolicy_roleName,
    getRolePolicy_policyName,

    -- * Destructuring the Response
    GetRolePolicyResponse (..),
    newGetRolePolicyResponse,

    -- * Response Lenses
    getRolePolicyResponse_httpStatus,
    getRolePolicyResponse_roleName,
    getRolePolicyResponse_policyName,
    getRolePolicyResponse_policyDocument,
  )
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:/ 'newGetRolePolicy' smart constructor.
data GetRolePolicy = GetRolePolicy'
  { -- | The name of the role associated with the policy.
    --
    -- 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: _+=,.\@-
    GetRolePolicy -> Text
roleName :: Prelude.Text,
    -- | The name of the policy document to get.
    --
    -- 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: _+=,.\@-
    GetRolePolicy -> Text
policyName :: Prelude.Text
  }
  deriving (GetRolePolicy -> GetRolePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRolePolicy -> GetRolePolicy -> Bool
$c/= :: GetRolePolicy -> GetRolePolicy -> Bool
== :: GetRolePolicy -> GetRolePolicy -> Bool
$c== :: GetRolePolicy -> GetRolePolicy -> Bool
Prelude.Eq, ReadPrec [GetRolePolicy]
ReadPrec GetRolePolicy
Int -> ReadS GetRolePolicy
ReadS [GetRolePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRolePolicy]
$creadListPrec :: ReadPrec [GetRolePolicy]
readPrec :: ReadPrec GetRolePolicy
$creadPrec :: ReadPrec GetRolePolicy
readList :: ReadS [GetRolePolicy]
$creadList :: ReadS [GetRolePolicy]
readsPrec :: Int -> ReadS GetRolePolicy
$creadsPrec :: Int -> ReadS GetRolePolicy
Prelude.Read, Int -> GetRolePolicy -> ShowS
[GetRolePolicy] -> ShowS
GetRolePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRolePolicy] -> ShowS
$cshowList :: [GetRolePolicy] -> ShowS
show :: GetRolePolicy -> String
$cshow :: GetRolePolicy -> String
showsPrec :: Int -> GetRolePolicy -> ShowS
$cshowsPrec :: Int -> GetRolePolicy -> ShowS
Prelude.Show, forall x. Rep GetRolePolicy x -> GetRolePolicy
forall x. GetRolePolicy -> Rep GetRolePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRolePolicy x -> GetRolePolicy
$cfrom :: forall x. GetRolePolicy -> Rep GetRolePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetRolePolicy' 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', 'getRolePolicy_roleName' - The name of the role associated with the policy.
--
-- 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: _+=,.\@-
--
-- 'policyName', 'getRolePolicy_policyName' - The name of the policy document to get.
--
-- 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: _+=,.\@-
newGetRolePolicy ::
  -- | 'roleName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  GetRolePolicy
newGetRolePolicy :: Text -> Text -> GetRolePolicy
newGetRolePolicy Text
pRoleName_ Text
pPolicyName_ =
  GetRolePolicy'
    { $sel:roleName:GetRolePolicy' :: Text
roleName = Text
pRoleName_,
      $sel:policyName:GetRolePolicy' :: Text
policyName = Text
pPolicyName_
    }

-- | The name of the role associated with the policy.
--
-- 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: _+=,.\@-
getRolePolicy_roleName :: Lens.Lens' GetRolePolicy Prelude.Text
getRolePolicy_roleName :: Lens' GetRolePolicy Text
getRolePolicy_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRolePolicy' {Text
roleName :: Text
$sel:roleName:GetRolePolicy' :: GetRolePolicy -> Text
roleName} -> Text
roleName) (\s :: GetRolePolicy
s@GetRolePolicy' {} Text
a -> GetRolePolicy
s {$sel:roleName:GetRolePolicy' :: Text
roleName = Text
a} :: GetRolePolicy)

-- | The name of the policy document to get.
--
-- 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: _+=,.\@-
getRolePolicy_policyName :: Lens.Lens' GetRolePolicy Prelude.Text
getRolePolicy_policyName :: Lens' GetRolePolicy Text
getRolePolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRolePolicy' {Text
policyName :: Text
$sel:policyName:GetRolePolicy' :: GetRolePolicy -> Text
policyName} -> Text
policyName) (\s :: GetRolePolicy
s@GetRolePolicy' {} Text
a -> GetRolePolicy
s {$sel:policyName:GetRolePolicy' :: Text
policyName = Text
a} :: GetRolePolicy)

instance Core.AWSRequest GetRolePolicy where
  type
    AWSResponse GetRolePolicy =
      GetRolePolicyResponse
  request :: (Service -> Service) -> GetRolePolicy -> Request GetRolePolicy
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 GetRolePolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRolePolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"GetRolePolicyResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> Text -> Text -> Text -> GetRolePolicyResponse
GetRolePolicyResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"RoleName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"PolicyName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"PolicyDocument")
      )

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

instance Prelude.NFData GetRolePolicy where
  rnf :: GetRolePolicy -> ()
rnf GetRolePolicy' {Text
policyName :: Text
roleName :: Text
$sel:policyName:GetRolePolicy' :: GetRolePolicy -> Text
$sel:roleName:GetRolePolicy' :: GetRolePolicy -> 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
policyName

instance Data.ToHeaders GetRolePolicy where
  toHeaders :: GetRolePolicy -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery GetRolePolicy where
  toQuery :: GetRolePolicy -> QueryString
toQuery GetRolePolicy' {Text
policyName :: Text
roleName :: Text
$sel:policyName:GetRolePolicy' :: GetRolePolicy -> Text
$sel:roleName:GetRolePolicy' :: GetRolePolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetRolePolicy" :: 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
"PolicyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyName
      ]

-- | Contains the response to a successful GetRolePolicy request.
--
-- /See:/ 'newGetRolePolicyResponse' smart constructor.
data GetRolePolicyResponse = GetRolePolicyResponse'
  { -- | The response's http status code.
    GetRolePolicyResponse -> Int
httpStatus :: Prelude.Int,
    -- | The role the policy is associated with.
    GetRolePolicyResponse -> Text
roleName :: Prelude.Text,
    -- | The name of the policy.
    GetRolePolicyResponse -> Text
policyName :: Prelude.Text,
    -- | The policy document.
    --
    -- IAM stores policies in JSON format. However, resources that were created
    -- using CloudFormation templates can be formatted in YAML. CloudFormation
    -- always converts a YAML policy to JSON format before submitting it to
    -- IAM.
    GetRolePolicyResponse -> Text
policyDocument :: Prelude.Text
  }
  deriving (GetRolePolicyResponse -> GetRolePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRolePolicyResponse -> GetRolePolicyResponse -> Bool
$c/= :: GetRolePolicyResponse -> GetRolePolicyResponse -> Bool
== :: GetRolePolicyResponse -> GetRolePolicyResponse -> Bool
$c== :: GetRolePolicyResponse -> GetRolePolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetRolePolicyResponse]
ReadPrec GetRolePolicyResponse
Int -> ReadS GetRolePolicyResponse
ReadS [GetRolePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRolePolicyResponse]
$creadListPrec :: ReadPrec [GetRolePolicyResponse]
readPrec :: ReadPrec GetRolePolicyResponse
$creadPrec :: ReadPrec GetRolePolicyResponse
readList :: ReadS [GetRolePolicyResponse]
$creadList :: ReadS [GetRolePolicyResponse]
readsPrec :: Int -> ReadS GetRolePolicyResponse
$creadsPrec :: Int -> ReadS GetRolePolicyResponse
Prelude.Read, Int -> GetRolePolicyResponse -> ShowS
[GetRolePolicyResponse] -> ShowS
GetRolePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRolePolicyResponse] -> ShowS
$cshowList :: [GetRolePolicyResponse] -> ShowS
show :: GetRolePolicyResponse -> String
$cshow :: GetRolePolicyResponse -> String
showsPrec :: Int -> GetRolePolicyResponse -> ShowS
$cshowsPrec :: Int -> GetRolePolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetRolePolicyResponse x -> GetRolePolicyResponse
forall x. GetRolePolicyResponse -> Rep GetRolePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRolePolicyResponse x -> GetRolePolicyResponse
$cfrom :: forall x. GetRolePolicyResponse -> Rep GetRolePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRolePolicyResponse' 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', 'getRolePolicyResponse_httpStatus' - The response's http status code.
--
-- 'roleName', 'getRolePolicyResponse_roleName' - The role the policy is associated with.
--
-- 'policyName', 'getRolePolicyResponse_policyName' - The name of the policy.
--
-- 'policyDocument', 'getRolePolicyResponse_policyDocument' - The policy document.
--
-- IAM stores policies in JSON format. However, resources that were created
-- using CloudFormation templates can be formatted in YAML. CloudFormation
-- always converts a YAML policy to JSON format before submitting it to
-- IAM.
newGetRolePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'roleName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  GetRolePolicyResponse
newGetRolePolicyResponse :: Int -> Text -> Text -> Text -> GetRolePolicyResponse
newGetRolePolicyResponse
  Int
pHttpStatus_
  Text
pRoleName_
  Text
pPolicyName_
  Text
pPolicyDocument_ =
    GetRolePolicyResponse'
      { $sel:httpStatus:GetRolePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:roleName:GetRolePolicyResponse' :: Text
roleName = Text
pRoleName_,
        $sel:policyName:GetRolePolicyResponse' :: Text
policyName = Text
pPolicyName_,
        $sel:policyDocument:GetRolePolicyResponse' :: Text
policyDocument = Text
pPolicyDocument_
      }

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

-- | The role the policy is associated with.
getRolePolicyResponse_roleName :: Lens.Lens' GetRolePolicyResponse Prelude.Text
getRolePolicyResponse_roleName :: Lens' GetRolePolicyResponse Text
getRolePolicyResponse_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRolePolicyResponse' {Text
roleName :: Text
$sel:roleName:GetRolePolicyResponse' :: GetRolePolicyResponse -> Text
roleName} -> Text
roleName) (\s :: GetRolePolicyResponse
s@GetRolePolicyResponse' {} Text
a -> GetRolePolicyResponse
s {$sel:roleName:GetRolePolicyResponse' :: Text
roleName = Text
a} :: GetRolePolicyResponse)

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

-- | The policy document.
--
-- IAM stores policies in JSON format. However, resources that were created
-- using CloudFormation templates can be formatted in YAML. CloudFormation
-- always converts a YAML policy to JSON format before submitting it to
-- IAM.
getRolePolicyResponse_policyDocument :: Lens.Lens' GetRolePolicyResponse Prelude.Text
getRolePolicyResponse_policyDocument :: Lens' GetRolePolicyResponse Text
getRolePolicyResponse_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRolePolicyResponse' {Text
policyDocument :: Text
$sel:policyDocument:GetRolePolicyResponse' :: GetRolePolicyResponse -> Text
policyDocument} -> Text
policyDocument) (\s :: GetRolePolicyResponse
s@GetRolePolicyResponse' {} Text
a -> GetRolePolicyResponse
s {$sel:policyDocument:GetRolePolicyResponse' :: Text
policyDocument = Text
a} :: GetRolePolicyResponse)

instance Prelude.NFData GetRolePolicyResponse where
  rnf :: GetRolePolicyResponse -> ()
rnf GetRolePolicyResponse' {Int
Text
policyDocument :: Text
policyName :: Text
roleName :: Text
httpStatus :: Int
$sel:policyDocument:GetRolePolicyResponse' :: GetRolePolicyResponse -> Text
$sel:policyName:GetRolePolicyResponse' :: GetRolePolicyResponse -> Text
$sel:roleName:GetRolePolicyResponse' :: GetRolePolicyResponse -> Text
$sel:httpStatus:GetRolePolicyResponse' :: GetRolePolicyResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyDocument