{-# 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.GetUserPolicy
-- 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 in the
-- specified IAM user.
--
-- 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 user can also have managed policies attached to it. To retrieve a
-- managed policy document that is attached to a user, 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/.
module Amazonka.IAM.GetUserPolicy
  ( -- * Creating a Request
    GetUserPolicy (..),
    newGetUserPolicy,

    -- * Request Lenses
    getUserPolicy_userName,
    getUserPolicy_policyName,

    -- * Destructuring the Response
    GetUserPolicyResponse (..),
    newGetUserPolicyResponse,

    -- * Response Lenses
    getUserPolicyResponse_httpStatus,
    getUserPolicyResponse_userName,
    getUserPolicyResponse_policyName,
    getUserPolicyResponse_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:/ 'newGetUserPolicy' smart constructor.
data GetUserPolicy = GetUserPolicy'
  { -- | The name of the user who the policy is associated with.
    --
    -- 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: _+=,.\@-
    GetUserPolicy -> Text
userName :: 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: _+=,.\@-
    GetUserPolicy -> Text
policyName :: Prelude.Text
  }
  deriving (GetUserPolicy -> GetUserPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUserPolicy -> GetUserPolicy -> Bool
$c/= :: GetUserPolicy -> GetUserPolicy -> Bool
== :: GetUserPolicy -> GetUserPolicy -> Bool
$c== :: GetUserPolicy -> GetUserPolicy -> Bool
Prelude.Eq, ReadPrec [GetUserPolicy]
ReadPrec GetUserPolicy
Int -> ReadS GetUserPolicy
ReadS [GetUserPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetUserPolicy]
$creadListPrec :: ReadPrec [GetUserPolicy]
readPrec :: ReadPrec GetUserPolicy
$creadPrec :: ReadPrec GetUserPolicy
readList :: ReadS [GetUserPolicy]
$creadList :: ReadS [GetUserPolicy]
readsPrec :: Int -> ReadS GetUserPolicy
$creadsPrec :: Int -> ReadS GetUserPolicy
Prelude.Read, Int -> GetUserPolicy -> ShowS
[GetUserPolicy] -> ShowS
GetUserPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUserPolicy] -> ShowS
$cshowList :: [GetUserPolicy] -> ShowS
show :: GetUserPolicy -> String
$cshow :: GetUserPolicy -> String
showsPrec :: Int -> GetUserPolicy -> ShowS
$cshowsPrec :: Int -> GetUserPolicy -> ShowS
Prelude.Show, forall x. Rep GetUserPolicy x -> GetUserPolicy
forall x. GetUserPolicy -> Rep GetUserPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUserPolicy x -> GetUserPolicy
$cfrom :: forall x. GetUserPolicy -> Rep GetUserPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetUserPolicy' 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:
--
-- 'userName', 'getUserPolicy_userName' - The name of the user who the policy is associated with.
--
-- 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', 'getUserPolicy_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: _+=,.\@-
newGetUserPolicy ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  GetUserPolicy
newGetUserPolicy :: Text -> Text -> GetUserPolicy
newGetUserPolicy Text
pUserName_ Text
pPolicyName_ =
  GetUserPolicy'
    { $sel:userName:GetUserPolicy' :: Text
userName = Text
pUserName_,
      $sel:policyName:GetUserPolicy' :: Text
policyName = Text
pPolicyName_
    }

-- | The name of the user who the policy is associated with.
--
-- 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: _+=,.\@-
getUserPolicy_userName :: Lens.Lens' GetUserPolicy Prelude.Text
getUserPolicy_userName :: Lens' GetUserPolicy Text
getUserPolicy_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetUserPolicy' {Text
userName :: Text
$sel:userName:GetUserPolicy' :: GetUserPolicy -> Text
userName} -> Text
userName) (\s :: GetUserPolicy
s@GetUserPolicy' {} Text
a -> GetUserPolicy
s {$sel:userName:GetUserPolicy' :: Text
userName = Text
a} :: GetUserPolicy)

-- | 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: _+=,.\@-
getUserPolicy_policyName :: Lens.Lens' GetUserPolicy Prelude.Text
getUserPolicy_policyName :: Lens' GetUserPolicy Text
getUserPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetUserPolicy' {Text
policyName :: Text
$sel:policyName:GetUserPolicy' :: GetUserPolicy -> Text
policyName} -> Text
policyName) (\s :: GetUserPolicy
s@GetUserPolicy' {} Text
a -> GetUserPolicy
s {$sel:policyName:GetUserPolicy' :: Text
policyName = Text
a} :: GetUserPolicy)

instance Core.AWSRequest GetUserPolicy where
  type
    AWSResponse GetUserPolicy =
      GetUserPolicyResponse
  request :: (Service -> Service) -> GetUserPolicy -> Request GetUserPolicy
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 GetUserPolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetUserPolicy)))
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
"GetUserPolicyResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> Text -> Text -> Text -> GetUserPolicyResponse
GetUserPolicyResponse'
            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
"UserName")
            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 GetUserPolicy where
  hashWithSalt :: Int -> GetUserPolicy -> Int
hashWithSalt Int
_salt GetUserPolicy' {Text
policyName :: Text
userName :: Text
$sel:policyName:GetUserPolicy' :: GetUserPolicy -> Text
$sel:userName:GetUserPolicy' :: GetUserPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName

instance Prelude.NFData GetUserPolicy where
  rnf :: GetUserPolicy -> ()
rnf GetUserPolicy' {Text
policyName :: Text
userName :: Text
$sel:policyName:GetUserPolicy' :: GetUserPolicy -> Text
$sel:userName:GetUserPolicy' :: GetUserPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyName

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

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

