{-# 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.Route53.GetReusableDelegationSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a specified reusable delegation set,
-- including the four name servers that are assigned to the delegation set.
module Amazonka.Route53.GetReusableDelegationSet
  ( -- * Creating a Request
    GetReusableDelegationSet (..),
    newGetReusableDelegationSet,

    -- * Request Lenses
    getReusableDelegationSet_id,

    -- * Destructuring the Response
    GetReusableDelegationSetResponse (..),
    newGetReusableDelegationSetResponse,

    -- * Response Lenses
    getReusableDelegationSetResponse_httpStatus,
    getReusableDelegationSetResponse_delegationSet,
  )
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.Route53.Types

-- | A request to get information about a specified reusable delegation set.
--
-- /See:/ 'newGetReusableDelegationSet' smart constructor.
data GetReusableDelegationSet = GetReusableDelegationSet'
  { -- | The ID of the reusable delegation set that you want to get a list of
    -- name servers for.
    GetReusableDelegationSet -> ResourceId
id :: ResourceId
  }
  deriving (GetReusableDelegationSet -> GetReusableDelegationSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReusableDelegationSet -> GetReusableDelegationSet -> Bool
$c/= :: GetReusableDelegationSet -> GetReusableDelegationSet -> Bool
== :: GetReusableDelegationSet -> GetReusableDelegationSet -> Bool
$c== :: GetReusableDelegationSet -> GetReusableDelegationSet -> Bool
Prelude.Eq, ReadPrec [GetReusableDelegationSet]
ReadPrec GetReusableDelegationSet
Int -> ReadS GetReusableDelegationSet
ReadS [GetReusableDelegationSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReusableDelegationSet]
$creadListPrec :: ReadPrec [GetReusableDelegationSet]
readPrec :: ReadPrec GetReusableDelegationSet
$creadPrec :: ReadPrec GetReusableDelegationSet
readList :: ReadS [GetReusableDelegationSet]
$creadList :: ReadS [GetReusableDelegationSet]
readsPrec :: Int -> ReadS GetReusableDelegationSet
$creadsPrec :: Int -> ReadS GetReusableDelegationSet
Prelude.Read, Int -> GetReusableDelegationSet -> ShowS
[GetReusableDelegationSet] -> ShowS
GetReusableDelegationSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReusableDelegationSet] -> ShowS
$cshowList :: [GetReusableDelegationSet] -> ShowS
show :: GetReusableDelegationSet -> String
$cshow :: GetReusableDelegationSet -> String
showsPrec :: Int -> GetReusableDelegationSet -> ShowS
$cshowsPrec :: Int -> GetReusableDelegationSet -> ShowS
Prelude.Show, forall x.
Rep GetReusableDelegationSet x -> GetReusableDelegationSet
forall x.
GetReusableDelegationSet -> Rep GetReusableDelegationSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetReusableDelegationSet x -> GetReusableDelegationSet
$cfrom :: forall x.
GetReusableDelegationSet -> Rep GetReusableDelegationSet x
Prelude.Generic)

-- |
-- Create a value of 'GetReusableDelegationSet' 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:
--
-- 'id', 'getReusableDelegationSet_id' - The ID of the reusable delegation set that you want to get a list of
-- name servers for.
newGetReusableDelegationSet ::
  -- | 'id'
  ResourceId ->
  GetReusableDelegationSet
newGetReusableDelegationSet :: ResourceId -> GetReusableDelegationSet
newGetReusableDelegationSet ResourceId
pId_ =
  GetReusableDelegationSet' {$sel:id:GetReusableDelegationSet' :: ResourceId
id = ResourceId
pId_}

-- | The ID of the reusable delegation set that you want to get a list of
-- name servers for.
getReusableDelegationSet_id :: Lens.Lens' GetReusableDelegationSet ResourceId
getReusableDelegationSet_id :: Lens' GetReusableDelegationSet ResourceId
getReusableDelegationSet_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReusableDelegationSet' {ResourceId
id :: ResourceId
$sel:id:GetReusableDelegationSet' :: GetReusableDelegationSet -> ResourceId
id} -> ResourceId
id) (\s :: GetReusableDelegationSet
s@GetReusableDelegationSet' {} ResourceId
a -> GetReusableDelegationSet
s {$sel:id:GetReusableDelegationSet' :: ResourceId
id = ResourceId
a} :: GetReusableDelegationSet)

instance Core.AWSRequest GetReusableDelegationSet where
  type
    AWSResponse GetReusableDelegationSet =
      GetReusableDelegationSetResponse
  request :: (Service -> Service)
-> GetReusableDelegationSet -> Request GetReusableDelegationSet
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetReusableDelegationSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetReusableDelegationSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> DelegationSet -> GetReusableDelegationSetResponse
GetReusableDelegationSetResponse'
            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 a
Data..@ Text
"DelegationSet")
      )

instance Prelude.Hashable GetReusableDelegationSet where
  hashWithSalt :: Int -> GetReusableDelegationSet -> Int
hashWithSalt Int
_salt GetReusableDelegationSet' {ResourceId
id :: ResourceId
$sel:id:GetReusableDelegationSet' :: GetReusableDelegationSet -> ResourceId
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceId
id

instance Prelude.NFData GetReusableDelegationSet where
  rnf :: GetReusableDelegationSet -> ()
rnf GetReusableDelegationSet' {ResourceId
id :: ResourceId
$sel:id:GetReusableDelegationSet' :: GetReusableDelegationSet -> ResourceId
..} = forall a. NFData a => a -> ()
Prelude.rnf ResourceId
id

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

