{-# 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.Route53Domains.UpdateDomainContactPrivacy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation updates the specified domain contact\'s privacy setting.
-- When privacy protection is enabled, contact information such as email
-- address is replaced either with contact information for Amazon Registrar
-- (for .com, .net, and .org domains) or with contact information for our
-- registrar associate, Gandi.
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
--
-- This operation affects only the contact information for the specified
-- contact type (administrative, registrant, or technical). If the request
-- succeeds, Amazon Route 53 returns an operation ID that you can use with
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_GetOperationDetail.html GetOperationDetail>
-- to track the progress and completion of the action. If the request
-- doesn\'t complete successfully, the domain registrant will be notified
-- by email.
--
-- By disabling the privacy service via API, you consent to the publication
-- of the contact information provided for this domain via the public WHOIS
-- database. You certify that you are the registrant of this domain name
-- and have the authority to make this decision. You may withdraw your
-- consent at any time by enabling privacy protection using either
-- @UpdateDomainContactPrivacy@ or the Route 53 console. Enabling privacy
-- protection removes the contact information provided for this domain from
-- the WHOIS database. For more information on our privacy practices, see
-- <https://aws.amazon.com/privacy/>.
module Amazonka.Route53Domains.UpdateDomainContactPrivacy
  ( -- * Creating a Request
    UpdateDomainContactPrivacy (..),
    newUpdateDomainContactPrivacy,

    -- * Request Lenses
    updateDomainContactPrivacy_adminPrivacy,
    updateDomainContactPrivacy_registrantPrivacy,
    updateDomainContactPrivacy_techPrivacy,
    updateDomainContactPrivacy_domainName,

    -- * Destructuring the Response
    UpdateDomainContactPrivacyResponse (..),
    newUpdateDomainContactPrivacyResponse,

    -- * Response Lenses
    updateDomainContactPrivacyResponse_operationId,
    updateDomainContactPrivacyResponse_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.Route53Domains.Types

-- | The UpdateDomainContactPrivacy request includes the following elements.
--
-- /See:/ 'newUpdateDomainContactPrivacy' smart constructor.
data UpdateDomainContactPrivacy = UpdateDomainContactPrivacy'
  { -- | Whether you want to conceal contact information from WHOIS queries. If
    -- you specify @true@, WHOIS (\"who is\") queries return contact
    -- information either for Amazon Registrar (for .com, .net, and .org
    -- domains) or for our registrar associate, Gandi (for all other TLDs). If
    -- you specify @false@, WHOIS queries return the information that you
    -- entered for the admin contact.
    --
    -- You must specify the same privacy setting for the administrative,
    -- registrant, and technical contacts.
    UpdateDomainContactPrivacy -> Maybe Bool
adminPrivacy :: Prelude.Maybe Prelude.Bool,
    -- | Whether you want to conceal contact information from WHOIS queries. If
    -- you specify @true@, WHOIS (\"who is\") queries return contact
    -- information either for Amazon Registrar (for .com, .net, and .org
    -- domains) or for our registrar associate, Gandi (for all other TLDs). If
    -- you specify @false@, WHOIS queries return the information that you
    -- entered for the registrant contact (domain owner).
    --
    -- You must specify the same privacy setting for the administrative,
    -- registrant, and technical contacts.
    UpdateDomainContactPrivacy -> Maybe Bool
registrantPrivacy :: Prelude.Maybe Prelude.Bool,
    -- | Whether you want to conceal contact information from WHOIS queries. If
    -- you specify @true@, WHOIS (\"who is\") queries return contact
    -- information either for Amazon Registrar (for .com, .net, and .org
    -- domains) or for our registrar associate, Gandi (for all other TLDs). If
    -- you specify @false@, WHOIS queries return the information that you
    -- entered for the technical contact.
    --
    -- You must specify the same privacy setting for the administrative,
    -- registrant, and technical contacts.
    UpdateDomainContactPrivacy -> Maybe Bool
techPrivacy :: Prelude.Maybe Prelude.Bool,
    -- | The name of the domain that you want to update the privacy setting for.
    UpdateDomainContactPrivacy -> Text
domainName :: Prelude.Text
  }
  deriving (UpdateDomainContactPrivacy -> UpdateDomainContactPrivacy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDomainContactPrivacy -> UpdateDomainContactPrivacy -> Bool
$c/= :: UpdateDomainContactPrivacy -> UpdateDomainContactPrivacy -> Bool
== :: UpdateDomainContactPrivacy -> UpdateDomainContactPrivacy -> Bool
$c== :: UpdateDomainContactPrivacy -> UpdateDomainContactPrivacy -> Bool
Prelude.Eq, ReadPrec [UpdateDomainContactPrivacy]
ReadPrec UpdateDomainContactPrivacy
Int -> ReadS UpdateDomainContactPrivacy
ReadS [UpdateDomainContactPrivacy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDomainContactPrivacy]
$creadListPrec :: ReadPrec [UpdateDomainContactPrivacy]
readPrec :: ReadPrec UpdateDomainContactPrivacy
$creadPrec :: ReadPrec UpdateDomainContactPrivacy
readList :: ReadS [UpdateDomainContactPrivacy]
$creadList :: ReadS [UpdateDomainContactPrivacy]
readsPrec :: Int -> ReadS UpdateDomainContactPrivacy
$creadsPrec :: Int -> ReadS UpdateDomainContactPrivacy
Prelude.Read, Int -> UpdateDomainContactPrivacy -> ShowS
[UpdateDomainContactPrivacy] -> ShowS
UpdateDomainContactPrivacy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDomainContactPrivacy] -> ShowS
$cshowList :: [UpdateDomainContactPrivacy] -> ShowS
show :: UpdateDomainContactPrivacy -> String
$cshow :: UpdateDomainContactPrivacy -> String
showsPrec :: Int -> UpdateDomainContactPrivacy -> ShowS
$cshowsPrec :: Int -> UpdateDomainContactPrivacy -> ShowS
Prelude.Show, forall x.
Rep UpdateDomainContactPrivacy x -> UpdateDomainContactPrivacy
forall x.
UpdateDomainContactPrivacy -> Rep UpdateDomainContactPrivacy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateDomainContactPrivacy x -> UpdateDomainContactPrivacy
$cfrom :: forall x.
UpdateDomainContactPrivacy -> Rep UpdateDomainContactPrivacy x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDomainContactPrivacy' 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:
--
-- 'adminPrivacy', 'updateDomainContactPrivacy_adminPrivacy' - Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the admin contact.
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
--
-- 'registrantPrivacy', 'updateDomainContactPrivacy_registrantPrivacy' - Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the registrant contact (domain owner).
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
--
-- 'techPrivacy', 'updateDomainContactPrivacy_techPrivacy' - Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the technical contact.
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
--
-- 'domainName', 'updateDomainContactPrivacy_domainName' - The name of the domain that you want to update the privacy setting for.
newUpdateDomainContactPrivacy ::
  -- | 'domainName'
  Prelude.Text ->
  UpdateDomainContactPrivacy
newUpdateDomainContactPrivacy :: Text -> UpdateDomainContactPrivacy
newUpdateDomainContactPrivacy Text
pDomainName_ =
  UpdateDomainContactPrivacy'
    { $sel:adminPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
adminPrivacy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registrantPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
registrantPrivacy = forall a. Maybe a
Prelude.Nothing,
      $sel:techPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
techPrivacy = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:UpdateDomainContactPrivacy' :: Text
domainName = Text
pDomainName_
    }

-- | Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the admin contact.
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
updateDomainContactPrivacy_adminPrivacy :: Lens.Lens' UpdateDomainContactPrivacy (Prelude.Maybe Prelude.Bool)
updateDomainContactPrivacy_adminPrivacy :: Lens' UpdateDomainContactPrivacy (Maybe Bool)
updateDomainContactPrivacy_adminPrivacy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDomainContactPrivacy' {Maybe Bool
adminPrivacy :: Maybe Bool
$sel:adminPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
adminPrivacy} -> Maybe Bool
adminPrivacy) (\s :: UpdateDomainContactPrivacy
s@UpdateDomainContactPrivacy' {} Maybe Bool
a -> UpdateDomainContactPrivacy
s {$sel:adminPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
adminPrivacy = Maybe Bool
a} :: UpdateDomainContactPrivacy)

-- | Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the registrant contact (domain owner).
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
updateDomainContactPrivacy_registrantPrivacy :: Lens.Lens' UpdateDomainContactPrivacy (Prelude.Maybe Prelude.Bool)
updateDomainContactPrivacy_registrantPrivacy :: Lens' UpdateDomainContactPrivacy (Maybe Bool)
updateDomainContactPrivacy_registrantPrivacy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDomainContactPrivacy' {Maybe Bool
registrantPrivacy :: Maybe Bool
$sel:registrantPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
registrantPrivacy} -> Maybe Bool
registrantPrivacy) (\s :: UpdateDomainContactPrivacy
s@UpdateDomainContactPrivacy' {} Maybe Bool
a -> UpdateDomainContactPrivacy
s {$sel:registrantPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
registrantPrivacy = Maybe Bool
a} :: UpdateDomainContactPrivacy)

-- | Whether you want to conceal contact information from WHOIS queries. If
-- you specify @true@, WHOIS (\"who is\") queries return contact
-- information either for Amazon Registrar (for .com, .net, and .org
-- domains) or for our registrar associate, Gandi (for all other TLDs). If
-- you specify @false@, WHOIS queries return the information that you
-- entered for the technical contact.
--
-- You must specify the same privacy setting for the administrative,
-- registrant, and technical contacts.
updateDomainContactPrivacy_techPrivacy :: Lens.Lens' UpdateDomainContactPrivacy (Prelude.Maybe Prelude.Bool)
updateDomainContactPrivacy_techPrivacy :: Lens' UpdateDomainContactPrivacy (Maybe Bool)
updateDomainContactPrivacy_techPrivacy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDomainContactPrivacy' {Maybe Bool
techPrivacy :: Maybe Bool
$sel:techPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
techPrivacy} -> Maybe Bool
techPrivacy) (\s :: UpdateDomainContactPrivacy
s@UpdateDomainContactPrivacy' {} Maybe Bool
a -> UpdateDomainContactPrivacy
s {$sel:techPrivacy:UpdateDomainContactPrivacy' :: Maybe Bool
techPrivacy = Maybe Bool
a} :: UpdateDomainContactPrivacy)

