{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.Iam.Commands.PutUserPolicy
( PutUserPolicy(..)
, PutUserPolicyResponse(..)
) where
import Aws.Core
import Aws.Iam.Core
import Aws.Iam.Internal
import Data.Text (Text)
import Data.Typeable
data PutUserPolicy
= PutUserPolicy {
PutUserPolicy -> Text
pupPolicyDocument :: Text
, PutUserPolicy -> Text
pupPolicyName :: Text
, PutUserPolicy -> Text
pupUserName :: Text
}
deriving (PutUserPolicy -> PutUserPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutUserPolicy -> PutUserPolicy -> Bool
$c/= :: PutUserPolicy -> PutUserPolicy -> Bool
== :: PutUserPolicy -> PutUserPolicy -> Bool
$c== :: PutUserPolicy -> PutUserPolicy -> Bool
Eq, Eq PutUserPolicy
PutUserPolicy -> PutUserPolicy -> Bool
PutUserPolicy -> PutUserPolicy -> Ordering
PutUserPolicy -> PutUserPolicy -> PutUserPolicy
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 :: PutUserPolicy -> PutUserPolicy -> PutUserPolicy
$cmin :: PutUserPolicy -> PutUserPolicy -> PutUserPolicy
max :: PutUserPolicy -> PutUserPolicy -> PutUserPolicy
$cmax :: PutUserPolicy -> PutUserPolicy -> PutUserPolicy
>= :: PutUserPolicy -> PutUserPolicy -> Bool
$c>= :: PutUserPolicy -> PutUserPolicy -> Bool
> :: PutUserPolicy -> PutUserPolicy -> Bool
$c> :: PutUserPolicy -> PutUserPolicy -> Bool
<= :: PutUserPolicy -> PutUserPolicy -> Bool
$c<= :: PutUserPolicy -> PutUserPolicy -> Bool
< :: PutUserPolicy -> PutUserPolicy -> Bool
$c< :: PutUserPolicy -> PutUserPolicy -> Bool
compare :: PutUserPolicy -> PutUserPolicy -> Ordering
$ccompare :: PutUserPolicy -> PutUserPolicy -> Ordering
Ord, Int -> PutUserPolicy -> ShowS
[PutUserPolicy] -> ShowS
PutUserPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutUserPolicy] -> ShowS
$cshowList :: [PutUserPolicy] -> ShowS
show :: PutUserPolicy -> String
$cshow :: PutUserPolicy -> String
showsPrec :: Int -> PutUserPolicy -> ShowS
$cshowsPrec :: Int -> PutUserPolicy -> ShowS
Show, Typeable)
instance SignQuery PutUserPolicy where
type ServiceConfiguration PutUserPolicy = IamConfiguration
signQuery :: forall queryType.
PutUserPolicy
-> ServiceConfiguration PutUserPolicy queryType
-> SignatureData
-> SignedQuery
signQuery PutUserPolicy{Text
pupUserName :: Text
pupPolicyName :: Text
pupPolicyDocument :: Text
pupUserName :: PutUserPolicy -> Text
pupPolicyName :: PutUserPolicy -> Text
pupPolicyDocument :: PutUserPolicy -> Text
..}
= forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
"PutUserPolicy" [
(ByteString
"PolicyDocument", Text
pupPolicyDocument)
, (ByteString
"PolicyName" , Text
pupPolicyName)
, (ByteString
"UserName" , Text
pupUserName)
]
data PutUserPolicyResponse = PutUserPolicyResponse
deriving (PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c/= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
== :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c== :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
Eq, Eq PutUserPolicyResponse
PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
PutUserPolicyResponse -> PutUserPolicyResponse -> Ordering
PutUserPolicyResponse
-> PutUserPolicyResponse -> PutUserPolicyResponse
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 :: PutUserPolicyResponse
-> PutUserPolicyResponse -> PutUserPolicyResponse
$cmin :: PutUserPolicyResponse
-> PutUserPolicyResponse -> PutUserPolicyResponse
max :: PutUserPolicyResponse
-> PutUserPolicyResponse -> PutUserPolicyResponse
$cmax :: PutUserPolicyResponse
-> PutUserPolicyResponse -> PutUserPolicyResponse
>= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c>= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
> :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c> :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
<= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c<= :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
< :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
$c< :: PutUserPolicyResponse -> PutUserPolicyResponse -> Bool
compare :: PutUserPolicyResponse -> PutUserPolicyResponse -> Ordering
$ccompare :: PutUserPolicyResponse -> PutUserPolicyResponse -> Ordering
Ord, Int -> PutUserPolicyResponse -> ShowS
[PutUserPolicyResponse] -> ShowS
PutUserPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutUserPolicyResponse] -> ShowS
$cshowList :: [PutUserPolicyResponse] -> ShowS
show :: PutUserPolicyResponse -> String
$cshow :: PutUserPolicyResponse -> String
showsPrec :: Int -> PutUserPolicyResponse -> ShowS
$cshowsPrec :: Int -> PutUserPolicyResponse -> ShowS
Show, Typeable)
instance ResponseConsumer PutUserPolicy PutUserPolicyResponse where
type ResponseMetadata PutUserPolicyResponse = IamMetadata
responseConsumer :: Request
-> PutUserPolicy
-> IORef (ResponseMetadata PutUserPolicyResponse)
-> HTTPResponseConsumer PutUserPolicyResponse
responseConsumer Request
_ PutUserPolicy
_
= forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return PutUserPolicyResponse
PutUserPolicyResponse)
instance Transaction PutUserPolicy PutUserPolicyResponse
instance AsMemoryResponse PutUserPolicyResponse where
type MemoryResponse PutUserPolicyResponse = PutUserPolicyResponse
loadToMemory :: PutUserPolicyResponse
-> ResourceT IO (MemoryResponse PutUserPolicyResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return