{-# 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.WorkMail.GetMailDomain
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets details for a mail domain, including domain records required to
-- configure your domain with recommended security.
module Amazonka.WorkMail.GetMailDomain
  ( -- * Creating a Request
    GetMailDomain (..),
    newGetMailDomain,

    -- * Request Lenses
    getMailDomain_organizationId,
    getMailDomain_domainName,

    -- * Destructuring the Response
    GetMailDomainResponse (..),
    newGetMailDomainResponse,

    -- * Response Lenses
    getMailDomainResponse_dkimVerificationStatus,
    getMailDomainResponse_isDefault,
    getMailDomainResponse_isTestDomain,
    getMailDomainResponse_ownershipVerificationStatus,
    getMailDomainResponse_records,
    getMailDomainResponse_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.WorkMail.Types

-- | /See:/ 'newGetMailDomain' smart constructor.
data GetMailDomain = GetMailDomain'
  { -- | The WorkMail organization for which the domain is retrieved.
    GetMailDomain -> Text
organizationId :: Prelude.Text,
    -- | The domain from which you want to retrieve details.
    GetMailDomain -> Text
domainName :: Prelude.Text
  }
  deriving (GetMailDomain -> GetMailDomain -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMailDomain -> GetMailDomain -> Bool
$c/= :: GetMailDomain -> GetMailDomain -> Bool
== :: GetMailDomain -> GetMailDomain -> Bool
$c== :: GetMailDomain -> GetMailDomain -> Bool
Prelude.Eq, ReadPrec [GetMailDomain]
ReadPrec GetMailDomain
Int -> ReadS GetMailDomain
ReadS [GetMailDomain]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMailDomain]
$creadListPrec :: ReadPrec [GetMailDomain]
readPrec :: ReadPrec GetMailDomain
$creadPrec :: ReadPrec GetMailDomain
readList :: ReadS [GetMailDomain]
$creadList :: ReadS [GetMailDomain]
readsPrec :: Int -> ReadS GetMailDomain
$creadsPrec :: Int -> ReadS GetMailDomain
Prelude.Read, Int -> GetMailDomain -> ShowS
[GetMailDomain] -> ShowS
GetMailDomain -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMailDomain] -> ShowS
$cshowList :: [GetMailDomain] -> ShowS
show :: GetMailDomain -> String
$cshow :: GetMailDomain -> String
showsPrec :: Int -> GetMailDomain -> ShowS
$cshowsPrec :: Int -> GetMailDomain -> ShowS
Prelude.Show, forall x. Rep GetMailDomain x -> GetMailDomain
forall x. GetMailDomain -> Rep GetMailDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMailDomain x -> GetMailDomain
$cfrom :: forall x. GetMailDomain -> Rep GetMailDomain x
Prelude.Generic)

-- |
-- Create a value of 'GetMailDomain' 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:
--
-- 'organizationId', 'getMailDomain_organizationId' - The WorkMail organization for which the domain is retrieved.
--
-- 'domainName', 'getMailDomain_domainName' - The domain from which you want to retrieve details.
newGetMailDomain ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'domainName'
  Prelude.Text ->
  GetMailDomain
newGetMailDomain :: Text -> Text -> GetMailDomain
newGetMailDomain Text
pOrganizationId_ Text
pDomainName_ =
  GetMailDomain'
    { $sel:organizationId:GetMailDomain' :: Text
organizationId = Text
pOrganizationId_,
      $sel:domainName:GetMailDomain' :: Text
domainName = Text
pDomainName_
    }

-- | The WorkMail organization for which the domain is retrieved.
getMailDomain_organizationId :: Lens.Lens' GetMailDomain Prelude.Text
getMailDomain_organizationId :: Lens' GetMailDomain Text
getMailDomain_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomain' {Text
organizationId :: Text
$sel:organizationId:GetMailDomain' :: GetMailDomain -> Text
organizationId} -> Text
organizationId) (\s :: GetMailDomain
s@GetMailDomain' {} Text
a -> GetMailDomain
s {$sel:organizationId:GetMailDomain' :: Text
organizationId = Text
a} :: GetMailDomain)

-- | The domain from which you want to retrieve details.
getMailDomain_domainName :: Lens.Lens' GetMailDomain Prelude.Text
getMailDomain_domainName :: Lens' GetMailDomain Text
getMailDomain_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomain' {Text
domainName :: Text
$sel:domainName:GetMailDomain' :: GetMailDomain -> Text
domainName} -> Text
domainName) (\s :: GetMailDomain
s@GetMailDomain' {} Text
a -> GetMailDomain
s {$sel:domainName:GetMailDomain' :: Text
domainName = Text
a} :: GetMailDomain)

instance Core.AWSRequest GetMailDomain where
  type
    AWSResponse GetMailDomain =
      GetMailDomainResponse
  request :: (Service -> Service) -> GetMailDomain -> Request GetMailDomain
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetMailDomain
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetMailDomain)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe DnsRecordVerificationStatus
-> Maybe Bool
-> Maybe Bool
-> Maybe DnsRecordVerificationStatus
-> Maybe [DnsRecord]
-> Int
-> GetMailDomainResponse
GetMailDomainResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DkimVerificationStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IsDefault")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IsTestDomain")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OwnershipVerificationStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Records" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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 GetMailDomain where
  hashWithSalt :: Int -> GetMailDomain -> Int
hashWithSalt Int
_salt GetMailDomain' {Text
domainName :: Text
organizationId :: Text
$sel:domainName:GetMailDomain' :: GetMailDomain -> Text
$sel:organizationId:GetMailDomain' :: GetMailDomain -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

instance Prelude.NFData GetMailDomain where
  rnf :: GetMailDomain -> ()
rnf GetMailDomain' {Text
domainName :: Text
organizationId :: Text
$sel:domainName:GetMailDomain' :: GetMailDomain -> Text
$sel:organizationId:GetMailDomain' :: GetMailDomain -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

instance Data.ToHeaders GetMailDomain where
  toHeaders :: GetMailDomain -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"WorkMailService.GetMailDomain" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetMailDomain where
  toJSON :: GetMailDomain -> Value
toJSON GetMailDomain' {Text
domainName :: Text
organizationId :: Text
$sel:domainName:GetMailDomain' :: GetMailDomain -> Text
$sel:organizationId:GetMailDomain' :: GetMailDomain -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
            forall a. a -> Maybe a
Prelude.Just (Key
"DomainName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainName)
          ]
      )

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

instance Data.ToQuery GetMailDomain where
  toQuery :: GetMailDomain -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetMailDomainResponse' smart constructor.
data GetMailDomainResponse = GetMailDomainResponse'
  { -- | Indicates the status of a DKIM verification.
    GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
dkimVerificationStatus :: Prelude.Maybe DnsRecordVerificationStatus,
    -- | Specifies whether the domain is the default domain for your
    -- organization.
    GetMailDomainResponse -> Maybe Bool
isDefault :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether the domain is a test domain provided by WorkMail, or a
    -- custom domain.
    GetMailDomainResponse -> Maybe Bool
isTestDomain :: Prelude.Maybe Prelude.Bool,
    -- | Indicates the status of the domain ownership verification.
    GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
ownershipVerificationStatus :: Prelude.Maybe DnsRecordVerificationStatus,
    -- | A list of the DNS records that WorkMail recommends adding in your DNS
    -- provider for the best user experience. The records configure your domain
    -- with DMARC, SPF, DKIM, and direct incoming email traffic to SES. See
    -- admin guide for more details.
    GetMailDomainResponse -> Maybe [DnsRecord]
records :: Prelude.Maybe [DnsRecord],
    -- | The response's http status code.
    GetMailDomainResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMailDomainResponse -> GetMailDomainResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMailDomainResponse -> GetMailDomainResponse -> Bool
$c/= :: GetMailDomainResponse -> GetMailDomainResponse -> Bool
== :: GetMailDomainResponse -> GetMailDomainResponse -> Bool
$c== :: GetMailDomainResponse -> GetMailDomainResponse -> Bool
Prelude.Eq, ReadPrec [GetMailDomainResponse]
ReadPrec GetMailDomainResponse
Int -> ReadS GetMailDomainResponse
ReadS [GetMailDomainResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMailDomainResponse]
$creadListPrec :: ReadPrec [GetMailDomainResponse]
readPrec :: ReadPrec GetMailDomainResponse
$creadPrec :: ReadPrec GetMailDomainResponse
readList :: ReadS [GetMailDomainResponse]
$creadList :: ReadS [GetMailDomainResponse]
readsPrec :: Int -> ReadS GetMailDomainResponse
$creadsPrec :: Int -> ReadS GetMailDomainResponse
Prelude.Read, Int -> GetMailDomainResponse -> ShowS
[GetMailDomainResponse] -> ShowS
GetMailDomainResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMailDomainResponse] -> ShowS
$cshowList :: [GetMailDomainResponse] -> ShowS
show :: GetMailDomainResponse -> String
$cshow :: GetMailDomainResponse -> String
showsPrec :: Int -> GetMailDomainResponse -> ShowS
$cshowsPrec :: Int -> GetMailDomainResponse -> ShowS
Prelude.Show, forall x. Rep GetMailDomainResponse x -> GetMailDomainResponse
forall x. GetMailDomainResponse -> Rep GetMailDomainResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMailDomainResponse x -> GetMailDomainResponse
$cfrom :: forall x. GetMailDomainResponse -> Rep GetMailDomainResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMailDomainResponse' 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:
--
-- 'dkimVerificationStatus', 'getMailDomainResponse_dkimVerificationStatus' - Indicates the status of a DKIM verification.
--
-- 'isDefault', 'getMailDomainResponse_isDefault' - Specifies whether the domain is the default domain for your
-- organization.
--
-- 'isTestDomain', 'getMailDomainResponse_isTestDomain' - Specifies whether the domain is a test domain provided by WorkMail, or a
-- custom domain.
--
-- 'ownershipVerificationStatus', 'getMailDomainResponse_ownershipVerificationStatus' - Indicates the status of the domain ownership verification.
--
-- 'records', 'getMailDomainResponse_records' - A list of the DNS records that WorkMail recommends adding in your DNS
-- provider for the best user experience. The records configure your domain
-- with DMARC, SPF, DKIM, and direct incoming email traffic to SES. See
-- admin guide for more details.
--
-- 'httpStatus', 'getMailDomainResponse_httpStatus' - The response's http status code.
newGetMailDomainResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMailDomainResponse
newGetMailDomainResponse :: Int -> GetMailDomainResponse
newGetMailDomainResponse Int
pHttpStatus_ =
  GetMailDomainResponse'
    { $sel:dkimVerificationStatus:GetMailDomainResponse' :: Maybe DnsRecordVerificationStatus
dkimVerificationStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:isDefault:GetMailDomainResponse' :: Maybe Bool
isDefault = forall a. Maybe a
Prelude.Nothing,
      $sel:isTestDomain:GetMailDomainResponse' :: Maybe Bool
isTestDomain = forall a. Maybe a
Prelude.Nothing,
      $sel:ownershipVerificationStatus:GetMailDomainResponse' :: Maybe DnsRecordVerificationStatus
ownershipVerificationStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:records:GetMailDomainResponse' :: Maybe [DnsRecord]
records = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMailDomainResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Indicates the status of a DKIM verification.
getMailDomainResponse_dkimVerificationStatus :: Lens.Lens' GetMailDomainResponse (Prelude.Maybe DnsRecordVerificationStatus)
getMailDomainResponse_dkimVerificationStatus :: Lens' GetMailDomainResponse (Maybe DnsRecordVerificationStatus)
getMailDomainResponse_dkimVerificationStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomainResponse' {Maybe DnsRecordVerificationStatus
dkimVerificationStatus :: Maybe DnsRecordVerificationStatus
$sel:dkimVerificationStatus:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
dkimVerificationStatus} -> Maybe DnsRecordVerificationStatus
dkimVerificationStatus) (\s :: GetMailDomainResponse
s@GetMailDomainResponse' {} Maybe DnsRecordVerificationStatus
a -> GetMailDomainResponse
s {$sel:dkimVerificationStatus:GetMailDomainResponse' :: Maybe DnsRecordVerificationStatus
dkimVerificationStatus = Maybe DnsRecordVerificationStatus
a} :: GetMailDomainResponse)

-- | Specifies whether the domain is the default domain for your
-- organization.
getMailDomainResponse_isDefault :: Lens.Lens' GetMailDomainResponse (Prelude.Maybe Prelude.Bool)
getMailDomainResponse_isDefault :: Lens' GetMailDomainResponse (Maybe Bool)
getMailDomainResponse_isDefault = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomainResponse' {Maybe Bool
isDefault :: Maybe Bool
$sel:isDefault:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe Bool
isDefault} -> Maybe Bool
isDefault) (\s :: GetMailDomainResponse
s@GetMailDomainResponse' {} Maybe Bool
a -> GetMailDomainResponse
s {$sel:isDefault:GetMailDomainResponse' :: Maybe Bool
isDefault = Maybe Bool
a} :: GetMailDomainResponse)

-- | Specifies whether the domain is a test domain provided by WorkMail, or a
-- custom domain.
getMailDomainResponse_isTestDomain :: Lens.Lens' GetMailDomainResponse (Prelude.Maybe Prelude.Bool)
getMailDomainResponse_isTestDomain :: Lens' GetMailDomainResponse (Maybe Bool)
getMailDomainResponse_isTestDomain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomainResponse' {Maybe Bool
isTestDomain :: Maybe Bool
$sel:isTestDomain:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe Bool
isTestDomain} -> Maybe Bool
isTestDomain) (\s :: GetMailDomainResponse
s@GetMailDomainResponse' {} Maybe Bool
a -> GetMailDomainResponse
s {$sel:isTestDomain:GetMailDomainResponse' :: Maybe Bool
isTestDomain = Maybe Bool
a} :: GetMailDomainResponse)

-- | Indicates the status of the domain ownership verification.
getMailDomainResponse_ownershipVerificationStatus :: Lens.Lens' GetMailDomainResponse (Prelude.Maybe DnsRecordVerificationStatus)
getMailDomainResponse_ownershipVerificationStatus :: Lens' GetMailDomainResponse (Maybe DnsRecordVerificationStatus)
getMailDomainResponse_ownershipVerificationStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomainResponse' {Maybe DnsRecordVerificationStatus
ownershipVerificationStatus :: Maybe DnsRecordVerificationStatus
$sel:ownershipVerificationStatus:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
ownershipVerificationStatus} -> Maybe DnsRecordVerificationStatus
ownershipVerificationStatus) (\s :: GetMailDomainResponse
s@GetMailDomainResponse' {} Maybe DnsRecordVerificationStatus
a -> GetMailDomainResponse
s {$sel:ownershipVerificationStatus:GetMailDomainResponse' :: Maybe DnsRecordVerificationStatus
ownershipVerificationStatus = Maybe DnsRecordVerificationStatus
a} :: GetMailDomainResponse)

-- | A list of the DNS records that WorkMail recommends adding in your DNS
-- provider for the best user experience. The records configure your domain
-- with DMARC, SPF, DKIM, and direct incoming email traffic to SES. See
-- admin guide for more details.
getMailDomainResponse_records :: Lens.Lens' GetMailDomainResponse (Prelude.Maybe [DnsRecord])
getMailDomainResponse_records :: Lens' GetMailDomainResponse (Maybe [DnsRecord])
getMailDomainResponse_records = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMailDomainResponse' {Maybe [DnsRecord]
records :: Maybe [DnsRecord]
$sel:records:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe [DnsRecord]
records} -> Maybe [DnsRecord]
records) (\s :: GetMailDomainResponse
s@GetMailDomainResponse' {} Maybe [DnsRecord]
a -> GetMailDomainResponse
s {$sel:records:GetMailDomainResponse' :: Maybe [DnsRecord]
records = Maybe [DnsRecord]
a} :: GetMailDomainResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetMailDomainResponse where
  rnf :: GetMailDomainResponse -> ()
rnf GetMailDomainResponse' {Int
Maybe Bool
Maybe [DnsRecord]
Maybe DnsRecordVerificationStatus
httpStatus :: Int
records :: Maybe [DnsRecord]
ownershipVerificationStatus :: Maybe DnsRecordVerificationStatus
isTestDomain :: Maybe Bool
isDefault :: Maybe Bool
dkimVerificationStatus :: Maybe DnsRecordVerificationStatus
$sel:httpStatus:GetMailDomainResponse' :: GetMailDomainResponse -> Int
$sel:records:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe [DnsRecord]
$sel:ownershipVerificationStatus:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
$sel:isTestDomain:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe Bool
$sel:isDefault:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe Bool
$sel:dkimVerificationStatus:GetMailDomainResponse' :: GetMailDomainResponse -> Maybe DnsRecordVerificationStatus
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DnsRecordVerificationStatus
dkimVerificationStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isDefault
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isTestDomain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DnsRecordVerificationStatus
ownershipVerificationStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DnsRecord]
records
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus