{-# 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.GetGroupPolicy
-- 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 group.
--
-- 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 group can also have managed policies attached to it. To retrieve
-- a managed policy document that is attached to a group, 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.GetGroupPolicy
  ( -- * Creating a Request
    GetGroupPolicy (..),
    newGetGroupPolicy,

    -- * Request Lenses
    getGroupPolicy_groupName,
    getGroupPolicy_policyName,

    -- * Destructuring the Response
    GetGroupPolicyResponse (..),
    newGetGroupPolicyResponse,

    -- * Response Lenses
    getGroupPolicyResponse_httpStatus,
    getGroupPolicyResponse_groupName,
    getGroupPolicyResponse_policyName,
    getGroupPolicyResponse_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:/ 'newGetGroupPolicy' smart constructor.
data GetGroupPolicy = GetGroupPolicy'
  { -- | The name of the group 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: _+=,.\@-
    GetGroupPolicy -> Text
groupName :: 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: _+=,.\@-
    GetGroupPolicy -> Text
policyName :: Prelude.Text
  }
  deriving (GetGroupPolicy -> GetGroupPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c/= :: GetGroupPolicy -> GetGroupPolicy -> Bool
== :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c== :: GetGroupPolicy -> GetGroupPolicy -> Bool
Prelude.Eq, ReadPrec [GetGroupPolicy]
ReadPrec GetGroupPolicy
Int -> ReadS GetGroupPolicy
ReadS [GetGroupPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupPolicy]
$creadListPrec :: ReadPrec [GetGroupPolicy]
readPrec :: ReadPrec GetGroupPolicy
$creadPrec :: ReadPrec GetGroupPolicy
readList :: ReadS [GetGroupPolicy]
$creadList :: ReadS [GetGroupPolicy]
readsPrec :: Int -> ReadS GetGroupPolicy
$creadsPrec :: Int -> ReadS GetGroupPolicy
Prelude.Read, Int -> GetGroupPolicy -> ShowS
[GetGroupPolicy] -> ShowS
GetGroupPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupPolicy] -> ShowS
$cshowList :: [GetGroupPolicy] -> ShowS
show :: GetGroupPolicy -> String
$cshow :: GetGroupPolicy -> String
showsPrec :: Int -> GetGroupPolicy -> ShowS
$cshowsPrec :: Int -> GetGroupPolicy -> ShowS
Prelude.Show, forall x. Rep GetGroupPolicy x -> GetGroupPolicy
forall x. GetGroupPolicy -> Rep GetGroupPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGroupPolicy x -> GetGroupPolicy
$cfrom :: forall x. GetGroupPolicy -> Rep GetGroupPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupPolicy' 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:
--
-- 'groupName', 'getGroupPolicy_groupName' - The name of the group 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', 'getGroupPolicy_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: _+=,.\@-
newGetGroupPolicy ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  GetGroupPolicy
newGetGroupPolicy :: Text -> Text -> GetGroupPolicy
newGetGroupPolicy Text
pGroupName_ Text
pPolicyName_ =
  GetGroupPolicy'
    { $sel:groupName:GetGroupPolicy' :: Text
groupName = Text
pGroupName_,
      $sel:policyName:GetGroupPolicy' :: Text
policyName = Text
pPolicyName_
    }

-- | The name of the group 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: _+=,.\@-
getGroupPolicy_groupName :: Lens.Lens' GetGroupPolicy Prelude.Text
getGroupPolicy_groupName :: Lens' GetGroupPolicy Text
getGroupPolicy_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupPolicy' {Text
groupName :: Text
$sel:groupName:GetGroupPolicy' :: GetGroupPolicy -> Text
groupName} -> Text
groupName) (\s :: GetGroupPolicy
s@GetGroupPolicy' {} Text
a -> GetGroupPolicy
s {$sel:groupName:GetGroupPolicy' :: Text
groupName = Text
a} :: GetGroupPolicy)

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

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

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

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

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

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

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

-- |
-- Create a value of 'GetGroupPolicyResponse' 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', 'getGroupPolicyResponse_httpStatus' - The response's http status code.
--
-- 'groupName', 'getGroupPolicyResponse_groupName' - The group the policy is associated with.
--
-- 'policyName', 'getGroupPolicyResponse_policyName' - The name of the policy.
--
-- 'policyDocument', 'getGroupPolicyResponse_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.
newGetGroupPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  GetGroupPolicyResponse
newGetGroupPolicyResponse :: Int -> Text -> Text -> Text -> GetGroupPolicyResponse
newGetGroupPolicyResponse
  Int
pHttpStatus_
  Text
pGroupName_
  Text
pPolicyName_
  Text
pPolicyDocument_ =
    GetGroupPolicyResponse'
      { $sel:httpStatus:GetGroupPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:groupName:GetGroupPolicyResponse' :: Text
groupName = Text
pGroupName_,
        $sel:policyName:GetGroupPolicyResponse' :: Text
policyName = Text
pPolicyName_,
        $sel:policyDocument:GetGroupPolicyResponse' :: Text
policyDocument = Text
pPolicyDocument_
      }

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

-- | The group the policy is associated with.
getGroupPolicyResponse_groupName :: Lens.Lens' GetGroupPolicyResponse Prelude.Text
getGroupPolicyResponse_groupName :: Lens' GetGroupPolicyResponse Text
getGroupPolicyResponse_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupPolicyResponse' {Text
groupName :: Text
$sel:groupName:GetGroupPolicyResponse' :: GetGroupPolicyResponse -> Text
groupName} -> Text
groupName) (\s :: GetGroupPolicyResponse
s@GetGroupPolicyResponse' {} Text
a -> GetGroupPolicyResponse
s {$sel:groupName:GetGroupPolicyResponse' :: Text
groupName = Text
a} :: GetGroupPolicyResponse)

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

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

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