{-# 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.GetRole
-- 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 information about the specified role, including the role\'s
-- path, GUID, ARN, and the role\'s trust policy that grants permission to
-- assume the role. For more information about roles, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/WorkingWithRoles.html Working with roles>.
--
-- 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.
module Amazonka.IAM.GetRole
  ( -- * Creating a Request
    GetRole (..),
    newGetRole,

    -- * Request Lenses
    getRole_roleName,

    -- * Destructuring the Response
    GetRoleResponse (..),
    newGetRoleResponse,

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

-- |
-- Create a value of 'GetRole' 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', 'getRole_roleName' - The name of the IAM role to get information about.
--
-- 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: _+=,.\@-
newGetRole ::
  -- | 'roleName'
  Prelude.Text ->
  GetRole
newGetRole :: Text -> GetRole
newGetRole Text
pRoleName_ =
  GetRole' {$sel:roleName:GetRole' :: Text
roleName = Text
pRoleName_}

-- | The name of the IAM role to get information about.
--
-- 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: _+=,.\@-
getRole_roleName :: Lens.Lens' GetRole Prelude.Text
getRole_roleName :: Lens' GetRole Text
getRole_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRole' {Text
roleName :: Text
$sel:roleName:GetRole' :: GetRole -> Text
roleName} -> Text
roleName) (\s :: GetRole
s@GetRole' {} Text
a -> GetRole
s {$sel:roleName:GetRole' :: Text
roleName = Text
a} :: GetRole)

instance Core.AWSRequest GetRole where
  type AWSResponse GetRole = GetRoleResponse
  request :: (Service -> Service) -> GetRole -> Request GetRole
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 GetRole
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRole)))
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
"GetRoleResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> Role -> GetRoleResponse
GetRoleResponse'
            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
"Role")
      )

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

instance Prelude.NFData GetRole where
  rnf :: GetRole -> ()
rnf GetRole' {Text
roleName :: Text
$sel:roleName:GetRole' :: GetRole -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
roleName

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

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

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

-- | Contains the response to a successful GetRole request.
--
-- /See:/ 'newGetRoleResponse' smart constructor.
data GetRoleResponse = GetRoleResponse'
  { -- | The response's http status code.
    GetRoleResponse -> Int
httpStatus :: Prelude.Int,
    -- | A structure containing details about the IAM role.
    GetRoleResponse -> Role
role' :: Role
  }
  deriving (GetRoleResponse -> GetRoleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRoleResponse -> GetRoleResponse -> Bool
$c/= :: GetRoleResponse -> GetRoleResponse -> Bool
== :: GetRoleResponse -> GetRoleResponse -> Bool
$c== :: GetRoleResponse -> GetRoleResponse -> Bool
Prelude.Eq, ReadPrec [GetRoleResponse]
ReadPrec GetRoleResponse
Int -> ReadS GetRoleResponse
ReadS [GetRoleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRoleResponse]
$creadListPrec :: ReadPrec [GetRoleResponse]
readPrec :: ReadPrec GetRoleResponse
$creadPrec :: ReadPrec GetRoleResponse
readList :: ReadS [GetRoleResponse]
$creadList :: ReadS [GetRoleResponse]
readsPrec :: Int -> ReadS GetRoleResponse
$creadsPrec :: Int -> ReadS GetRoleResponse
Prelude.Read, Int -> GetRoleResponse -> ShowS
[GetRoleResponse] -> ShowS
GetRoleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRoleResponse] -> ShowS
$cshowList :: [GetRoleResponse] -> ShowS
show :: GetRoleResponse -> String
$cshow :: GetRoleResponse -> String
showsPrec :: Int -> GetRoleResponse -> ShowS
$cshowsPrec :: Int -> GetRoleResponse -> ShowS
Prelude.Show, forall x. Rep GetRoleResponse x -> GetRoleResponse
forall x. GetRoleResponse -> Rep GetRoleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRoleResponse x -> GetRoleResponse
$cfrom :: forall x. GetRoleResponse -> Rep GetRoleResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRoleResponse' 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', 'getRoleResponse_httpStatus' - The response's http status code.
--
-- 'role'', 'getRoleResponse_role' - A structure containing details about the IAM role.
newGetRoleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'role''
  Role ->
  GetRoleResponse
newGetRoleResponse :: Int -> Role -> GetRoleResponse
newGetRoleResponse Int
pHttpStatus_ Role
pRole_ =
  GetRoleResponse'
    { $sel:httpStatus:GetRoleResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:role':GetRoleResponse' :: Role
role' = Role
pRole_
    }

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

-- | A structure containing details about the IAM role.
getRoleResponse_role :: Lens.Lens' GetRoleResponse Role
getRoleResponse_role :: Lens' GetRoleResponse Role
getRoleResponse_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRoleResponse' {Role
role' :: Role
$sel:role':GetRoleResponse' :: GetRoleResponse -> Role
role'} -> Role
role') (\s :: GetRoleResponse
s@GetRoleResponse' {} Role
a -> GetRoleResponse
s {$sel:role':GetRoleResponse' :: Role
role' = Role
a} :: GetRoleResponse)

instance Prelude.NFData GetRoleResponse where
  rnf :: GetRoleResponse -> ()
rnf GetRoleResponse' {Int
Role
role' :: Role
httpStatus :: Int
$sel:role':GetRoleResponse' :: GetRoleResponse -> Role
$sel:httpStatus:GetRoleResponse' :: GetRoleResponse -> 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 Role
role'