instance Data.ToPath GetReusableDelegationSet where
  toPath :: GetReusableDelegationSet -> ByteString
toPath GetReusableDelegationSet' {ResourceId
id :: ResourceId
$sel:id:GetReusableDelegationSet' :: GetReusableDelegationSet -> ResourceId
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2013-04-01/delegationset/", forall a. ToByteString a => a -> ByteString
Data.toBS ResourceId
id]

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

-- | A complex type that contains the response to the
-- @GetReusableDelegationSet@ request.
--
-- /See:/ 'newGetReusableDelegationSetResponse' smart constructor.
data GetReusableDelegationSetResponse = GetReusableDelegationSetResponse'
  { -- | The response's http status code.
    GetReusableDelegationSetResponse -> Int
httpStatus :: Prelude.Int,
    -- | A complex type that contains information about the reusable delegation
    -- set.
    GetReusableDelegationSetResponse -> DelegationSet
delegationSet :: DelegationSet
  }
  deriving (GetReusableDelegationSetResponse
-> GetReusableDelegationSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReusableDelegationSetResponse
-> GetReusableDelegationSetResponse -> Bool
$c/= :: GetReusableDelegationSetResponse
-> GetReusableDelegationSetResponse -> Bool
== :: GetReusableDelegationSetResponse
-> GetReusableDelegationSetResponse -> Bool
$c== :: GetReusableDelegationSetResponse
-> GetReusableDelegationSetResponse -> Bool
Prelude.Eq, ReadPrec [GetReusableDelegationSetResponse]
ReadPrec GetReusableDelegationSetResponse
Int -> ReadS GetReusableDelegationSetResponse
ReadS [GetReusableDelegationSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReusableDelegationSetResponse]
$creadListPrec :: ReadPrec [GetReusableDelegationSetResponse]
readPrec :: ReadPrec GetReusableDelegationSetResponse
$creadPrec :: ReadPrec GetReusableDelegationSetResponse
readList :: ReadS [GetReusableDelegationSetResponse]
$creadList :: ReadS [GetReusableDelegationSetResponse]
readsPrec :: Int -> ReadS GetReusableDelegationSetResponse
$creadsPrec :: Int -> ReadS GetReusableDelegationSetResponse
Prelude.Read, Int -> GetReusableDelegationSetResponse -> ShowS
[GetReusableDelegationSetResponse] -> ShowS
GetReusableDelegationSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReusableDelegationSetResponse] -> ShowS
$cshowList :: [GetReusableDelegationSetResponse] -> ShowS
show :: GetReusableDelegationSetResponse -> String
$cshow :: GetReusableDelegationSetResponse -> String
showsPrec :: Int -> GetReusableDelegationSetResponse -> ShowS
$cshowsPrec :: Int -> GetReusableDelegationSetResponse -> ShowS
Prelude.Show, forall x.
Rep GetReusableDelegationSetResponse x
-> GetReusableDelegationSetResponse
forall x.
GetReusableDelegationSetResponse
-> Rep GetReusableDelegationSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetReusableDelegationSetResponse x
-> GetReusableDelegationSetResponse
$cfrom :: forall x.
GetReusableDelegationSetResponse
-> Rep GetReusableDelegationSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetReusableDelegationSetResponse' 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', 'getReusableDelegationSetResponse_httpStatus' - The response's http status code.
--
-- 'delegationSet', 'getReusableDelegationSetResponse_delegationSet' - A complex type that contains information about the reusable delegation
-- set.
newGetReusableDelegationSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'delegationSet'
  DelegationSet ->
  GetReusableDelegationSetResponse
newGetReusableDelegationSetResponse :: Int -> DelegationSet -> GetReusableDelegationSetResponse
newGetReusableDelegationSetResponse
  Int
pHttpStatus_
  DelegationSet
pDelegationSet_ =
    GetReusableDelegationSetResponse'
      { $sel:httpStatus:GetReusableDelegationSetResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:delegationSet:GetReusableDelegationSetResponse' :: DelegationSet
delegationSet = DelegationSet
pDelegationSet_
      }

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

-- | A complex type that contains information about the reusable delegation
-- set.
getReusableDelegationSetResponse_delegationSet :: Lens.Lens' GetReusableDelegationSetResponse DelegationSet
getReusableDelegationSetResponse_delegationSet :: Lens' GetReusableDelegationSetResponse DelegationSet
getReusableDelegationSetResponse_delegationSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReusableDelegationSetResponse' {DelegationSet
delegationSet :: DelegationSet
$sel:delegationSet:GetReusableDelegationSetResponse' :: GetReusableDelegationSetResponse -> DelegationSet
delegationSet} -> DelegationSet
delegationSet) (\s :: GetReusableDelegationSetResponse
s@GetReusableDelegationSetResponse' {} DelegationSet
a -> GetReusableDelegationSetResponse
s {$sel:delegationSet:GetReusableDelegationSetResponse' :: DelegationSet
delegationSet = DelegationSet
a} :: GetReusableDelegationSetResponse)

instance
  Prelude.NFData
    GetReusableDelegationSetResponse
  where
  rnf :: GetReusableDelegationSetResponse -> ()
rnf GetReusableDelegationSetResponse' {Int
DelegationSet
delegationSet :: DelegationSet
httpStatus :: Int
$sel:delegationSet:GetReusableDelegationSetResponse' :: GetReusableDelegationSetResponse -> DelegationSet
$sel:httpStatus:GetReusableDelegationSetResponse' :: GetReusableDelegationSetResponse -> 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 DelegationSet
delegationSet