-- | The name of the domain that you want to update the privacy setting for.
updateDomainContactPrivacy_domainName :: Lens.Lens' UpdateDomainContactPrivacy Prelude.Text
updateDomainContactPrivacy_domainName :: Lens' UpdateDomainContactPrivacy Text
updateDomainContactPrivacy_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDomainContactPrivacy' {Text
domainName :: Text
$sel:domainName:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Text
domainName} -> Text
domainName) (\s :: UpdateDomainContactPrivacy
s@UpdateDomainContactPrivacy' {} Text
a -> UpdateDomainContactPrivacy
s {$sel:domainName:UpdateDomainContactPrivacy' :: Text
domainName = Text
a} :: UpdateDomainContactPrivacy)

instance Core.AWSRequest UpdateDomainContactPrivacy where
  type
    AWSResponse UpdateDomainContactPrivacy =
      UpdateDomainContactPrivacyResponse
  request :: (Service -> Service)
-> UpdateDomainContactPrivacy -> Request UpdateDomainContactPrivacy
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 UpdateDomainContactPrivacy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateDomainContactPrivacy)))
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 Text -> Int -> UpdateDomainContactPrivacyResponse
UpdateDomainContactPrivacyResponse'
            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
"OperationId")
            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 UpdateDomainContactPrivacy where
  hashWithSalt :: Int -> UpdateDomainContactPrivacy -> Int
