{-# 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.RejectDomainTransferFromAnotherAwsAccount
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Rejects the transfer of a domain from another Amazon Web Services
-- account to the current Amazon Web Services account. You initiate a
-- transfer betweenAmazon Web Services accounts using
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_TransferDomainToAnotherAwsAccount.html TransferDomainToAnotherAwsAccount>.
--
-- Use either
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_ListOperations.html ListOperations>
-- or
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_GetOperationDetail.html GetOperationDetail>
-- to determine whether the operation succeeded.
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_GetOperationDetail.html GetOperationDetail>
-- provides additional information, for example,
-- @Domain Transfer from Aws Account 111122223333 has been cancelled@.
module Amazonka.Route53Domains.RejectDomainTransferFromAnotherAwsAccount
  ( -- * Creating a Request
    RejectDomainTransferFromAnotherAwsAccount (..),
    newRejectDomainTransferFromAnotherAwsAccount,

    -- * Request Lenses
    rejectDomainTransferFromAnotherAwsAccount_domainName,

    -- * Destructuring the Response
    RejectDomainTransferFromAnotherAwsAccountResponse (..),
    newRejectDomainTransferFromAnotherAwsAccountResponse,

    -- * Response Lenses
    rejectDomainTransferFromAnotherAwsAccountResponse_operationId,
    rejectDomainTransferFromAnotherAwsAccountResponse_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 RejectDomainTransferFromAnotherAwsAccount request includes the
-- following element.
--
-- /See:/ 'newRejectDomainTransferFromAnotherAwsAccount' smart constructor.
data RejectDomainTransferFromAnotherAwsAccount = RejectDomainTransferFromAnotherAwsAccount'
  { -- | The name of the domain that was specified when another Amazon Web
    -- Services account submitted a
    -- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_TransferDomainToAnotherAwsAccount.html TransferDomainToAnotherAwsAccount>
    -- request.
    RejectDomainTransferFromAnotherAwsAccount -> Text
domainName :: Prelude.Text
  }
  deriving (RejectDomainTransferFromAnotherAwsAccount
-> RejectDomainTransferFromAnotherAwsAccount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RejectDomainTransferFromAnotherAwsAccount
-> RejectDomainTransferFromAnotherAwsAccount -> Bool
$c/= :: RejectDomainTransferFromAnotherAwsAccount
-> RejectDomainTransferFromAnotherAwsAccount -> Bool
== :: RejectDomainTransferFromAnotherAwsAccount
-> RejectDomainTransferFromAnotherAwsAccount -> Bool
$c== :: RejectDomainTransferFromAnotherAwsAccount
-> RejectDomainTransferFromAnotherAwsAccount -> Bool
Prelude.Eq, ReadPrec [RejectDomainTransferFromAnotherAwsAccount]
ReadPrec RejectDomainTransferFromAnotherAwsAccount
Int -> ReadS RejectDomainTransferFromAnotherAwsAccount
ReadS [RejectDomainTransferFromAnotherAwsAccount]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RejectDomainTransferFromAnotherAwsAccount]
$creadListPrec :: ReadPrec [RejectDomainTransferFromAnotherAwsAccount]
readPrec :: ReadPrec RejectDomainTransferFromAnotherAwsAccount
$creadPrec :: ReadPrec RejectDomainTransferFromAnotherAwsAccount
readList :: ReadS [RejectDomainTransferFromAnotherAwsAccount]
$creadList :: ReadS [RejectDomainTransferFromAnotherAwsAccount]
readsPrec :: Int -> ReadS RejectDomainTransferFromAnotherAwsAccount
$creadsPrec :: Int -> ReadS RejectDomainTransferFromAnotherAwsAccount
Prelude.Read, Int -> RejectDomainTransferFromAnotherAwsAccount -> ShowS
[RejectDomainTransferFromAnotherAwsAccount] -> ShowS
RejectDomainTransferFromAnotherAwsAccount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RejectDomainTransferFromAnotherAwsAccount] -> ShowS
$cshowList :: [RejectDomainTransferFromAnotherAwsAccount] -> ShowS
show :: RejectDomainTransferFromAnotherAwsAccount -> String
$cshow :: RejectDomainTransferFromAnotherAwsAccount -> String
showsPrec :: Int -> RejectDomainTransferFromAnotherAwsAccount -> ShowS
$cshowsPrec :: Int -> RejectDomainTransferFromAnotherAwsAccount -> ShowS
Prelude.Show, forall x.
Rep RejectDomainTransferFromAnotherAwsAccount x
-> RejectDomainTransferFromAnotherAwsAccount
forall x.
RejectDomainTransferFromAnotherAwsAccount
-> Rep RejectDomainTransferFromAnotherAwsAccount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RejectDomainTransferFromAnotherAwsAccount x
-> RejectDomainTransferFromAnotherAwsAccount
$cfrom :: forall x.
RejectDomainTransferFromAnotherAwsAccount
-> Rep RejectDomainTransferFromAnotherAwsAccount x
Prelude.Generic)

-- |
-- Create a value of 'RejectDomainTransferFromAnotherAwsAccount' 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:
--
-- 'domainName', 'rejectDomainTransferFromAnotherAwsAccount_domainName' - The name of the domain that was specified when another Amazon Web
-- Services account submitted a
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_TransferDomainToAnotherAwsAccount.html TransferDomainToAnotherAwsAccount>
-- request.
newRejectDomainTransferFromAnotherAwsAccount ::
  -- | 'domainName'
  Prelude.Text ->
  RejectDomainTransferFromAnotherAwsAccount
newRejectDomainTransferFromAnotherAwsAccount :: Text -> RejectDomainTransferFromAnotherAwsAccount
newRejectDomainTransferFromAnotherAwsAccount
  Text
pDomainName_ =
    RejectDomainTransferFromAnotherAwsAccount'
      { $sel:domainName:RejectDomainTransferFromAnotherAwsAccount' :: Text
domainName =
          Text
pDomainName_
      }

-- | The name of the domain that was specified when another Amazon Web
-- Services account submitted a
-- <https://docs.aws.amazon.com/Route53/latest/APIReference/API_domains_TransferDomainToAnotherAwsAccount.html TransferDomainToAnotherAwsAccount>
-- request.
rejectDomainTransferFromAnotherAwsAccount_domainName :: Lens.Lens' RejectDomainTransferFromAnotherAwsAccount Prelude.Text
rejectDomainTransferFromAnotherAwsAccount_domainName :: Lens' RejectDomainTransferFromAnotherAwsAccount Text
rejectDomainTransferFromAnotherAwsAccount_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RejectDomainTransferFromAnotherAwsAccount' {Text
domainName :: Text
$sel:domainName:RejectDomainTransferFromAnotherAwsAccount' :: RejectDomainTransferFromAnotherAwsAccount -> Text
domainName} -> Text
domainName) (\s :: RejectDomainTransferFromAnotherAwsAccount
s@RejectDomainTransferFromAnotherAwsAccount' {} Text
a -> RejectDomainTransferFromAnotherAwsAccount
s {$sel:domainName:RejectDomainTransferFromAnotherAwsAccount' :: Text
domainName = Text
a} :: RejectDomainTransferFromAnotherAwsAccount)

instance
  Core.AWSRequest
    RejectDomainTransferFromAnotherAwsAccount
  where
  type
    AWSResponse
      RejectDomainTransferFromAnotherAwsAccount =
      RejectDomainTransferFromAnotherAwsAccountResponse
  request :: (Service -> Service)
-> RejectDomainTransferFromAnotherAwsAccount
-> Request RejectDomainTransferFromAnotherAwsAccount
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 RejectDomainTransferFromAnotherAwsAccount
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse RejectDomainTransferFromAnotherAwsAccount)))
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 -> RejectDomainTransferFromAnotherAwsAccountResponse
RejectDomainTransferFromAnotherAwsAccountResponse'
            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
    RejectDomainTransferFromAnotherAwsAccount
  where
  hashWithSalt :: Int -> RejectDomainTransferFromAnotherAwsAccount -> Int
hashWithSalt
    Int
_salt
    RejectDomainTransferFromAnotherAwsAccount' {Text
