{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SES.VerifyDomainDkim
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a set of DKIM tokens for a domain identity.
--
-- When you execute the @VerifyDomainDkim@ operation, the domain that you
-- specify is added to the list of identities that are associated with your
-- account. This is true even if you haven\'t already associated the domain
-- with your account by using the @VerifyDomainIdentity@ operation.
-- However, you can\'t send email from the domain until you either
-- successfully
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/verify-domains.html verify it>
-- or you successfully
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html set up DKIM for it>.
--
-- You use the tokens that are generated by this operation to create CNAME
-- records. When Amazon SES detects that you\'ve added these records to the
-- DNS configuration for a domain, you can start sending email from that
-- domain. You can start sending email even if you haven\'t added the TXT
-- record provided by the VerifyDomainIdentity operation to the DNS
-- configuration for your domain. All email that you send from the domain
-- is authenticated using DKIM.
--
-- To create the CNAME records for DKIM authentication, use the following
-- values:
--
-- -   __Name__: /token/._domainkey./example.com/
--
-- -   __Type__: CNAME
--
-- -   __Value__: /token/.dkim.amazonses.com
--
-- In the preceding example, replace /token/ with one of the tokens that
-- are generated when you execute this operation. Replace /example.com/
-- with your domain. Repeat this process for each token that\'s generated
-- by this operation.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.VerifyDomainDkim
  ( -- * Creating a Request
    VerifyDomainDkim (..),
    newVerifyDomainDkim,

    -- * Request Lenses
    verifyDomainDkim_domain,

    -- * Destructuring the Response
    VerifyDomainDkimResponse (..),
    newVerifyDomainDkimResponse,

    -- * Response Lenses
    verifyDomainDkimResponse_httpStatus,
    verifyDomainDkimResponse_dkimTokens,
  )
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

-- | Represents a request to generate the CNAME records needed to set up Easy
-- DKIM with Amazon SES. For more information about setting up Easy DKIM,
-- see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html Amazon SES Developer Guide>.
--
-- /See:/ 'newVerifyDomainDkim' smart constructor.
data VerifyDomainDkim = VerifyDomainDkim'
  { -- | The name of the domain to be verified for Easy DKIM signing.
    VerifyDomainDkim -> Text
domain :: Prelude.Text
  }
  deriving (VerifyDomainDkim -> VerifyDomainDkim -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyDomainDkim -> VerifyDomainDkim -> Bool
$c/= :: VerifyDomainDkim -> VerifyDomainDkim -> Bool
== :: VerifyDomainDkim -> VerifyDomainDkim -> Bool
$c== :: VerifyDomainDkim -> VerifyDomainDkim -> Bool
Prelude.Eq, ReadPrec [VerifyDomainDkim]
ReadPrec VerifyDomainDkim
Int -> ReadS VerifyDomainDkim
ReadS [VerifyDomainDkim]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyDomainDkim]
$creadListPrec :: ReadPrec [VerifyDomainDkim]
readPrec :: ReadPrec VerifyDomainDkim
$creadPrec :: ReadPrec VerifyDomainDkim
readList :: ReadS [VerifyDomainDkim]
$creadList :: ReadS [VerifyDomainDkim]
readsPrec :: Int -> ReadS VerifyDomainDkim
$creadsPrec :: Int -> ReadS VerifyDomainDkim
Prelude.Read, Int -> VerifyDomainDkim -> ShowS
[VerifyDomainDkim] -> ShowS
VerifyDomainDkim -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyDomainDkim] -> ShowS
$cshowList :: [VerifyDomainDkim] -> ShowS
show :: VerifyDomainDkim -> String
$cshow :: VerifyDomainDkim -> String
showsPrec :: Int -> VerifyDomainDkim -> ShowS
$cshowsPrec :: Int -> VerifyDomainDkim -> ShowS
Prelude.Show, forall x. Rep VerifyDomainDkim x -> VerifyDomainDkim
forall x. VerifyDomainDkim -> Rep VerifyDomainDkim x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerifyDomainDkim x -> VerifyDomainDkim
$cfrom :: forall x. VerifyDomainDkim -> Rep VerifyDomainDkim x
Prelude.Generic)

-- |
-- Create a value of 'VerifyDomainDkim' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'domain', 'verifyDomainDkim_domain' - The name of the domain to be verified for Easy DKIM signing.
newVerifyDomainDkim ::
  -- | 'domain'
  Prelude.Text ->
  VerifyDomainDkim
newVerifyDomainDkim :: Text -> VerifyDomainDkim
newVerifyDomainDkim Text
pDomain_ =
  VerifyDomainDkim' {$sel:domain:VerifyDomainDkim' :: Text
domain = Text
pDomain_}

-- | The name of the domain to be verified for Easy DKIM signing.
verifyDomainDkim_domain :: Lens.Lens' VerifyDomainDkim Prelude.Text
verifyDomainDkim_domain :: Lens' VerifyDomainDkim Text
verifyDomainDkim_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainDkim' {Text
domain :: Text
$sel:domain:VerifyDomainDkim' :: VerifyDomainDkim -> Text
domain} -> Text
domain) (\s :: VerifyDomainDkim
s@VerifyDomainDkim' {} Text
a -> VerifyDomainDkim
s {$sel:domain:VerifyDomainDkim' :: Text
domain = Text
a} :: VerifyDomainDkim)

instance Core.AWSRequest VerifyDomainDkim where
  type
    AWSResponse VerifyDomainDkim =
      VerifyDomainDkimResponse
  request :: (Service -> Service)
-> VerifyDomainDkim -> Request VerifyDomainDkim
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 VerifyDomainDkim
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse VerifyDomainDkim)))
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
"VerifyDomainDkimResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> [Text] -> VerifyDomainDkimResponse
VerifyDomainDkimResponse'
            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 (Maybe a)
Data..@? Text
"DkimTokens"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                        )
      )

instance Prelude.Hashable VerifyDomainDkim where
  hashWithSalt :: Int -> VerifyDomainDkim -> Int
hashWithSalt Int
_salt VerifyDomainDkim' {Text
domain :: Text
$sel:domain:VerifyDomainDkim' :: VerifyDomainDkim -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain

instance Prelude.NFData VerifyDomainDkim where
  rnf :: VerifyDomainDkim -> ()
rnf VerifyDomainDkim' {Text
domain :: Text
$sel:domain:VerifyDomainDkim' :: VerifyDomainDkim -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
domain

instance Data.ToHeaders VerifyDomainDkim where
  toHeaders :: VerifyDomainDkim -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath VerifyDomainDkim where
  toPath :: VerifyDomainDkim -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery VerifyDomainDkim where
  toQuery :: VerifyDomainDkim -> QueryString
toQuery VerifyDomainDkim' {Text
domain :: Text
$sel:domain:VerifyDomainDkim' :: VerifyDomainDkim -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"VerifyDomainDkim" :: 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
      ]

-- | Returns CNAME records that you must publish to the DNS server of your
-- domain to set up Easy DKIM with Amazon SES.
--
-- /See:/ 'newVerifyDomainDkimResponse' smart constructor.
data VerifyDomainDkimResponse = VerifyDomainDkimResponse'
  { -- | The response's http status code.
    VerifyDomainDkimResponse -> Int
httpStatus :: Prelude.Int,
    -- | A set of character strings that represent the domain\'s identity. If the
    -- identity is an email address, the tokens represent the domain of that
    -- address.
    --
    -- Using these tokens, you need to create DNS CNAME records that point to
    -- DKIM public keys that are hosted by Amazon SES. Amazon Web Services
    -- eventually detects that you\'ve updated your DNS records. This detection
    -- process might take up to 72 hours. After successful detection, Amazon
    -- SES is able to DKIM-sign email originating from that domain. (This only
    -- applies to domain identities, not email address identities.)
    --
    -- For more information about creating DNS records using DKIM tokens, see
    -- the
    -- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html Amazon SES Developer Guide>.
    VerifyDomainDkimResponse -> [Text]
dkimTokens :: [Prelude.Text]
  }
  deriving (VerifyDomainDkimResponse -> VerifyDomainDkimResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyDomainDkimResponse -> VerifyDomainDkimResponse -> Bool
$c/= :: VerifyDomainDkimResponse -> VerifyDomainDkimResponse -> Bool
== :: VerifyDomainDkimResponse -> VerifyDomainDkimResponse -> Bool
$c== :: VerifyDomainDkimResponse -> VerifyDomainDkimResponse -> Bool
Prelude.Eq, ReadPrec [VerifyDomainDkimResponse]
ReadPrec VerifyDomainDkimResponse
Int -> ReadS VerifyDomainDkimResponse
ReadS [VerifyDomainDkimResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerifyDomainDkimResponse]
$creadListPrec :: ReadPrec [VerifyDomainDkimResponse]
readPrec :: ReadPrec VerifyDomainDkimResponse
$creadPrec :: ReadPrec VerifyDomainDkimResponse
readList :: ReadS [VerifyDomainDkimResponse]
$creadList :: ReadS [VerifyDomainDkimResponse]
readsPrec :: Int -> ReadS VerifyDomainDkimResponse
$creadsPrec :: Int -> ReadS VerifyDomainDkimResponse
Prelude.Read, Int -> VerifyDomainDkimResponse -> ShowS
[VerifyDomainDkimResponse] -> ShowS
VerifyDomainDkimResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyDomainDkimResponse] -> ShowS
$cshowList :: [VerifyDomainDkimResponse] -> ShowS
show :: VerifyDomainDkimResponse -> String
$cshow :: VerifyDomainDkimResponse -> String
showsPrec :: Int -> VerifyDomainDkimResponse -> ShowS
$cshowsPrec :: Int -> VerifyDomainDkimResponse -> ShowS
Prelude.Show, forall x.
Rep VerifyDomainDkimResponse x -> VerifyDomainDkimResponse
forall x.
VerifyDomainDkimResponse -> Rep VerifyDomainDkimResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VerifyDomainDkimResponse x -> VerifyDomainDkimResponse
$cfrom :: forall x.
VerifyDomainDkimResponse -> Rep VerifyDomainDkimResponse x
Prelude.Generic)

