{-# 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.GetIdentityDkimAttributes
-- 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 the current status of Easy DKIM signing for an entity. For
-- domain name identities, this operation also returns the DKIM tokens that
-- are required for Easy DKIM signing, and whether Amazon SES has
-- successfully verified that these tokens have been published.
--
-- This operation takes a list of identities as input and returns the
-- following information for each:
--
-- -   Whether Easy DKIM signing is enabled or disabled.
--
-- -   A set of DKIM tokens that represent the identity. If the identity is
--     an email address, the tokens represent the domain of that address.
--
-- -   Whether Amazon SES has successfully verified the DKIM tokens
--     published in the domain\'s DNS. This information is only returned
--     for domain name identities, not for email addresses.
--
-- This operation is throttled at one request per second and can only get
-- DKIM attributes for up to 100 identities at a time.
--
-- For more information about creating DNS records using DKIM tokens, go to
-- the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim-dns-records.html Amazon SES Developer Guide>.
module Amazonka.SES.GetIdentityDkimAttributes
  ( -- * Creating a Request
    GetIdentityDkimAttributes (..),
    newGetIdentityDkimAttributes,

    -- * Request Lenses
    getIdentityDkimAttributes_identities,

    -- * Destructuring the Response
    GetIdentityDkimAttributesResponse (..),
    newGetIdentityDkimAttributesResponse,

    -- * Response Lenses
    getIdentityDkimAttributesResponse_httpStatus,
    getIdentityDkimAttributesResponse_dkimAttributes,
  )
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 for the status of Amazon SES Easy DKIM signing for
-- an identity. For domain identities, this request also returns the DKIM
-- tokens that are required for Easy DKIM signing, and whether Amazon SES
-- successfully verified that these tokens were published. For more
-- information about Easy DKIM, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/easy-dkim.html Amazon SES Developer Guide>.
--
-- /See:/ 'newGetIdentityDkimAttributes' smart constructor.
data GetIdentityDkimAttributes = GetIdentityDkimAttributes'
  { -- | A list of one or more verified identities - email addresses, domains, or
    -- both.
    GetIdentityDkimAttributes -> [Text]
identities :: [Prelude.Text]
  }
  deriving (GetIdentityDkimAttributes -> GetIdentityDkimAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIdentityDkimAttributes -> GetIdentityDkimAttributes -> Bool
$c/= :: GetIdentityDkimAttributes -> GetIdentityDkimAttributes -> Bool
== :: GetIdentityDkimAttributes -> GetIdentityDkimAttributes -> Bool
$c== :: GetIdentityDkimAttributes -> GetIdentityDkimAttributes -> Bool
Prelude.Eq, ReadPrec [GetIdentityDkimAttributes]
ReadPrec GetIdentityDkimAttributes
Int -> ReadS GetIdentityDkimAttributes
ReadS [GetIdentityDkimAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIdentityDkimAttributes]
$creadListPrec :: ReadPrec [GetIdentityDkimAttributes]
readPrec :: ReadPrec GetIdentityDkimAttributes
$creadPrec :: ReadPrec GetIdentityDkimAttributes
readList :: ReadS [GetIdentityDkimAttributes]
$creadList :: ReadS [GetIdentityDkimAttributes]
readsPrec :: Int -> ReadS GetIdentityDkimAttributes
$creadsPrec :: Int -> ReadS GetIdentityDkimAttributes
Prelude.Read, Int -> GetIdentityDkimAttributes -> ShowS
[GetIdentityDkimAttributes] -> ShowS
GetIdentityDkimAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIdentityDkimAttributes] -> ShowS
$cshowList :: [GetIdentityDkimAttributes] -> ShowS
show :: GetIdentityDkimAttributes -> String
$cshow :: GetIdentityDkimAttributes -> String
showsPrec :: Int -> GetIdentityDkimAttributes -> ShowS
$cshowsPrec :: Int -> GetIdentityDkimAttributes -> ShowS
Prelude.Show, forall x.
Rep GetIdentityDkimAttributes x -> GetIdentityDkimAttributes
forall x.
GetIdentityDkimAttributes -> Rep GetIdentityDkimAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIdentityDkimAttributes x -> GetIdentityDkimAttributes
$cfrom :: forall x.
GetIdentityDkimAttributes -> Rep GetIdentityDkimAttributes x
Prelude.Generic)

-- |
-- Create a value of 'GetIdentityDkimAttributes' 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:
--
-- 'identities', 'getIdentityDkimAttributes_identities' - A list of one or more verified identities - email addresses, domains, or
-- both.
newGetIdentityDkimAttributes ::
  GetIdentityDkimAttributes
newGetIdentityDkimAttributes :: GetIdentityDkimAttributes
newGetIdentityDkimAttributes =
  GetIdentityDkimAttributes'
    { $sel:identities:GetIdentityDkimAttributes' :: [Text]
identities =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | A list of one or more verified identities - email addresses, domains, or
-- both.
getIdentityDkimAttributes_identities :: Lens.Lens' GetIdentityDkimAttributes [Prelude.Text]
getIdentityDkimAttributes_identities :: Lens' GetIdentityDkimAttributes [Text]
getIdentityDkimAttributes_identities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIdentityDkimAttributes' {[Text]
identities :: [Text]
$sel:identities:GetIdentityDkimAttributes' :: GetIdentityDkimAttributes -> [Text]
identities} -> [Text]
identities) (\s :: GetIdentityDkimAttributes
s@GetIdentityDkimAttributes' {} [Text]
a -> GetIdentityDkimAttributes
s {$sel:identities:GetIdentityDkimAttributes' :: [Text]
identities = [Text]
a} :: GetIdentityDkimAttributes) 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 Core.AWSRequest GetIdentityDkimAttributes where
  type
    AWSResponse GetIdentityDkimAttributes =
      GetIdentityDkimAttributesResponse
  request :: (Service -> Service)
-> GetIdentityDkimAttributes -> Request GetIdentityDkimAttributes
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 GetIdentityDkimAttributes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetIdentityDkimAttributes)))
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
"GetIdentityDkimAttributesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int
-> HashMap Text IdentityDkimAttributes
-> GetIdentityDkimAttributesResponse
GetIdentityDkimAttributesResponse'
            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
"DkimAttributes"
                            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 k v.
(Eq k, Hashable k, FromText k, FromXML v) =>
Text -> Text -> Text -> [Node] -> Either String (HashMap k v)
Data.parseXMLMap Text
"entry" Text
"key" Text
"value"
                        )
      )

instance Prelude.Hashable GetIdentityDkimAttributes where
  hashWithSalt :: Int -> GetIdentityDkimAttributes -> Int
hashWithSalt Int
_salt GetIdentityDkimAttributes' {[Text]
identities :: [Text]
$sel:identities:GetIdentityDkimAttributes' :: GetIdentityDkimAttributes -> [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
identities

instance Prelude.NFData GetIdentityDkimAttributes where
  rnf :: GetIdentityDkimAttributes -> ()
rnf GetIdentityDkimAttributes' {[Text]
identities :: [Text]
$sel:identities:GetIdentityDkimAttributes' :: GetIdentityDkimAttributes -> [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [Text]
identities

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

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

instance Data.ToQuery GetIdentityDkimAttributes where
  toQuery :: GetIdentityDkimAttributes -> QueryString
toQuery GetIdentityDkimAttributes' {[Text]
identities :: [Text]
$sel:identities:GetIdentityDkimAttributes' :: GetIdentityDkimAttributes -> [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetIdentityDkimAttributes" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"Identities"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
identities
      ]

-- | Represents the status of Amazon SES Easy DKIM signing for an identity.
-- For domain identities, this response also contains the DKIM tokens that
-- are required for Easy DKIM signing, and whether Amazon SES successfully
-- verified that these tokens were published.
--
-- /See:/ 'newGetIdentityDkimAttributesResponse' smart constructor.
data GetIdentityDkimAttributesResponse = GetIdentityDkimAttributesResponse'
  { -- | The response's http status code.
    GetIdentityDkimAttributesResponse -> Int
httpStatus :: Prelude.Int,
    -- | The DKIM attributes for an email address or a domain.
    GetIdentityDkimAttributesResponse
-> HashMap Text IdentityDkimAttributes
dkimAttributes :: Prelude.HashMap Prelude.Text IdentityDkimAttributes
  }
  deriving (GetIdentityDkimAttributesResponse
-> GetIdentityDkimAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIdentityDkimAttributesResponse
-> GetIdentityDkimAttributesResponse -> Bool
$c/= :: GetIdentityDkimAttributesResponse
-> GetIdentityDkimAttributesResponse -> Bool
== :: GetIdentityDkimAttributesResponse
-> GetIdentityDkimAttributesResponse -> Bool
$c== :: GetIdentityDkimAttributesResponse
-> GetIdentityDkimAttributesResponse -> Bool
Prelude.Eq, ReadPrec [GetIdentityDkimAttributesResponse]
ReadPrec GetIdentityDkimAttributesResponse
Int -> ReadS GetIdentityDkimAttributesResponse
ReadS [GetIdentityDkimAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIdentityDkimAttributesResponse]
$creadListPrec :: ReadPrec [GetIdentityDkimAttributesResponse]
readPrec :: ReadPrec GetIdentityDkimAttributesResponse
$creadPrec :: ReadPrec GetIdentityDkimAttributesResponse
readList :: ReadS [GetIdentityDkimAttributesResponse]
$creadList :: ReadS [GetIdentityDkimAttributesResponse]
readsPrec :: Int -> ReadS GetIdentityDkimAttributesResponse
$creadsPrec :: Int -> ReadS GetIdentityDkimAttributesResponse
Prelude.Read, Int -> GetIdentityDkimAttributesResponse -> ShowS
[GetIdentityDkimAttributesResponse] -> ShowS
GetIdentityDkimAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIdentityDkimAttributesResponse] -> ShowS
$cshowList :: [GetIdentityDkimAttributesResponse] -> ShowS
show :: GetIdentityDkimAttributesResponse -> String
$cshow :: GetIdentityDkimAttributesResponse -> String
showsPrec :: Int -> GetIdentityDkimAttributesResponse -> ShowS
$cshowsPrec :: Int -> GetIdentityDkimAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep GetIdentityDkimAttributesResponse x
-> GetIdentityDkimAttributesResponse
forall x.
GetIdentityDkimAttributesResponse
-> Rep GetIdentityDkimAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIdentityDkimAttributesResponse x
-> GetIdentityDkimAttributesResponse
$cfrom :: forall x.
GetIdentityDkimAttributesResponse
-> Rep GetIdentityDkimAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIdentityDkimAttributesResponse' 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', 'getIdentityDkimAttributesResponse_httpStatus' - The response's http status code.
--
-- 'dkimAttributes', 'getIdentityDkimAttributesResponse_dkimAttributes' - The DKIM attributes for an email address or a domain.
newGetIdentityDkimAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetIdentityDkimAttributesResponse
newGetIdentityDkimAttributesResponse :: Int -> GetIdentityDkimAttributesResponse
newGetIdentityDkimAttributesResponse Int
pHttpStatus_ =
  GetIdentityDkimAttributesResponse'
    { $sel:httpStatus:GetIdentityDkimAttributesResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:dkimAttributes:GetIdentityDkimAttributesResponse' :: HashMap Text IdentityDkimAttributes
dkimAttributes = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | The DKIM attributes for an email address or a domain.
getIdentityDkimAttributesResponse_dkimAttributes :: Lens.Lens' GetIdentityDkimAttributesResponse (Prelude.HashMap Prelude.Text IdentityDkimAttributes)
getIdentityDkimAttributesResponse_dkimAttributes :: Lens'
  GetIdentityDkimAttributesResponse
  (HashMap Text IdentityDkimAttributes)
getIdentityDkimAttributesResponse_dkimAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIdentityDkimAttributesResponse' {HashMap Text IdentityDkimAttributes
dkimAttributes :: HashMap Text IdentityDkimAttributes
$sel:dkimAttributes:GetIdentityDkimAttributesResponse' :: GetIdentityDkimAttributesResponse
-> HashMap Text IdentityDkimAttributes
dkimAttributes} -> HashMap Text IdentityDkimAttributes
dkimAttributes) (\s :: GetIdentityDkimAttributesResponse
s@GetIdentityDkimAttributesResponse' {} HashMap Text IdentityDkimAttributes
a -> GetIdentityDkimAttributesResponse
s {$sel:dkimAttributes:GetIdentityDkimAttributesResponse' :: HashMap Text IdentityDkimAttributes
dkimAttributes = HashMap Text IdentityDkimAttributes
a} :: GetIdentityDkimAttributesResponse) 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
    GetIdentityDkimAttributesResponse
  where
  rnf :: GetIdentityDkimAttributesResponse -> ()
rnf GetIdentityDkimAttributesResponse' {Int
HashMap Text IdentityDkimAttributes
dkimAttributes :: HashMap Text IdentityDkimAttributes
httpStatus :: Int
$sel:dkimAttributes:GetIdentityDkimAttributesResponse' :: GetIdentityDkimAttributesResponse
-> HashMap Text IdentityDkimAttributes
$sel:httpStatus:GetIdentityDkimAttributesResponse' :: GetIdentityDkimAttributesResponse -> 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 HashMap Text IdentityDkimAttributes
dkimAttributes