{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.SES.VerifyEmailIdentity
(
VerifyEmailIdentity (..),
newVerifyEmailIdentity,
verifyEmailIdentity_emailAddress,
VerifyEmailIdentityResponse (..),
newVerifyEmailIdentityResponse,
verifyEmailIdentityResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SES.Types
data VerifyEmailIdentity = VerifyEmailIdentity'
{
VerifyEmailIdentity -> Text
emailAddress :: Prelude.Text
}
deriving (VerifyEmailIdentity -> VerifyEmailIdentity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyEmailIdentity -> VerifyEmailIdentity -> Bool
$c/= :: VerifyEmailIdentity -> VerifyEmailIdentity -> Bool
== :: VerifyEmailIdentity -> VerifyEmailIdentity -> Bool
$c== :: VerifyEmailIdentity -> VerifyEmailIdentity -> Bool
Prelude.Eq, ReadPrec [VerifyEmailIdentity]
ReadPrec VerifyEmailIdentity
Int -> ReadS VerifyEmailIdentity
ReadS [VerifyEmailIdentity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyEmailIdentity]
$creadListPrec :: ReadPrec [VerifyEmailIdentity]
readPrec :: ReadPrec VerifyEmailIdentity
$creadPrec :: ReadPrec VerifyEmailIdentity
readList :: ReadS [VerifyEmailIdentity]
$creadList :: ReadS [VerifyEmailIdentity]
readsPrec :: Int -> ReadS VerifyEmailIdentity
$creadsPrec :: Int -> ReadS VerifyEmailIdentity
Prelude.Read, Int -> VerifyEmailIdentity -> ShowS
[VerifyEmailIdentity] -> ShowS
VerifyEmailIdentity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyEmailIdentity] -> ShowS
$cshowList :: [VerifyEmailIdentity] -> ShowS
show :: VerifyEmailIdentity -> String
$cshow :: VerifyEmailIdentity -> String
showsPrec :: Int -> VerifyEmailIdentity -> ShowS
$cshowsPrec :: Int -> VerifyEmailIdentity -> ShowS
Prelude.Show, forall x. Rep VerifyEmailIdentity x -> VerifyEmailIdentity
forall x. VerifyEmailIdentity -> Rep VerifyEmailIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerifyEmailIdentity x -> VerifyEmailIdentity
$cfrom :: forall x. VerifyEmailIdentity -> Rep VerifyEmailIdentity x
Prelude.Generic)
newVerifyEmailIdentity ::
Prelude.Text ->
VerifyEmailIdentity
newVerifyEmailIdentity :: Text -> VerifyEmailIdentity
newVerifyEmailIdentity Text
pEmailAddress_ =
VerifyEmailIdentity' {$sel:emailAddress:VerifyEmailIdentity' :: Text
emailAddress = Text
pEmailAddress_}
verifyEmailIdentity_emailAddress :: Lens.Lens' VerifyEmailIdentity Prelude.Text
verifyEmailIdentity_emailAddress :: Lens' VerifyEmailIdentity Text
verifyEmailIdentity_emailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyEmailIdentity' {Text
emailAddress :: Text
$sel:emailAddress:VerifyEmailIdentity' :: VerifyEmailIdentity -> Text
emailAddress} -> Text
emailAddress) (\s :: VerifyEmailIdentity
s@VerifyEmailIdentity' {} Text
a -> VerifyEmailIdentity
s {$sel:emailAddress:VerifyEmailIdentity' :: Text
emailAddress = Text
a} :: VerifyEmailIdentity)
instance Core.AWSRequest VerifyEmailIdentity where
type
AWSResponse VerifyEmailIdentity =
VerifyEmailIdentityResponse
request :: (Service -> Service)
-> VerifyEmailIdentity -> Request VerifyEmailIdentity
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy VerifyEmailIdentity
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse VerifyEmailIdentity)))
response =
forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
-> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
Text
"VerifyEmailIdentityResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Int -> VerifyEmailIdentityResponse
VerifyEmailIdentityResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable VerifyEmailIdentity where
hashWithSalt :: Int -> VerifyEmailIdentity -> Int
hashWithSalt Int
_salt VerifyEmailIdentity' {Text
emailAddress :: Text
$sel:emailAddress:VerifyEmailIdentity' :: VerifyEmailIdentity -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
emailAddress
instance Prelude.NFData VerifyEmailIdentity where
rnf :: VerifyEmailIdentity -> ()
rnf VerifyEmailIdentity' {Text
emailAddress :: Text
$sel:emailAddress:VerifyEmailIdentity' :: VerifyEmailIdentity -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
emailAddress
instance Data.ToHeaders VerifyEmailIdentity where
toHeaders :: VerifyEmailIdentity -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath VerifyEmailIdentity where
toPath :: VerifyEmailIdentity -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery VerifyEmailIdentity where
toQuery :: VerifyEmailIdentity -> QueryString
toQuery VerifyEmailIdentity' {Text
emailAddress :: Text
$sel:emailAddress:VerifyEmailIdentity' :: VerifyEmailIdentity -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"VerifyEmailIdentity" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
ByteString
"EmailAddress" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
emailAddress
]
data VerifyEmailIdentityResponse = VerifyEmailIdentityResponse'
{
VerifyEmailIdentityResponse -> Int
httpStatus :: Prelude.Int
}
deriving (VerifyEmailIdentityResponse -> VerifyEmailIdentityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyEmailIdentityResponse -> VerifyEmailIdentityResponse -> Bool
$c/= :: VerifyEmailIdentityResponse -> VerifyEmailIdentityResponse -> Bool
== :: VerifyEmailIdentityResponse -> VerifyEmailIdentityResponse -> Bool
$c== :: VerifyEmailIdentityResponse -> VerifyEmailIdentityResponse -> Bool
Prelude.Eq, ReadPrec [VerifyEmailIdentityResponse]
ReadPrec VerifyEmailIdentityResponse
Int -> ReadS VerifyEmailIdentityResponse
ReadS [VerifyEmailIdentityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyEmailIdentityResponse]
$creadListPrec :: ReadPrec [VerifyEmailIdentityResponse]
readPrec :: ReadPrec VerifyEmailIdentityResponse
$creadPrec :: ReadPrec VerifyEmailIdentityResponse
readList :: ReadS [VerifyEmailIdentityResponse]
$creadList :: ReadS [VerifyEmailIdentityResponse]
readsPrec :: Int -> ReadS VerifyEmailIdentityResponse
$creadsPrec :: Int -> ReadS VerifyEmailIdentityResponse
Prelude.Read, Int -> VerifyEmailIdentityResponse -> ShowS
[VerifyEmailIdentityResponse] -> ShowS
VerifyEmailIdentityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyEmailIdentityResponse] -> ShowS
$cshowList :: [VerifyEmailIdentityResponse] -> ShowS
show :: VerifyEmailIdentityResponse -> String
$cshow :: VerifyEmailIdentityResponse -> String
showsPrec :: Int -> VerifyEmailIdentityResponse -> ShowS
$cshowsPrec :: Int -> VerifyEmailIdentityResponse -> ShowS
Prelude.Show, forall x.
Rep VerifyEmailIdentityResponse x -> VerifyEmailIdentityResponse
forall x.
VerifyEmailIdentityResponse -> Rep VerifyEmailIdentityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VerifyEmailIdentityResponse x -> VerifyEmailIdentityResponse
$cfrom :: forall x.
VerifyEmailIdentityResponse -> Rep VerifyEmailIdentityResponse x
Prelude.Generic)
newVerifyEmailIdentityResponse ::
Prelude.Int ->
VerifyEmailIdentityResponse
newVerifyEmailIdentityResponse :: Int -> VerifyEmailIdentityResponse
newVerifyEmailIdentityResponse Int
pHttpStatus_ =
VerifyEmailIdentityResponse'
{ $sel:httpStatus:VerifyEmailIdentityResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
verifyEmailIdentityResponse_httpStatus :: Lens.Lens' VerifyEmailIdentityResponse Prelude.Int
verifyEmailIdentityResponse_httpStatus :: Lens' VerifyEmailIdentityResponse Int
verifyEmailIdentityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyEmailIdentityResponse' {Int
httpStatus :: Int
$sel:httpStatus:VerifyEmailIdentityResponse' :: VerifyEmailIdentityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: VerifyEmailIdentityResponse
s@VerifyEmailIdentityResponse' {} Int
a -> VerifyEmailIdentityResponse
s {$sel:httpStatus:VerifyEmailIdentityResponse' :: Int
httpStatus = Int
a} :: VerifyEmailIdentityResponse)
instance Prelude.NFData VerifyEmailIdentityResponse where
rnf :: VerifyEmailIdentityResponse -> ()
rnf VerifyEmailIdentityResponse' {Int
httpStatus :: Int
$sel:httpStatus:VerifyEmailIdentityResponse' :: VerifyEmailIdentityResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus