{-# 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.VerifyDomainIdentity
  ( 
    VerifyDomainIdentity (..),
    newVerifyDomainIdentity,
    
    verifyDomainIdentity_domain,
    
    VerifyDomainIdentityResponse (..),
    newVerifyDomainIdentityResponse,
    
    verifyDomainIdentityResponse_httpStatus,
    verifyDomainIdentityResponse_verificationToken,
  )
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 VerifyDomainIdentity = VerifyDomainIdentity'
  { 
    VerifyDomainIdentity -> Text
domain :: Prelude.Text
  }
  deriving (VerifyDomainIdentity -> VerifyDomainIdentity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyDomainIdentity -> VerifyDomainIdentity -> Bool
$c/= :: VerifyDomainIdentity -> VerifyDomainIdentity -> Bool
== :: VerifyDomainIdentity -> VerifyDomainIdentity -> Bool
$c== :: VerifyDomainIdentity -> VerifyDomainIdentity -> Bool
Prelude.Eq, ReadPrec [VerifyDomainIdentity]
ReadPrec VerifyDomainIdentity
Int -> ReadS VerifyDomainIdentity
ReadS [VerifyDomainIdentity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyDomainIdentity]
$creadListPrec :: ReadPrec [VerifyDomainIdentity]
readPrec :: ReadPrec VerifyDomainIdentity
$creadPrec :: ReadPrec VerifyDomainIdentity
readList :: ReadS [VerifyDomainIdentity]
$creadList :: ReadS [VerifyDomainIdentity]
readsPrec :: Int -> ReadS VerifyDomainIdentity
$creadsPrec :: Int -> ReadS VerifyDomainIdentity
Prelude.Read, Int -> VerifyDomainIdentity -> ShowS
[VerifyDomainIdentity] -> ShowS
VerifyDomainIdentity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyDomainIdentity] -> ShowS
$cshowList :: [VerifyDomainIdentity] -> ShowS
show :: VerifyDomainIdentity -> String
$cshow :: VerifyDomainIdentity -> String
showsPrec :: Int -> VerifyDomainIdentity -> ShowS
$cshowsPrec :: Int -> VerifyDomainIdentity -> ShowS
Prelude.Show, forall x. Rep VerifyDomainIdentity x -> VerifyDomainIdentity
forall x. VerifyDomainIdentity -> Rep VerifyDomainIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerifyDomainIdentity x -> VerifyDomainIdentity
$cfrom :: forall x. VerifyDomainIdentity -> Rep VerifyDomainIdentity x
Prelude.Generic)
newVerifyDomainIdentity ::
  
  Prelude.Text ->
  VerifyDomainIdentity
newVerifyDomainIdentity :: Text -> VerifyDomainIdentity
newVerifyDomainIdentity Text
pDomain_ =
  VerifyDomainIdentity' {$sel:domain:VerifyDomainIdentity' :: Text
domain = Text
pDomain_}
verifyDomainIdentity_domain :: Lens.Lens' VerifyDomainIdentity Prelude.Text
verifyDomainIdentity_domain :: Lens' VerifyDomainIdentity Text
verifyDomainIdentity_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainIdentity' {Text
domain :: Text
$sel:domain:VerifyDomainIdentity' :: VerifyDomainIdentity -> Text
domain} -> Text
domain) (\s :: VerifyDomainIdentity
s@VerifyDomainIdentity' {} Text
a -> VerifyDomainIdentity
s {$sel:domain:VerifyDomainIdentity' :: Text
domain = Text
a} :: VerifyDomainIdentity)
instance Core.AWSRequest VerifyDomainIdentity where
  type
    AWSResponse VerifyDomainIdentity =
      VerifyDomainIdentityResponse
  request :: (Service -> Service)
-> VerifyDomainIdentity -> Request VerifyDomainIdentity
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 VerifyDomainIdentity
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse VerifyDomainIdentity)))
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
"VerifyDomainIdentityResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> Text -> VerifyDomainIdentityResponse
VerifyDomainIdentityResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"VerificationToken")
      )
instance Prelude.Hashable VerifyDomainIdentity where
  hashWithSalt :: Int -> VerifyDomainIdentity -> Int
hashWithSalt Int
_salt VerifyDomainIdentity' {Text
domain :: Text
$sel:domain:VerifyDomainIdentity' :: VerifyDomainIdentity -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
instance Prelude.NFData VerifyDomainIdentity where
  rnf :: VerifyDomainIdentity -> ()
rnf VerifyDomainIdentity' {Text
domain :: Text
$sel:domain:VerifyDomainIdentity' :: VerifyDomainIdentity -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
domain
instance Data.ToHeaders VerifyDomainIdentity where
  toHeaders :: VerifyDomainIdentity -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath VerifyDomainIdentity where
  toPath :: VerifyDomainIdentity -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery VerifyDomainIdentity where
  toQuery :: VerifyDomainIdentity -> QueryString
toQuery VerifyDomainIdentity' {Text
domain :: Text
$sel:domain:VerifyDomainIdentity' :: VerifyDomainIdentity -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"VerifyDomainIdentity" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"Domain" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domain
      ]