instance Data.ToQuery GetUserPolicy where
  toQuery :: GetUserPolicy -> QueryString
toQuery GetUserPolicy' {Text
policyName :: Text
userName :: Text
$sel:policyName:GetUserPolicy' :: GetUserPolicy -> Text
$sel:userName:GetUserPolicy' :: GetUserPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetUserPolicy" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"UserName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
userName,
        ByteString
"PolicyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyName
      ]

-- | Contains the response to a successful GetUserPolicy request.
--
-- /See:/ 'newGetUserPolicyResponse' smart constructor.
data GetUserPolicyResponse = GetUserPolicyResponse'
  { -- | The response's http status code.
    GetUserPolicyResponse -> Int
httpStatus :: Prelude.Int,
    -- | The user the policy is associated with.
    GetUserPolicyResponse -> Text
userName :: Prelude.Text,
    -- | The name of the policy.
    GetUserPolicyResponse -> 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.
    GetUserPolicyResponse -> Text
policyDocument :: Prelude.Text
  }
  deriving (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c/= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
== :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c== :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetUserPolicyResponse]
ReadPrec GetUserPolicyResponse
Int -> ReadS GetUserPolicyResponse
ReadS [GetUserPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetUserPolicyResponse]
$creadListPrec :: ReadPrec [GetUserPolicyResponse]
readPrec :: ReadPrec GetUserPolicyResponse
$creadPrec :: ReadPrec GetUserPolicyResponse
readList :: ReadS [GetUserPolicyResponse]
$creadList :: ReadS [GetUserPolicyResponse]
readsPrec :: Int -> ReadS GetUserPolicyResponse
$creadsPrec :: Int -> ReadS GetUserPolicyResponse
Prelude.Read, Int -> GetUserPolicyResponse -> ShowS
[GetUserPolicyResponse] -> ShowS
GetUserPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUserPolicyResponse] -> ShowS
$cshowList :: [GetUserPolicyResponse] -> ShowS
show :: GetUserPolicyResponse -> String
$cshow :: GetUserPolicyResponse -> String
showsPrec :: Int -> GetUserPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetUserPolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetUserPolicyResponse x -> GetUserPolicyResponse
forall x. GetUserPolicyResponse -> Rep GetUserPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUserPolicyResponse x -> GetUserPolicyResponse
$cfrom :: forall x. GetUserPolicyResponse -> Rep GetUserPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetUserPolicyResponse' 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', 'getUserPolicyResponse_httpStatus' - The response's http status code.
--
-- 'userName', 'getUserPolicyResponse_userName' - The user the policy is associated with.
--
-- 'policyName', 'getUserPolicyResponse_policyName' - The name of the policy.
--
-- 'policyDocument', 'getUserPolicyResponse_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.
newGetUserPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'userName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  GetUserPolicyResponse
newGetUserPolicyResponse :: Int -> Text -> Text -> Text -> GetUserPolicyResponse
newGetUserPolicyResponse
  Int
pHttpStatus_
  Text
pUserName_
  Text
pPolicyName_
  Text
pPolicyDocument_ =
    GetUserPolicyResponse'
      { $sel:httpStatus:GetUserPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:userName:GetUserPolicyResponse' :: Text
userName = Text
pUserName_,
        $sel:policyName:GetUserPolicyResponse' :: Text
policyName = Text
pPolicyName_,
        $sel:policyDocument:GetUserPolicyResponse' :: Text
policyDocument = Text
pPolicyDocument_
      }

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

-- | The user the policy is associated with.
getUserPolicyResponse_userName :: Lens.Lens' GetUserPolicyResponse Prelude.Text
getUserPolicyResponse_userName :: Lens' GetUserPolicyResponse Text
getUserPolicyResponse_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetUserPolicyResponse' {Text
userName :: Text
$sel:userName:GetUserPolicyResponse' :: GetUserPolicyResponse -> Text
userName} -> Text
userName) (\s :: GetUserPolicyResponse
s@GetUserPolicyResponse' {} Text
a -> GetUserPolicyResponse
s {$sel:userName:GetUserPolicyResponse' :: Text
userName = Text
a} :: GetUserPolicyResponse)

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

-- | 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.
getUserPolicyResponse_policyDocument :: Lens.Lens' GetUserPolicyResponse Prelude.Text
getUserPolicyResponse_policyDocument :: Lens' GetUserPolicyResponse Text
getUserPolicyResponse_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetUserPolicyResponse' {Text
policyDocument :: Text
$sel:policyDocument:GetUserPolicyResponse' :: GetUserPolicyResponse -> Text
policyDocument} -> Text
policyDocument) (\s :: GetUserPolicyResponse
s@GetUserPolicyResponse' {} Text
a -> GetUserPolicyResponse
s {$sel:policyDocument:GetUserPolicyResponse' :: Text
policyDocument = Text
a} :: GetUserPolicyResponse)

instance Prelude.NFData GetUserPolicyResponse where
  rnf :: GetUserPolicyResponse -> ()
rnf GetUserPolicyResponse' {Int
Text
policyDocument :: Text
policyName :: Text
userName :: Text
httpStatus :: Int
$sel:policyDocument:GetUserPolicyResponse' :: GetUserPolicyResponse -> Text
$sel:policyName:GetUserPolicyResponse' :: GetUserPolicyResponse -> Text
$sel:userName:GetUserPolicyResponse' :: GetUserPolicyResponse -> Text
$sel:httpStatus:GetUserPolicyResponse' :: GetUserPolicyResponse -> 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
userName
      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