{-# 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.RetrieveDomainAuthCode
-- 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 returns the authorization code for the domain. To
-- transfer a domain to another registrar, you provide this value to the
-- new registrar.
module Amazonka.Route53Domains.RetrieveDomainAuthCode
  ( -- * Creating a Request
    RetrieveDomainAuthCode (..),
    newRetrieveDomainAuthCode,

    -- * Request Lenses
    retrieveDomainAuthCode_domainName,

    -- * Destructuring the Response
    RetrieveDomainAuthCodeResponse (..),
    newRetrieveDomainAuthCodeResponse,

    -- * Response Lenses
    retrieveDomainAuthCodeResponse_authCode,
    retrieveDomainAuthCodeResponse_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

-- | A request for the authorization code for the specified domain. To
-- transfer a domain to another registrar, you provide this value to the
-- new registrar.
--
-- /See:/ 'newRetrieveDomainAuthCode' smart constructor.
data RetrieveDomainAuthCode = RetrieveDomainAuthCode'
  { -- | The name of the domain that you want to get an authorization code for.
    RetrieveDomainAuthCode -> Text
domainName :: Prelude.Text
  }
  deriving (RetrieveDomainAuthCode -> RetrieveDomainAuthCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetrieveDomainAuthCode -> RetrieveDomainAuthCode -> Bool
$c/= :: RetrieveDomainAuthCode -> RetrieveDomainAuthCode -> Bool
== :: RetrieveDomainAuthCode -> RetrieveDomainAuthCode -> Bool
$c== :: RetrieveDomainAuthCode -> RetrieveDomainAuthCode -> Bool
Prelude.Eq, ReadPrec [RetrieveDomainAuthCode]
ReadPrec RetrieveDomainAuthCode
Int -> ReadS RetrieveDomainAuthCode
ReadS [RetrieveDomainAuthCode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetrieveDomainAuthCode]
$creadListPrec :: ReadPrec [RetrieveDomainAuthCode]
readPrec :: ReadPrec RetrieveDomainAuthCode
$creadPrec :: ReadPrec RetrieveDomainAuthCode
readList :: ReadS [RetrieveDomainAuthCode]
$creadList :: ReadS [RetrieveDomainAuthCode]
readsPrec :: Int -> ReadS RetrieveDomainAuthCode
$creadsPrec :: Int -> ReadS RetrieveDomainAuthCode
Prelude.Read, Int -> RetrieveDomainAuthCode -> ShowS
[RetrieveDomainAuthCode] -> ShowS
RetrieveDomainAuthCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetrieveDomainAuthCode] -> ShowS
$cshowList :: [RetrieveDomainAuthCode] -> ShowS
show :: RetrieveDomainAuthCode -> String
$cshow :: RetrieveDomainAuthCode -> String
showsPrec :: Int -> RetrieveDomainAuthCode -> ShowS
$cshowsPrec :: Int -> RetrieveDomainAuthCode -> ShowS
Prelude.Show, forall x. Rep RetrieveDomainAuthCode x -> RetrieveDomainAuthCode
forall x. RetrieveDomainAuthCode -> Rep RetrieveDomainAuthCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RetrieveDomainAuthCode x -> RetrieveDomainAuthCode
$cfrom :: forall x. RetrieveDomainAuthCode -> Rep RetrieveDomainAuthCode x
Prelude.Generic)

-- |
-- Create a value of 'RetrieveDomainAuthCode' 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', 'retrieveDomainAuthCode_domainName' - The name of the domain that you want to get an authorization code for.
newRetrieveDomainAuthCode ::
  -- | 'domainName'
  Prelude.Text ->
  RetrieveDomainAuthCode
newRetrieveDomainAuthCode :: Text -> RetrieveDomainAuthCode
newRetrieveDomainAuthCode Text
pDomainName_ =
  RetrieveDomainAuthCode' {$sel:domainName:RetrieveDomainAuthCode' :: Text
domainName = Text
pDomainName_}

-- | The name of the domain that you want to get an authorization code for.
retrieveDomainAuthCode_domainName :: Lens.Lens' RetrieveDomainAuthCode Prelude.Text
retrieveDomainAuthCode_domainName :: Lens' RetrieveDomainAuthCode Text
retrieveDomainAuthCode_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveDomainAuthCode' {Text
domainName :: Text
$sel:domainName:RetrieveDomainAuthCode' :: RetrieveDomainAuthCode -> Text
domainName} -> Text
domainName) (\s :: RetrieveDomainAuthCode
s@RetrieveDomainAuthCode' {} Text
a -> RetrieveDomainAuthCode
s {$sel:domainName:RetrieveDomainAuthCode' :: Text
domainName = Text
a} :: RetrieveDomainAuthCode)

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

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

