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 {
gupPolicyName :: Text
, gupUserName :: Text
}
deriving (Eq, Ord, Show, Typeable)
instance SignQuery GetUserPolicy where
type ServiceConfiguration GetUserPolicy = IamConfiguration
signQuery GetUserPolicy{..}
= iamAction "GetUserPolicy" [
("PolicyName", gupPolicyName)
, ("UserName", gupUserName)
]
data GetUserPolicyResponse
= GetUserPolicyResponse {
guprPolicyDocument :: Text
, guprPolicyName :: Text
, guprUserName :: Text
}
deriving (Eq, Ord, Show, Typeable)
instance ResponseConsumer GetUserPolicy GetUserPolicyResponse where
type ResponseMetadata GetUserPolicyResponse = IamMetadata
responseConsumer _ _
= iamResponseConsumer $ \cursor -> do
let attr name = force ("Missing " ++ Text.unpack name) $
cursor $// elContent name
guprPolicyDocument <- decodePolicy <$>
attr "PolicyDocument"
guprPolicyName <- attr "PolicyName"
guprUserName <- attr "UserName"
return GetUserPolicyResponse{..}
where
decodePolicy = Text.decodeUtf8 . HTTP.urlDecode False
. Text.encodeUtf8
instance Transaction GetUserPolicy GetUserPolicyResponse
instance AsMemoryResponse GetUserPolicyResponse where
type MemoryResponse GetUserPolicyResponse = GetUserPolicyResponse
loadToMemory = return