domainName :: Text
$sel:domainName:RejectDomainTransferFromAnotherAwsAccount' :: RejectDomainTransferFromAnotherAwsAccount -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

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

instance
  Data.ToHeaders
    RejectDomainTransferFromAnotherAwsAccount
  where
  toHeaders :: RejectDomainTransferFromAnotherAwsAccount -> 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.RejectDomainTransferFromAnotherAwsAccount" ::
                          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
    RejectDomainTransferFromAnotherAwsAccount
  where
  toJSON :: RejectDomainTransferFromAnotherAwsAccount -> Value
toJSON RejectDomainTransferFromAnotherAwsAccount' {Text
domainName :: Text
$sel:domainName:RejectDomainTransferFromAnotherAwsAccount' :: RejectDomainTransferFromAnotherAwsAccount -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [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
    RejectDomainTransferFromAnotherAwsAccount
  where
  toPath :: RejectDomainTransferFromAnotherAwsAccount -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | The RejectDomainTransferFromAnotherAwsAccount response includes the
-- following element.
--
-- /See:/ 'newRejectDomainTransferFromAnotherAwsAccountResponse' smart constructor.
data RejectDomainTransferFromAnotherAwsAccountResponse = RejectDomainTransferFromAnotherAwsAccountResponse'
  { -- | The identifier that @TransferDomainToAnotherAwsAccount@ returned to
    -- track the progress of the request. Because the transfer request was
    -- rejected, the value is no longer valid, and you can\'t use
    -- @GetOperationDetail@ to query the operation status.
    RejectDomainTransferFromAnotherAwsAccountResponse -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RejectDomainTransferFromAnotherAwsAccountResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RejectDomainTransferFromAnotherAwsAccountResponse
-> RejectDomainTransferFromAnotherAwsAccountResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RejectDomainTransferFromAnotherAwsAccountResponse
-> RejectDomainTransferFromAnotherAwsAccountResponse -> Bool
$c/= :: RejectDomainTransferFromAnotherAwsAccountResponse
-> RejectDomainTransferFromAnotherAwsAccountResponse -> Bool
== :: RejectDomainTransferFromAnotherAwsAccountResponse
-> RejectDomainTransferFromAnotherAwsAccountResponse -> Bool
$c== :: RejectDomainTransferFromAnotherAwsAccountResponse
-> RejectDomainTransferFromAnotherAwsAccountResponse -> Bool
Prelude.Eq, ReadPrec [RejectDomainTransferFromAnotherAwsAccountResponse]
ReadPrec RejectDomainTransferFromAnotherAwsAccountResponse
Int -> ReadS RejectDomainTransferFromAnotherAwsAccountResponse
ReadS [RejectDomainTransferFromAnotherAwsAccountResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RejectDomainTransferFromAnotherAwsAccountResponse]
$creadListPrec :: ReadPrec [RejectDomainTransferFromAnotherAwsAccountResponse]
readPrec :: ReadPrec RejectDomainTransferFromAnotherAwsAccountResponse
$creadPrec :: ReadPrec RejectDomainTransferFromAnotherAwsAccountResponse
readList :: ReadS [RejectDomainTransferFromAnotherAwsAccountResponse]
$creadList :: ReadS [RejectDomainTransferFromAnotherAwsAccountResponse]
readsPrec :: Int -> ReadS RejectDomainTransferFromAnotherAwsAccountResponse
$creadsPrec :: Int -> ReadS RejectDomainTransferFromAnotherAwsAccountResponse
Prelude.Read, Int -> RejectDomainTransferFromAnotherAwsAccountResponse -> ShowS
[RejectDomainTransferFromAnotherAwsAccountResponse] -> ShowS
RejectDomainTransferFromAnotherAwsAccountResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RejectDomainTransferFromAnotherAwsAccountResponse] -> ShowS
$cshowList :: [RejectDomainTransferFromAnotherAwsAccountResponse] -> ShowS
show :: RejectDomainTransferFromAnotherAwsAccountResponse -> String
$cshow :: RejectDomainTransferFromAnotherAwsAccountResponse -> String
showsPrec :: Int -> RejectDomainTransferFromAnotherAwsAccountResponse -> ShowS
$cshowsPrec :: Int -> RejectDomainTransferFromAnotherAwsAccountResponse -> ShowS
Prelude.Show, forall x.
Rep RejectDomainTransferFromAnotherAwsAccountResponse x
-> RejectDomainTransferFromAnotherAwsAccountResponse
forall x.
RejectDomainTransferFromAnotherAwsAccountResponse
-> Rep RejectDomainTransferFromAnotherAwsAccountResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RejectDomainTransferFromAnotherAwsAccountResponse x
-> RejectDomainTransferFromAnotherAwsAccountResponse
$cfrom :: forall x.
RejectDomainTransferFromAnotherAwsAccountResponse
-> Rep RejectDomainTransferFromAnotherAwsAccountResponse x
Prelude.Generic)

-- |
-- Create a value of 'RejectDomainTransferFromAnotherAwsAccountResponse' 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', 'rejectDomainTransferFromAnotherAwsAccountResponse_operationId' - The identifier that @TransferDomainToAnotherAwsAccount@ returned to
-- track the progress of the request. Because the transfer request was
-- rejected, the value is no longer valid, and you can\'t use
-- @GetOperationDetail@ to query the operation status.
--
-- 'httpStatus', 'rejectDomainTransferFromAnotherAwsAccountResponse_httpStatus' - The response's http status code.
newRejectDomainTransferFromAnotherAwsAccountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RejectDomainTransferFromAnotherAwsAccountResponse
newRejectDomainTransferFromAnotherAwsAccountResponse :: Int -> RejectDomainTransferFromAnotherAwsAccountResponse
newRejectDomainTransferFromAnotherAwsAccountResponse
  Int
pHttpStatus_ =
    RejectDomainTransferFromAnotherAwsAccountResponse'
      { $sel:operationId:RejectDomainTransferFromAnotherAwsAccountResponse' :: Maybe Text
operationId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:RejectDomainTransferFromAnotherAwsAccountResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The identifier that @TransferDomainToAnotherAwsAccount@ returned to
-- track the progress of the request. Because the transfer request was
-- rejected, the value is no longer valid, and you can\'t use
-- @GetOperationDetail@ to query the operation status.
rejectDomainTransferFromAnotherAwsAccountResponse_operationId :: Lens.Lens' RejectDomainTransferFromAnotherAwsAccountResponse (Prelude.Maybe Prelude.Text)
rejectDomainTransferFromAnotherAwsAccountResponse_operationId :: Lens'
  RejectDomainTransferFromAnotherAwsAccountResponse (Maybe Text)
rejectDomainTransferFromAnotherAwsAccountResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RejectDomainTransferFromAnotherAwsAccountResponse' {Maybe Text
operationId :: Maybe Text
$sel:operationId:RejectDomainTransferFromAnotherAwsAccountResponse' :: RejectDomainTransferFromAnotherAwsAccountResponse -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: RejectDomainTransferFromAnotherAwsAccountResponse
s@RejectDomainTransferFromAnotherAwsAccountResponse' {} Maybe Text
a -> RejectDomainTransferFromAnotherAwsAccountResponse
s {$sel:operationId:RejectDomainTransferFromAnotherAwsAccountResponse' :: Maybe Text
operationId = Maybe Text
a} :: RejectDomainTransferFromAnotherAwsAccountResponse)

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

instance
  Prelude.NFData
    RejectDomainTransferFromAnotherAwsAccountResponse
  where
  rnf :: RejectDomainTransferFromAnotherAwsAccountResponse -> ()
rnf
    RejectDomainTransferFromAnotherAwsAccountResponse' {Int
Maybe Text
httpStatus :: Int
operationId :: Maybe Text
$sel:httpStatus:RejectDomainTransferFromAnotherAwsAccountResponse' :: RejectDomainTransferFromAnotherAwsAccountResponse -> Int
$sel:operationId:RejectDomainTransferFromAnotherAwsAccountResponse' :: RejectDomainTransferFromAnotherAwsAccountResponse -> 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