{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE TypeFamilies          #-}
module Aws.Iam.Commands.GetGroupPolicy
    ( GetGroupPolicy(..)
    , GetGroupPolicyResponse(..)
    ) where

import           Aws.Core
import           Aws.Iam.Core
import           Aws.Iam.Internal
import           Control.Applicative
import           Data.Text           (Text)
import qualified Data.Text           as Text
import qualified Data.Text.Encoding  as Text
import           Data.Typeable
import qualified Network.HTTP.Types  as HTTP
import           Text.XML.Cursor     (($//))
import           Prelude

-- | Retreives the specified policy document for the specified group.
--
-- <http://docs.aws.amazon.com/IAM/latest/APIReference/API_GetGroupPolicy.html>
data GetGroupPolicy
    = GetGroupPolicy {
        GetGroupPolicy -> Text
ggpPolicyName :: Text
      -- ^ Name of the policy.
      , GetGroupPolicy -> Text
ggpGroupName   :: Text
      -- ^ Name of the group with whom the policy is associated.
      }
    deriving (GetGroupPolicy -> GetGroupPolicy -> Bool
(GetGroupPolicy -> GetGroupPolicy -> Bool)
-> (GetGroupPolicy -> GetGroupPolicy -> Bool) -> Eq GetGroupPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetGroupPolicy -> GetGroupPolicy -> Bool
== :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c/= :: GetGroupPolicy -> GetGroupPolicy -> Bool
/= :: GetGroupPolicy -> GetGroupPolicy -> Bool
Eq, Eq GetGroupPolicy
Eq GetGroupPolicy =>
(GetGroupPolicy -> GetGroupPolicy -> Ordering)
-> (GetGroupPolicy -> GetGroupPolicy -> Bool)
-> (GetGroupPolicy -> GetGroupPolicy -> Bool)
-> (GetGroupPolicy -> GetGroupPolicy -> Bool)
-> (GetGroupPolicy -> GetGroupPolicy -> Bool)
-> (GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy)
-> (GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy)
-> Ord GetGroupPolicy
GetGroupPolicy -> GetGroupPolicy -> Bool
GetGroupPolicy -> GetGroupPolicy -> Ordering
GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GetGroupPolicy -> GetGroupPolicy -> Ordering
compare :: GetGroupPolicy -> GetGroupPolicy -> Ordering
$c< :: GetGroupPolicy -> GetGroupPolicy -> Bool
< :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c<= :: GetGroupPolicy -> GetGroupPolicy -> Bool
<= :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c> :: GetGroupPolicy -> GetGroupPolicy -> Bool
> :: GetGroupPolicy -> GetGroupPolicy -> Bool
$c>= :: GetGroupPolicy -> GetGroupPolicy -> Bool
>= :: GetGroupPolicy -> GetGroupPolicy -> Bool
$cmax :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
max :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
$cmin :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
min :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
Ord, Int -> GetGroupPolicy -> ShowS
[GetGroupPolicy] -> ShowS
GetGroupPolicy -> String
(Int -> GetGroupPolicy -> ShowS)
-> (GetGroupPolicy -> String)
-> ([GetGroupPolicy] -> ShowS)
-> Show GetGroupPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetGroupPolicy -> ShowS
showsPrec :: Int -> GetGroupPolicy -> ShowS
$cshow :: GetGroupPolicy -> String
show :: GetGroupPolicy -> String
$cshowList :: [GetGroupPolicy] -> ShowS
showList :: [GetGroupPolicy] -> ShowS
Show, Typeable)

instance SignQuery GetGroupPolicy where
    type ServiceConfiguration GetGroupPolicy = IamConfiguration
    signQuery :: forall queryType.
GetGroupPolicy
-> ServiceConfiguration GetGroupPolicy queryType
-> SignatureData
-> SignedQuery
signQuery GetGroupPolicy{Text
ggpPolicyName :: GetGroupPolicy -> Text
ggpGroupName :: GetGroupPolicy -> Text
ggpPolicyName :: Text
ggpGroupName :: Text
..}
        = ByteString
-> [(ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
"GetGroupPolicy" [
              (ByteString
"PolicyName", Text
ggpPolicyName)
            , (ByteString
"GroupName", Text
ggpGroupName)
            ]

data GetGroupPolicyResponse
    = GetGroupPolicyResponse {
        GetGroupPolicyResponse -> Text
ggprPolicyDocument :: Text
      -- ^ The policy document.
      , GetGroupPolicyResponse -> Text
ggprPolicyName     :: Text
      -- ^ Name of the policy.
      , GetGroupPolicyResponse -> Text
ggprGroupName       :: Text
      -- ^ Name of the group with whom the policy is associated.
      }
    deriving (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
(GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> Eq GetGroupPolicyResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
== :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$c/= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
/= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
Eq, Eq GetGroupPolicyResponse
Eq GetGroupPolicyResponse =>
(GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering)
-> (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> (GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool)
-> (GetGroupPolicyResponse
    -> GetGroupPolicyResponse -> GetGroupPolicyResponse)
-> (GetGroupPolicyResponse
    -> GetGroupPolicyResponse -> GetGroupPolicyResponse)
-> Ord GetGroupPolicyResponse
GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering
GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering
compare :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering
$c< :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
< :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$c<= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
<= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$c> :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
> :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$c>= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
>= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$cmax :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
max :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
$cmin :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
min :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
Ord, Int -> GetGroupPolicyResponse -> ShowS
[GetGroupPolicyResponse] -> ShowS
GetGroupPolicyResponse -> String
(Int -> GetGroupPolicyResponse -> ShowS)
-> (GetGroupPolicyResponse -> String)
-> ([GetGroupPolicyResponse] -> ShowS)
-> Show GetGroupPolicyResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetGroupPolicyResponse -> ShowS
showsPrec :: Int -> GetGroupPolicyResponse -> ShowS
$cshow :: GetGroupPolicyResponse -> String
show :: GetGroupPolicyResponse -> String
$cshowList :: [GetGroupPolicyResponse] -> ShowS
showList :: [GetGroupPolicyResponse] -> ShowS
Show, Typeable)

instance ResponseConsumer GetGroupPolicy GetGroupPolicyResponse where
    type ResponseMetadata GetGroupPolicyResponse = IamMetadata
    responseConsumer :: Request
-> GetGroupPolicy
-> IORef (ResponseMetadata GetGroupPolicyResponse)
-> HTTPResponseConsumer GetGroupPolicyResponse
responseConsumer Request
_ GetGroupPolicy
_
        = (Cursor -> Response IamMetadata GetGroupPolicyResponse)
-> IORef IamMetadata -> HTTPResponseConsumer GetGroupPolicyResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer ((Cursor -> Response IamMetadata GetGroupPolicyResponse)
 -> IORef IamMetadata
 -> HTTPResponseConsumer GetGroupPolicyResponse)
-> (Cursor -> Response IamMetadata GetGroupPolicyResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer GetGroupPolicyResponse
forall a b. (a -> b) -> a -> b
$ \Cursor
cursor -> do
            let attr :: Text -> Response IamMetadata Text
attr Text
name = String -> [Text] -> Response IamMetadata Text
forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force (String
"Missing " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
name) ([Text] -> Response IamMetadata Text)
-> [Text] -> Response IamMetadata Text
forall a b. (a -> b) -> a -> b
$
                            Cursor
cursor Cursor -> (Cursor -> [Text]) -> [Text]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Cursor -> [Text]
elContent Text
name
            Text
ggprPolicyDocument <- Text -> Text
decodePolicy (Text -> Text)
-> Response IamMetadata Text -> Response IamMetadata Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                                  Text -> Response IamMetadata Text
attr Text
"PolicyDocument"
            Text
ggprPolicyName     <- Text -> Response IamMetadata Text
attr Text
"PolicyName"
            Text
ggprGroupName       <- Text -> Response IamMetadata Text
attr Text
"GroupName"
            GetGroupPolicyResponse
-> Response IamMetadata GetGroupPolicyResponse
forall a. a -> Response IamMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return GetGroupPolicyResponse{Text
ggprPolicyDocument :: Text
ggprPolicyName :: Text
ggprGroupName :: Text
ggprPolicyDocument :: Text
ggprPolicyName :: Text
ggprGroupName :: Text
..}
        where
          decodePolicy :: Text -> Text
decodePolicy = ByteString -> Text
Text.decodeUtf8 (ByteString -> Text) -> (Text -> ByteString) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ByteString -> ByteString
HTTP.urlDecode Bool
False
                       (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8


instance Transaction GetGroupPolicy GetGroupPolicyResponse

instance AsMemoryResponse GetGroupPolicyResponse where
    type MemoryResponse GetGroupPolicyResponse = GetGroupPolicyResponse
    loadToMemory :: GetGroupPolicyResponse
-> ResourceT IO (MemoryResponse GetGroupPolicyResponse)
loadToMemory = GetGroupPolicyResponse
-> ResourceT IO (MemoryResponse GetGroupPolicyResponse)
GetGroupPolicyResponse -> ResourceT IO GetGroupPolicyResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return