module Aws.Ses.Commands.DeleteIdentity
    ( DeleteIdentity(..)
    , DeleteIdentityResponse(..)
    ) where

import Data.Text (Text)
import Data.Text.Encoding as T (encodeUtf8)
import Data.Typeable
import Aws.Core
import Aws.Ses.Core

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

-- | ServiceConfiguration: 'SesConfiguration'
instance SignQuery DeleteIdentity where
    type ServiceConfiguration DeleteIdentity = SesConfiguration
    signQuery :: forall queryType.
DeleteIdentity
-> ServiceConfiguration DeleteIdentity queryType
-> SignatureData
-> SignedQuery
signQuery (DeleteIdentity Text
identity) =
        [(ByteString, ByteString)]
-> SesConfiguration queryType -> SignatureData -> SignedQuery
forall qt.
[(ByteString, ByteString)]
-> SesConfiguration qt -> SignatureData -> SignedQuery
sesSignQuery [ (ByteString
"Action", ByteString
"DeleteIdentity")
                     , (ByteString
"Identity", Text -> ByteString
T.encodeUtf8 Text
identity)
                     ]

-- | The response sent back by Amazon SES after a
-- 'DeleteIdentity' command.
data DeleteIdentityResponse = DeleteIdentityResponse
    deriving (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
(DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> Eq DeleteIdentityResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
== :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
$c/= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
/= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
Eq, Eq DeleteIdentityResponse
Eq DeleteIdentityResponse =>
(DeleteIdentityResponse -> DeleteIdentityResponse -> Ordering)
-> (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> (DeleteIdentityResponse -> DeleteIdentityResponse -> Bool)
-> (DeleteIdentityResponse
    -> DeleteIdentityResponse -> DeleteIdentityResponse)
-> (DeleteIdentityResponse
    -> DeleteIdentityResponse -> DeleteIdentityResponse)
-> Ord DeleteIdentityResponse
DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
DeleteIdentityResponse -> DeleteIdentityResponse -> Ordering
DeleteIdentityResponse
-> DeleteIdentityResponse -> DeleteIdentityResponse
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 :: DeleteIdentityResponse -> DeleteIdentityResponse -> Ordering
compare :: DeleteIdentityResponse -> DeleteIdentityResponse -> Ordering
$c< :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
< :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
$c<= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
<= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
$c> :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
> :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
$c>= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
>= :: DeleteIdentityResponse -> DeleteIdentityResponse -> Bool
$cmax :: DeleteIdentityResponse
-> DeleteIdentityResponse -> DeleteIdentityResponse
max :: DeleteIdentityResponse
-> DeleteIdentityResponse -> DeleteIdentityResponse
$cmin :: DeleteIdentityResponse
-> DeleteIdentityResponse -> DeleteIdentityResponse
min :: DeleteIdentityResponse
-> DeleteIdentityResponse -> DeleteIdentityResponse
Ord, Int -> DeleteIdentityResponse -> ShowS
[DeleteIdentityResponse] -> ShowS
DeleteIdentityResponse -> String
(Int -> DeleteIdentityResponse -> ShowS)
-> (DeleteIdentityResponse -> String)
-> ([DeleteIdentityResponse] -> ShowS)
-> Show DeleteIdentityResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeleteIdentityResponse -> ShowS
showsPrec :: Int -> DeleteIdentityResponse -> ShowS
$cshow :: DeleteIdentityResponse -> String
show :: DeleteIdentityResponse -> String
$cshowList :: [DeleteIdentityResponse] -> ShowS
showList :: [DeleteIdentityResponse] -> ShowS
Show, Typeable)


instance ResponseConsumer DeleteIdentity DeleteIdentityResponse where
    type ResponseMetadata DeleteIdentityResponse = SesMetadata
    responseConsumer :: Request
-> DeleteIdentity
-> IORef (ResponseMetadata DeleteIdentityResponse)
-> HTTPResponseConsumer DeleteIdentityResponse
responseConsumer Request
_ DeleteIdentity
_
        = (Cursor -> Response SesMetadata DeleteIdentityResponse)
-> IORef SesMetadata -> HTTPResponseConsumer DeleteIdentityResponse
forall a.
(Cursor -> Response SesMetadata a)
-> IORef SesMetadata -> HTTPResponseConsumer a
sesResponseConsumer ((Cursor -> Response SesMetadata DeleteIdentityResponse)
 -> IORef SesMetadata
 -> HTTPResponseConsumer DeleteIdentityResponse)
-> (Cursor -> Response SesMetadata DeleteIdentityResponse)
-> IORef SesMetadata
-> HTTPResponseConsumer DeleteIdentityResponse
forall a b. (a -> b) -> a -> b
$ \Cursor
_ -> DeleteIdentityResponse
-> Response SesMetadata DeleteIdentityResponse
forall a. a -> Response SesMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return DeleteIdentityResponse
DeleteIdentityResponse


instance Transaction DeleteIdentity DeleteIdentityResponse where

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