instance Data.ToHeaders RetrieveDomainAuthCode where
  toHeaders :: RetrieveDomainAuthCode -> 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.RetrieveDomainAuthCode" ::
                          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 RetrieveDomainAuthCode where
  toJSON :: RetrieveDomainAuthCode -> Value
toJSON RetrieveDomainAuthCode' {Text
domainName :: Text
$sel:domainName:RetrieveDomainAuthCode' :: RetrieveDomainAuthCode -> 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 RetrieveDomainAuthCode where
  toPath :: RetrieveDomainAuthCode -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | The RetrieveDomainAuthCode response includes the following element.
--
-- /See:/ 'newRetrieveDomainAuthCodeResponse' smart constructor.
data RetrieveDomainAuthCodeResponse = RetrieveDomainAuthCodeResponse'
  { -- | The authorization code for the domain.
    RetrieveDomainAuthCodeResponse -> Maybe (Sensitive Text)
authCode :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    RetrieveDomainAuthCodeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RetrieveDomainAuthCodeResponse
-> RetrieveDomainAuthCodeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetrieveDomainAuthCodeResponse
-> RetrieveDomainAuthCodeResponse -> Bool
$c/= :: RetrieveDomainAuthCodeResponse
-> RetrieveDomainAuthCodeResponse -> Bool
== :: RetrieveDomainAuthCodeResponse
-> RetrieveDomainAuthCodeResponse -> Bool
$c== :: RetrieveDomainAuthCodeResponse
-> RetrieveDomainAuthCodeResponse -> Bool
Prelude.Eq, Int -> RetrieveDomainAuthCodeResponse -> ShowS
[RetrieveDomainAuthCodeResponse] -> ShowS
RetrieveDomainAuthCodeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetrieveDomainAuthCodeResponse] -> ShowS
$cshowList :: [RetrieveDomainAuthCodeResponse] -> ShowS
show :: RetrieveDomainAuthCodeResponse -> String
$cshow :: RetrieveDomainAuthCodeResponse -> String
showsPrec :: Int -> RetrieveDomainAuthCodeResponse -> ShowS
$cshowsPrec :: Int -> RetrieveDomainAuthCodeResponse -> ShowS
Prelude.Show, forall x.
Rep RetrieveDomainAuthCodeResponse x
-> RetrieveDomainAuthCodeResponse
forall x.
RetrieveDomainAuthCodeResponse
-> Rep RetrieveDomainAuthCodeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RetrieveDomainAuthCodeResponse x
-> RetrieveDomainAuthCodeResponse
$cfrom :: forall x.
RetrieveDomainAuthCodeResponse
-> Rep RetrieveDomainAuthCodeResponse x
Prelude.Generic)

-- |
-- Create a value of 'RetrieveDomainAuthCodeResponse' 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:
--
-- 'authCode', 'retrieveDomainAuthCodeResponse_authCode' - The authorization code for the domain.
--
-- 'httpStatus', 'retrieveDomainAuthCodeResponse_httpStatus' - The response's http status code.
newRetrieveDomainAuthCodeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RetrieveDomainAuthCodeResponse
newRetrieveDomainAuthCodeResponse :: Int -> RetrieveDomainAuthCodeResponse
newRetrieveDomainAuthCodeResponse Int
pHttpStatus_ =
  RetrieveDomainAuthCodeResponse'
    { $sel:authCode:RetrieveDomainAuthCodeResponse' :: Maybe (Sensitive Text)
authCode =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RetrieveDomainAuthCodeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The authorization code for the domain.
retrieveDomainAuthCodeResponse_authCode :: Lens.Lens' RetrieveDomainAuthCodeResponse (Prelude.Maybe Prelude.Text)
retrieveDomainAuthCodeResponse_authCode :: Lens' RetrieveDomainAuthCodeResponse (Maybe Text)
retrieveDomainAuthCodeResponse_authCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveDomainAuthCodeResponse' {Maybe (Sensitive Text)
authCode :: Maybe (Sensitive Text)
$sel:authCode:RetrieveDomainAuthCodeResponse' :: RetrieveDomainAuthCodeResponse -> Maybe (Sensitive Text)
authCode} -> Maybe (Sensitive Text)
authCode) (\s :: RetrieveDomainAuthCodeResponse
s@RetrieveDomainAuthCodeResponse' {} Maybe (Sensitive Text)
a -> RetrieveDomainAuthCodeResponse
s {$sel:authCode:RetrieveDomainAuthCodeResponse' :: Maybe (Sensitive Text)
authCode = Maybe (Sensitive Text)
a} :: RetrieveDomainAuthCodeResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive

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

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