-- |
-- Create a value of 'VerifyDomainDkimResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'verifyDomainDkimResponse_httpStatus' - The response's http status code.
--
-- 'dkimTokens', 'verifyDomainDkimResponse_dkimTokens' - A set of character strings that represent the domain\'s identity. If the
-- identity is an email address, the tokens represent the domain of that
-- address.
--
-- Using these tokens, you need to create DNS CNAME records that point to
-- DKIM public keys that are hosted by Amazon SES. Amazon Web Services
-- eventually detects that you\'ve updated your DNS records. This detection
-- process might take up to 72 hours. After successful detection, Amazon
-- SES is able to DKIM-sign email originating from that domain. (This only
-- applies to domain identities, not email address identities.)
--
-- For more information about creating DNS records using DKIM tokens, see
-- the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html Amazon SES Developer Guide>.
newVerifyDomainDkimResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  VerifyDomainDkimResponse
newVerifyDomainDkimResponse :: Int -> VerifyDomainDkimResponse
newVerifyDomainDkimResponse Int
pHttpStatus_ =
  VerifyDomainDkimResponse'
    { $sel:httpStatus:VerifyDomainDkimResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:dkimTokens:VerifyDomainDkimResponse' :: [Text]
dkimTokens = forall a. Monoid a => a
Prelude.mempty
    }

-- | The response's http status code.
verifyDomainDkimResponse_httpStatus :: Lens.Lens' VerifyDomainDkimResponse Prelude.Int
verifyDomainDkimResponse_httpStatus :: Lens' VerifyDomainDkimResponse Int
verifyDomainDkimResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainDkimResponse' {Int
httpStatus :: Int
$sel:httpStatus:VerifyDomainDkimResponse' :: VerifyDomainDkimResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: VerifyDomainDkimResponse
s@VerifyDomainDkimResponse' {} Int
a -> VerifyDomainDkimResponse
s {$sel:httpStatus:VerifyDomainDkimResponse' :: Int
httpStatus = Int
a} :: VerifyDomainDkimResponse)

-- | A set of character strings that represent the domain\'s identity. If the
-- identity is an email address, the tokens represent the domain of that
-- address.
--
-- Using these tokens, you need to create DNS CNAME records that point to
-- DKIM public keys that are hosted by Amazon SES. Amazon Web Services
-- eventually detects that you\'ve updated your DNS records. This detection
-- process might take up to 72 hours. After successful detection, Amazon
-- SES is able to DKIM-sign email originating from that domain. (This only
-- applies to domain identities, not email address identities.)
--
-- For more information about creating DNS records using DKIM tokens, see
-- the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html Amazon SES Developer Guide>.
verifyDomainDkimResponse_dkimTokens :: Lens.Lens' VerifyDomainDkimResponse [Prelude.Text]
verifyDomainDkimResponse_dkimTokens :: Lens' VerifyDomainDkimResponse [Text]
verifyDomainDkimResponse_dkimTokens = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VerifyDomainDkimResponse' {[Text]
dkimTokens :: [Text]
$sel:dkimTokens:VerifyDomainDkimResponse' :: VerifyDomainDkimResponse -> [Text]
dkimTokens} -> [Text]
dkimTokens) (\s :: VerifyDomainDkimResponse
s@VerifyDomainDkimResponse' {} [Text]
a -> VerifyDomainDkimResponse
s {$sel:dkimTokens:VerifyDomainDkimResponse' :: [Text]
dkimTokens = [Text]
a} :: VerifyDomainDkimResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData VerifyDomainDkimResponse where
  rnf :: VerifyDomainDkimResponse -> ()
rnf VerifyDomainDkimResponse' {Int
[Text]
dkimTokens :: [Text]
httpStatus :: Int
$sel:dkimTokens:VerifyDomainDkimResponse' :: VerifyDomainDkimResponse -> [Text]
$sel:httpStatus:VerifyDomainDkimResponse' :: VerifyDomainDkimResponse -> 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]
dkimTokens