data VerifyDomainIdentityResponse = VerifyDomainIdentityResponse'
  { 
    VerifyDomainIdentityResponse -> Int
httpStatus :: Prelude.Int,
    
    
    
    
    
    
    
    
    
    VerifyDomainIdentityResponse -> Text
verificationToken :: Prelude.Text
  }
  deriving (VerifyDomainIdentityResponse
-> VerifyDomainIdentityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyDomainIdentityResponse
-> VerifyDomainIdentityResponse -> Bool
$c/= :: VerifyDomainIdentityResponse
-> VerifyDomainIdentityResponse -> Bool
== :: VerifyDomainIdentityResponse
-> VerifyDomainIdentityResponse -> Bool
$c== :: VerifyDomainIdentityResponse
-> VerifyDomainIdentityResponse -> Bool
Prelude.Eq, ReadPrec [VerifyDomainIdentityResponse]
ReadPrec VerifyDomainIdentityResponse
Int -> ReadS VerifyDomainIdentityResponse
ReadS [VerifyDomainIdentityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyDomainIdentityResponse]
$creadListPrec :: ReadPrec [VerifyDomainIdentityResponse]
readPrec :: ReadPrec VerifyDomainIdentityResponse
$creadPrec :: ReadPrec VerifyDomainIdentityResponse
readList :: ReadS [VerifyDomainIdentityResponse]
$creadList :: ReadS [VerifyDomainIdentityResponse]
readsPrec :: Int -> ReadS VerifyDomainIdentityResponse
$creadsPrec :: Int -> ReadS VerifyDomainIdentityResponse
Prelude.Read, Int -> VerifyDomainIdentityResponse -> ShowS
[VerifyDomainIdentityResponse] -> ShowS
VerifyDomainIdentityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyDomainIdentityResponse] -> ShowS
$cshowList :: [VerifyDomainIdentityResponse] -> ShowS
show :: VerifyDomainIdentityResponse -> String
$cshow :: VerifyDomainIdentityResponse -> String
showsPrec :: Int -> VerifyDomainIdentityResponse -> ShowS
$cshowsPrec :: Int -> VerifyDomainIdentityResponse -> ShowS
Prelude.Show, forall x.
Rep VerifyDomainIdentityResponse x -> VerifyDomainIdentityResponse
forall x.
VerifyDomainIdentityResponse -> Rep VerifyDomainIdentityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VerifyDomainIdentityResponse x -> VerifyDomainIdentityResponse
$cfrom :: forall x.
VerifyDomainIdentityResponse -> Rep VerifyDomainIdentityResponse x
Prelude.Generic)
newVerifyDomainIdentityResponse ::
  
  Prelude.Int ->
  
  Prelude.Text ->
  VerifyDomainIdentityResponse
newVerifyDomainIdentityResponse :: Int -> Text -> VerifyDomainIdentityResponse
newVerifyDomainIdentityResponse
  Int
pHttpStatus_
  Text
pVerificationToken_ =
    VerifyDomainIdentityResponse'
      { $sel:httpStatus:VerifyDomainIdentityResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:verificationToken:VerifyDomainIdentityResponse' :: Text
verificationToken = Text
pVerificationToken_
      }
verifyDomainIdentityResponse_httpStatus :: Lens.Lens' VerifyDomainIdentityResponse Prelude.Int
verifyDomainIdentityResponse_httpStatus :: Lens' VerifyDomainIdentityResponse Int
verifyDomainIdentityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainIdentityResponse' {Int
httpStatus :: Int
$sel:httpStatus:VerifyDomainIdentityResponse' :: VerifyDomainIdentityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: VerifyDomainIdentityResponse
s@VerifyDomainIdentityResponse' {} Int
a -> VerifyDomainIdentityResponse
s {$sel:httpStatus:VerifyDomainIdentityResponse' :: Int
httpStatus = Int
a} :: VerifyDomainIdentityResponse)
verifyDomainIdentityResponse_verificationToken :: Lens.Lens' VerifyDomainIdentityResponse Prelude.Text
verifyDomainIdentityResponse_verificationToken :: Lens' VerifyDomainIdentityResponse Text
verifyDomainIdentityResponse_verificationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainIdentityResponse' {Text
verificationToken :: Text
$sel:verificationToken:VerifyDomainIdentityResponse' :: VerifyDomainIdentityResponse -> Text
verificationToken} -> Text
verificationToken) (\s :: VerifyDomainIdentityResponse
s@VerifyDomainIdentityResponse' {} Text
a -> VerifyDomainIdentityResponse
s {$sel:verificationToken:VerifyDomainIdentityResponse' :: Text
verificationToken = Text
a} :: VerifyDomainIdentityResponse)
instance Prelude.NFData VerifyDomainIdentityResponse where
  rnf :: VerifyDomainIdentityResponse -> ()
rnf VerifyDomainIdentityResponse' {Int
Text
verificationToken :: Text
httpStatus :: Int
$sel:verificationToken:VerifyDomainIdentityResponse' :: VerifyDomainIdentityResponse -> Text
$sel:httpStatus:VerifyDomainIdentityResponse' :: VerifyDomainIdentityResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
verificationToken