hashWithSalt Int
_salt UpdateDomainContactPrivacy' {Maybe Bool
Text
domainName :: Text
techPrivacy :: Maybe Bool
registrantPrivacy :: Maybe Bool
adminPrivacy :: Maybe Bool
$sel:domainName:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Text
$sel:techPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:registrantPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:adminPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
adminPrivacy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
registrantPrivacy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
techPrivacy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

instance Prelude.NFData UpdateDomainContactPrivacy where
  rnf :: UpdateDomainContactPrivacy -> ()
rnf UpdateDomainContactPrivacy' {Maybe Bool
Text
domainName :: Text
techPrivacy :: Maybe Bool
registrantPrivacy :: Maybe Bool
adminPrivacy :: Maybe Bool
$sel:domainName:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Text
$sel:techPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:registrantPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:adminPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
adminPrivacy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
registrantPrivacy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
techPrivacy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

instance Data.ToHeaders UpdateDomainContactPrivacy where
  toHeaders :: UpdateDomainContactPrivacy -> 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
"Route53Domains_v20140515.UpdateDomainContactPrivacy" ::
                          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 UpdateDomainContactPrivacy where
  toJSON :: UpdateDomainContactPrivacy -> Value
toJSON UpdateDomainContactPrivacy' {Maybe Bool
Text
domainName :: Text
techPrivacy :: Maybe Bool
registrantPrivacy :: Maybe Bool
adminPrivacy :: Maybe Bool
$sel:domainName:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Text
$sel:techPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:registrantPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
$sel:adminPrivacy:UpdateDomainContactPrivacy' :: UpdateDomainContactPrivacy -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AdminPrivacy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
adminPrivacy,
            (Key
"RegistrantPrivacy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
registrantPrivacy,
            (Key
"TechPrivacy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
techPrivacy,
            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 UpdateDomainContactPrivacy where
  toPath :: UpdateDomainContactPrivacy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | The UpdateDomainContactPrivacy response includes the following element.
--
-- /See:/ 'newUpdateDomainContactPrivacyResponse' smart constructor.
data UpdateDomainContactPrivacyResponse = UpdateDomainContactPrivacyResponse'
  { -- | Identifier for tracking the progress of the request. To use this ID to
    -- query the operation status, use GetOperationDetail.
    UpdateDomainContactPrivacyResponse -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateDomainContactPrivacyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateDomainContactPrivacyResponse
-> UpdateDomainContactPrivacyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDomainContactPrivacyResponse
-> UpdateDomainContactPrivacyResponse -> Bool
$c/= :: UpdateDomainContactPrivacyResponse
-> UpdateDomainContactPrivacyResponse -> Bool
== :: UpdateDomainContactPrivacyResponse
-> UpdateDomainContactPrivacyResponse -> Bool
$c== :: UpdateDomainContactPrivacyResponse
-> UpdateDomainContactPrivacyResponse -> Bool
Prelude.Eq, ReadPrec [UpdateDomainContactPrivacyResponse]
ReadPrec UpdateDomainContactPrivacyResponse
Int -> ReadS UpdateDomainContactPrivacyResponse
ReadS [UpdateDomainContactPrivacyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDomainContactPrivacyResponse]
$creadListPrec :: ReadPrec [UpdateDomainContactPrivacyResponse]
readPrec :: ReadPrec UpdateDomainContactPrivacyResponse
$creadPrec :: ReadPrec UpdateDomainContactPrivacyResponse
readList :: ReadS [UpdateDomainContactPrivacyResponse]
$creadList :: ReadS [UpdateDomainContactPrivacyResponse]
readsPrec :: Int -> ReadS UpdateDomainContactPrivacyResponse
$creadsPrec :: Int -> ReadS UpdateDomainContactPrivacyResponse
Prelude.Read, Int -> UpdateDomainContactPrivacyResponse -> ShowS
[UpdateDomainContactPrivacyResponse] -> ShowS
UpdateDomainContactPrivacyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDomainContactPrivacyResponse] -> ShowS
$cshowList :: [UpdateDomainContactPrivacyResponse] -> ShowS
show :: UpdateDomainContactPrivacyResponse -> String
$cshow :: UpdateDomainContactPrivacyResponse -> String
showsPrec :: Int -> UpdateDomainContactPrivacyResponse -> ShowS
$cshowsPrec :: Int -> UpdateDomainContactPrivacyResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateDomainContactPrivacyResponse x
-> UpdateDomainContactPrivacyResponse
forall x.
UpdateDomainContactPrivacyResponse
-> Rep UpdateDomainContactPrivacyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateDomainContactPrivacyResponse x
-> UpdateDomainContactPrivacyResponse
$cfrom :: forall x.
UpdateDomainContactPrivacyResponse
-> Rep UpdateDomainContactPrivacyResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDomainContactPrivacyResponse' 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:
--
-- 'operationId', 'updateDomainContactPrivacyResponse_operationId' - Identifier for tracking the progress of the request. To use this ID to
-- query the operation status, use GetOperationDetail.
--
-- 'httpStatus', 'updateDomainContactPrivacyResponse_httpStatus' - The response's http status code.
newUpdateDomainContactPrivacyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateDomainContactPrivacyResponse
newUpdateDomainContactPrivacyResponse :: Int -> UpdateDomainContactPrivacyResponse
newUpdateDomainContactPrivacyResponse Int
pHttpStatus_ =
  UpdateDomainContactPrivacyResponse'
    { $sel:operationId:UpdateDomainContactPrivacyResponse' :: Maybe Text
operationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateDomainContactPrivacyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Identifier for tracking the progress of the request. To use this ID to
-- query the operation status, use GetOperationDetail.
updateDomainContactPrivacyResponse_operationId :: Lens.Lens' UpdateDomainContactPrivacyResponse (Prelude.Maybe Prelude.Text)
updateDomainContactPrivacyResponse_operationId :: Lens' UpdateDomainContactPrivacyResponse (Maybe Text)
updateDomainContactPrivacyResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDomainContactPrivacyResponse' {Maybe Text
operationId :: Maybe Text
$sel:operationId:UpdateDomainContactPrivacyResponse' :: UpdateDomainContactPrivacyResponse -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: UpdateDomainContactPrivacyResponse
s@UpdateDomainContactPrivacyResponse' {} Maybe Text
a -> UpdateDomainContactPrivacyResponse
s {$sel:operationId:UpdateDomainContactPrivacyResponse' :: Maybe Text
operationId = Maybe Text
a} :: UpdateDomainContactPrivacyResponse)

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

instance
  Prelude.NFData
    UpdateDomainContactPrivacyResponse
  where
  rnf :: UpdateDomainContactPrivacyResponse -> ()
rnf UpdateDomainContactPrivacyResponse' {Int
Maybe Text
httpStatus :: Int
operationId :: Maybe Text
$sel:httpStatus:UpdateDomainContactPrivacyResponse' :: UpdateDomainContactPrivacyResponse -> Int
$sel:operationId:UpdateDomainContactPrivacyResponse' :: UpdateDomainContactPrivacyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus