{-# 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
data GetGroupPolicy
= GetGroupPolicy {
GetGroupPolicy -> Text
ggpPolicyName :: Text
, GetGroupPolicy -> Text
ggpGroupName :: 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
Eq, Eq 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
min :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
$cmin :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
max :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
$cmax :: GetGroupPolicy -> GetGroupPolicy -> GetGroupPolicy
>= :: GetGroupPolicy -> GetGroupPolicy -> Bool
$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
compare :: GetGroupPolicy -> GetGroupPolicy -> Ordering
$ccompare :: GetGroupPolicy -> GetGroupPolicy -> Ordering
Ord, 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
Show, Typeable)
instance SignQuery GetGroupPolicy where
type ServiceConfiguration GetGroupPolicy = IamConfiguration
signQuery :: forall queryType.
GetGroupPolicy
-> ServiceConfiguration GetGroupPolicy queryType
-> SignatureData
-> SignedQuery
signQuery GetGroupPolicy{Text
ggpGroupName :: Text
ggpPolicyName :: Text
ggpGroupName :: GetGroupPolicy -> Text
ggpPolicyName :: GetGroupPolicy -> Text
..}
= 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
, GetGroupPolicyResponse -> Text
ggprPolicyName :: Text
, GetGroupPolicyResponse -> Text
ggprGroupName :: 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
Eq, Eq 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
min :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
$cmin :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
max :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
$cmax :: GetGroupPolicyResponse
-> GetGroupPolicyResponse -> GetGroupPolicyResponse
>= :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Bool
$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
compare :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering
$ccompare :: GetGroupPolicyResponse -> GetGroupPolicyResponse -> Ordering
Ord, 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
Show, Typeable)
instance ResponseConsumer GetGroupPolicy GetGroupPolicyResponse where
type ResponseMetadata GetGroupPolicyResponse = IamMetadata
responseConsumer :: Request
-> GetGroupPolicy
-> IORef (ResponseMetadata GetGroupPolicyResponse)
-> HTTPResponseConsumer GetGroupPolicyResponse
responseConsumer Request
_ GetGroupPolicy
_
= forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer forall a b. (a -> b) -> a -> b
$ \Cursor
cursor -> do
let attr :: Text -> Response IamMetadata Text
attr Text
name = forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force (String
"Missing " forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
name) forall a b. (a -> b) -> a -> b
$
Cursor
cursor forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Cursor -> [Text]
elContent Text
name
Text
ggprPolicyDocument <- Text -> Text
decodePolicy 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"
forall (m :: * -> *) a. Monad m => a -> m a
return GetGroupPolicyResponse{Text
ggprGroupName :: Text
ggprPolicyName :: Text
ggprPolicyDocument :: Text
ggprGroupName :: Text
ggprPolicyName :: Text
ggprPolicyDocument :: Text
..}
where
decodePolicy :: Text -> Text
decodePolicy = ByteString -> Text
Text.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ByteString -> ByteString
HTTP.urlDecode Bool
False
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 = forall (m :: * -> *) a. Monad m => a -> m a
return