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

import           Aws.Core
import           Aws.Iam.Core
import           Aws.Iam.Internal
import           Data.Text          (Text)
import           Data.Typeable

-- | Deletes the specified policy associated with the specified user.
--
-- <http://docs.aws.amazon.com/IAM/latest/APIReference/API_DeleteUserPolicy.html>
data DeleteUserPolicy
    = DeleteUserPolicy {
        DeleteUserPolicy -> Text
dupPolicyName :: Text
      -- ^ Name of the policy to be deleted.
      , DeleteUserPolicy -> Text
dupUserName   :: Text
      -- ^ Name of the user with whom the policy is associated.
      }
    deriving (DeleteUserPolicy -> DeleteUserPolicy -> Bool
(DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> (DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> Eq DeleteUserPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
== :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c/= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
/= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
Eq, Eq DeleteUserPolicy
Eq DeleteUserPolicy =>
(DeleteUserPolicy -> DeleteUserPolicy -> Ordering)
-> (DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> (DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> (DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> (DeleteUserPolicy -> DeleteUserPolicy -> Bool)
-> (DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy)
-> (DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy)
-> Ord DeleteUserPolicy
DeleteUserPolicy -> DeleteUserPolicy -> Bool
DeleteUserPolicy -> DeleteUserPolicy -> Ordering
DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy
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 :: DeleteUserPolicy -> DeleteUserPolicy -> Ordering
compare :: DeleteUserPolicy -> DeleteUserPolicy -> Ordering
$c< :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
< :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c<= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
<= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c> :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
> :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c>= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
>= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$cmax :: DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy
max :: DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy
$cmin :: DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy
min :: DeleteUserPolicy -> DeleteUserPolicy -> DeleteUserPolicy
Ord, Int -> DeleteUserPolicy -> ShowS
[DeleteUserPolicy] -> ShowS
DeleteUserPolicy -> String
(Int -> DeleteUserPolicy -> ShowS)
-> (DeleteUserPolicy -> String)
-> ([DeleteUserPolicy] -> ShowS)
-> Show DeleteUserPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeleteUserPolicy -> ShowS
showsPrec :: Int -> DeleteUserPolicy -> ShowS
$cshow :: DeleteUserPolicy -> String
show :: DeleteUserPolicy -> String
$cshowList :: [DeleteUserPolicy] -> ShowS
showList :: [DeleteUserPolicy] -> ShowS
Show, Typeable)

instance SignQuery DeleteUserPolicy where
    type ServiceConfiguration DeleteUserPolicy = IamConfiguration
    signQuery :: forall queryType.
DeleteUserPolicy
-> ServiceConfiguration DeleteUserPolicy queryType
-> SignatureData
-> SignedQuery
signQuery DeleteUserPolicy{Text
dupPolicyName :: DeleteUserPolicy -> Text
dupUserName :: DeleteUserPolicy -> Text
dupPolicyName :: Text
dupUserName :: Text
..}
        = ByteString
-> [(ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
"DeleteUserPolicy" [
              (ByteString
"PolicyName", Text
dupPolicyName)
            , (ByteString
"UserName", Text
dupUserName)
            ]

data DeleteUserPolicyResponse = DeleteUserPolicyResponse
    deriving (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
(DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> Eq DeleteUserPolicyResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
== :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
$c/= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
/= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
Eq, Eq DeleteUserPolicyResponse
Eq DeleteUserPolicyResponse =>
(DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Ordering)
-> (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> (DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool)
-> (DeleteUserPolicyResponse
    -> DeleteUserPolicyResponse -> DeleteUserPolicyResponse)
-> (DeleteUserPolicyResponse
    -> DeleteUserPolicyResponse -> DeleteUserPolicyResponse)
-> Ord DeleteUserPolicyResponse
DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Ordering
DeleteUserPolicyResponse
-> DeleteUserPolicyResponse -> DeleteUserPolicyResponse
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 :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Ordering
compare :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Ordering
$c< :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
< :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
$c<= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
<= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
$c> :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
> :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
$c>= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
>= :: DeleteUserPolicyResponse -> DeleteUserPolicyResponse -> Bool
$cmax :: DeleteUserPolicyResponse
-> DeleteUserPolicyResponse -> DeleteUserPolicyResponse
max :: DeleteUserPolicyResponse
-> DeleteUserPolicyResponse -> DeleteUserPolicyResponse
$cmin :: DeleteUserPolicyResponse
-> DeleteUserPolicyResponse -> DeleteUserPolicyResponse
min :: DeleteUserPolicyResponse
-> DeleteUserPolicyResponse -> DeleteUserPolicyResponse
Ord, Int -> DeleteUserPolicyResponse -> ShowS
[DeleteUserPolicyResponse] -> ShowS
DeleteUserPolicyResponse -> String
(Int -> DeleteUserPolicyResponse -> ShowS)
-> (DeleteUserPolicyResponse -> String)
-> ([DeleteUserPolicyResponse] -> ShowS)
-> Show DeleteUserPolicyResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeleteUserPolicyResponse -> ShowS
showsPrec :: Int -> DeleteUserPolicyResponse -> ShowS
$cshow :: DeleteUserPolicyResponse -> String
show :: DeleteUserPolicyResponse -> String
$cshowList :: [DeleteUserPolicyResponse] -> ShowS
showList :: [DeleteUserPolicyResponse] -> ShowS
Show, Typeable)

instance ResponseConsumer DeleteUserPolicy DeleteUserPolicyResponse where
    type ResponseMetadata DeleteUserPolicyResponse = IamMetadata
    responseConsumer :: Request
-> DeleteUserPolicy
-> IORef (ResponseMetadata DeleteUserPolicyResponse)
-> HTTPResponseConsumer DeleteUserPolicyResponse
responseConsumer Request
_ DeleteUserPolicy
_ =
        (Cursor -> Response IamMetadata DeleteUserPolicyResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer DeleteUserPolicyResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer (Response IamMetadata DeleteUserPolicyResponse
-> Cursor -> Response IamMetadata DeleteUserPolicyResponse
forall a b. a -> b -> a
const (Response IamMetadata DeleteUserPolicyResponse
 -> Cursor -> Response IamMetadata DeleteUserPolicyResponse)
-> Response IamMetadata DeleteUserPolicyResponse
-> Cursor
-> Response IamMetadata DeleteUserPolicyResponse
forall a b. (a -> b) -> a -> b
$ DeleteUserPolicyResponse
-> Response IamMetadata DeleteUserPolicyResponse
forall a. a -> Response IamMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return DeleteUserPolicyResponse
DeleteUserPolicyResponse)

instance Transaction DeleteUserPolicy DeleteUserPolicyResponse

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