{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.Iam.Commands.GetUserPolicy
( GetUserPolicy(..)
, GetUserPolicyResponse(..)
) 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 GetUserPolicy
= GetUserPolicy {
GetUserPolicy -> Text
gupPolicyName :: Text
, GetUserPolicy -> Text
gupUserName :: Text
}
deriving (GetUserPolicy -> GetUserPolicy -> Bool
(GetUserPolicy -> GetUserPolicy -> Bool)
-> (GetUserPolicy -> GetUserPolicy -> Bool) -> Eq GetUserPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetUserPolicy -> GetUserPolicy -> Bool
== :: GetUserPolicy -> GetUserPolicy -> Bool
$c/= :: GetUserPolicy -> GetUserPolicy -> Bool
/= :: GetUserPolicy -> GetUserPolicy -> Bool
Eq, Eq GetUserPolicy
Eq GetUserPolicy =>
(GetUserPolicy -> GetUserPolicy -> Ordering)
-> (GetUserPolicy -> GetUserPolicy -> Bool)
-> (GetUserPolicy -> GetUserPolicy -> Bool)
-> (GetUserPolicy -> GetUserPolicy -> Bool)
-> (GetUserPolicy -> GetUserPolicy -> Bool)
-> (GetUserPolicy -> GetUserPolicy -> GetUserPolicy)
-> (GetUserPolicy -> GetUserPolicy -> GetUserPolicy)
-> Ord GetUserPolicy
GetUserPolicy -> GetUserPolicy -> Bool
GetUserPolicy -> GetUserPolicy -> Ordering
GetUserPolicy -> GetUserPolicy -> GetUserPolicy
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 :: GetUserPolicy -> GetUserPolicy -> Ordering
compare :: GetUserPolicy -> GetUserPolicy -> Ordering
$c< :: GetUserPolicy -> GetUserPolicy -> Bool
< :: GetUserPolicy -> GetUserPolicy -> Bool
$c<= :: GetUserPolicy -> GetUserPolicy -> Bool
<= :: GetUserPolicy -> GetUserPolicy -> Bool
$c> :: GetUserPolicy -> GetUserPolicy -> Bool
> :: GetUserPolicy -> GetUserPolicy -> Bool
$c>= :: GetUserPolicy -> GetUserPolicy -> Bool
>= :: GetUserPolicy -> GetUserPolicy -> Bool
$cmax :: GetUserPolicy -> GetUserPolicy -> GetUserPolicy
max :: GetUserPolicy -> GetUserPolicy -> GetUserPolicy
$cmin :: GetUserPolicy -> GetUserPolicy -> GetUserPolicy
min :: GetUserPolicy -> GetUserPolicy -> GetUserPolicy
Ord, Int -> GetUserPolicy -> ShowS
[GetUserPolicy] -> ShowS
GetUserPolicy -> String
(Int -> GetUserPolicy -> ShowS)
-> (GetUserPolicy -> String)
-> ([GetUserPolicy] -> ShowS)
-> Show GetUserPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetUserPolicy -> ShowS
showsPrec :: Int -> GetUserPolicy -> ShowS
$cshow :: GetUserPolicy -> String
show :: GetUserPolicy -> String
$cshowList :: [GetUserPolicy] -> ShowS
showList :: [GetUserPolicy] -> ShowS
Show, Typeable)
instance SignQuery GetUserPolicy where
type ServiceConfiguration GetUserPolicy = IamConfiguration
signQuery :: forall queryType.
GetUserPolicy
-> ServiceConfiguration GetUserPolicy queryType
-> SignatureData
-> SignedQuery
signQuery GetUserPolicy{Text
gupPolicyName :: GetUserPolicy -> Text
gupUserName :: GetUserPolicy -> Text
gupPolicyName :: Text
gupUserName :: Text
..}
= ByteString
-> [(ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
"GetUserPolicy" [
(ByteString
"PolicyName", Text
gupPolicyName)
, (ByteString
"UserName", Text
gupUserName)
]
data GetUserPolicyResponse
= GetUserPolicyResponse {
GetUserPolicyResponse -> Text
guprPolicyDocument :: Text
, GetUserPolicyResponse -> Text
guprPolicyName :: Text
, GetUserPolicyResponse -> Text
guprUserName :: Text
}
deriving (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
(GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> Eq GetUserPolicyResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
== :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c/= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
/= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
Eq, Eq GetUserPolicyResponse
Eq GetUserPolicyResponse =>
(GetUserPolicyResponse -> GetUserPolicyResponse -> Ordering)
-> (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> (GetUserPolicyResponse -> GetUserPolicyResponse -> Bool)
-> (GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse)
-> (GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse)
-> Ord GetUserPolicyResponse
GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
GetUserPolicyResponse -> GetUserPolicyResponse -> Ordering
GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse
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 :: GetUserPolicyResponse -> GetUserPolicyResponse -> Ordering
compare :: GetUserPolicyResponse -> GetUserPolicyResponse -> Ordering
$c< :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
< :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c<= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
<= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c> :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
> :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$c>= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
>= :: GetUserPolicyResponse -> GetUserPolicyResponse -> Bool
$cmax :: GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse
max :: GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse
$cmin :: GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse
min :: GetUserPolicyResponse
-> GetUserPolicyResponse -> GetUserPolicyResponse
Ord, Int -> GetUserPolicyResponse -> ShowS
[GetUserPolicyResponse] -> ShowS
GetUserPolicyResponse -> String
(Int -> GetUserPolicyResponse -> ShowS)
-> (GetUserPolicyResponse -> String)
-> ([GetUserPolicyResponse] -> ShowS)
-> Show GetUserPolicyResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetUserPolicyResponse -> ShowS
showsPrec :: Int -> GetUserPolicyResponse -> ShowS
$cshow :: GetUserPolicyResponse -> String
show :: GetUserPolicyResponse -> String
$cshowList :: [GetUserPolicyResponse] -> ShowS
showList :: [GetUserPolicyResponse] -> ShowS
Show, Typeable)
instance ResponseConsumer GetUserPolicy GetUserPolicyResponse where
type ResponseMetadata GetUserPolicyResponse = IamMetadata
responseConsumer :: Request
-> GetUserPolicy
-> IORef (ResponseMetadata GetUserPolicyResponse)
-> HTTPResponseConsumer GetUserPolicyResponse
responseConsumer Request
_ GetUserPolicy
_
= (Cursor -> Response IamMetadata GetUserPolicyResponse)
-> IORef IamMetadata -> HTTPResponseConsumer GetUserPolicyResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer ((Cursor -> Response IamMetadata GetUserPolicyResponse)
-> IORef IamMetadata -> HTTPResponseConsumer GetUserPolicyResponse)
-> (Cursor -> Response IamMetadata GetUserPolicyResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer GetUserPolicyResponse
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
guprPolicyDocument <- 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
guprPolicyName <- Text -> Response IamMetadata Text
attr Text
"PolicyName"
Text
guprUserName <- Text -> Response IamMetadata Text
attr Text
"UserName"
GetUserPolicyResponse -> Response IamMetadata GetUserPolicyResponse
forall a. a -> Response IamMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return GetUserPolicyResponse{Text
guprPolicyDocument :: Text
guprPolicyName :: Text
guprUserName :: Text
guprPolicyDocument :: Text
guprPolicyName :: Text
guprUserName :: 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 GetUserPolicy GetUserPolicyResponse
instance AsMemoryResponse GetUserPolicyResponse where
type MemoryResponse GetUserPolicyResponse = GetUserPolicyResponse
loadToMemory :: GetUserPolicyResponse
-> ResourceT IO (MemoryResponse GetUserPolicyResponse)
loadToMemory = GetUserPolicyResponse
-> ResourceT IO (MemoryResponse GetUserPolicyResponse)
GetUserPolicyResponse -> ResourceT IO GetUserPolicyResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return