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
data DeleteUserPolicy
    = DeleteUserPolicy {
        dupPolicyName :: Text
      
      , dupUserName   :: Text
      
      }
    deriving (Eq, Ord, Show, Typeable)
instance SignQuery DeleteUserPolicy where
    type ServiceConfiguration DeleteUserPolicy = IamConfiguration
    signQuery DeleteUserPolicy{..}
        = iamAction "DeleteUserPolicy" [
              ("PolicyName", dupPolicyName)
            , ("UserName", dupUserName)
            ]
data DeleteUserPolicyResponse = DeleteUserPolicyResponse
    deriving (Eq, Ord, Show, Typeable)
instance ResponseConsumer DeleteUserPolicy DeleteUserPolicyResponse where
    type ResponseMetadata DeleteUserPolicyResponse = IamMetadata
    responseConsumer _ = iamResponseConsumer (const $ return DeleteUserPolicyResponse)
instance Transaction DeleteUserPolicy DeleteUserPolicyResponse
instance AsMemoryResponse DeleteUserPolicyResponse where
    type MemoryResponse DeleteUserPolicyResponse = DeleteUserPolicyResponse
    loadToMemory = return