{-# 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.CreateReusableDelegationSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a delegation set (a group of four name servers) that can be
-- reused by multiple hosted zones that were created by the same Amazon Web
-- Services account.
--
-- You can also create a reusable delegation set that uses the four name
-- servers that are associated with an existing hosted zone. Specify the
-- hosted zone ID in the @CreateReusableDelegationSet@ request.
--
-- You can\'t associate a reusable delegation set with a private hosted
-- zone.
--
-- For information about using a reusable delegation set to configure white
-- label name servers, see
-- <https://docs.aws.amazon.com/Route53/latest/DeveloperGuide/white-label-name-servers.html Configuring White Label Name Servers>.
--
-- The process for migrating existing hosted zones to use a reusable
-- delegation set is comparable to the process for configuring white label
-- name servers. You need to perform the following steps:
--
-- 1.  Create a reusable delegation set.
--
-- 2.  Recreate hosted zones, and reduce the TTL to 60 seconds or less.
--
-- 3.  Recreate resource record sets in the new hosted zones.
--
-- 4.  Change the registrar\'s name servers to use the name servers for the
--     new hosted zones.
--
-- 5.  Monitor traffic for the website or application.
--
-- 6.  Change TTLs back to their original values.
--
-- If you want to migrate existing hosted zones to use a reusable
-- delegation set, the existing hosted zones can\'t use any of the name
-- servers that are assigned to the reusable delegation set. If one or more
-- hosted zones do use one or more name servers that are assigned to the
-- reusable delegation set, you can do one of the following:
--
-- -   For small numbers of hosted zones—up to a few hundred—it\'s
--     relatively easy to create reusable delegation sets until you get one
--     that has four name servers that don\'t overlap with any of the name
--     servers in your hosted zones.
--
-- -   For larger numbers of hosted zones, the easiest solution is to use
--     more than one reusable delegation set.
--
-- -   For larger numbers of hosted zones, you can also migrate hosted
--     zones that have overlapping name servers to hosted zones that don\'t
--     have overlapping name servers, then migrate the hosted zones again
--     to use the reusable delegation set.
module Amazonka.Route53.CreateReusableDelegationSet
  ( -- * Creating a Request
    CreateReusableDelegationSet (..),
    newCreateReusableDelegationSet,

    -- * Request Lenses
    createReusableDelegationSet_hostedZoneId,
    createReusableDelegationSet_callerReference,

    -- * Destructuring the Response
    CreateReusableDelegationSetResponse (..),
    newCreateReusableDelegationSetResponse,

    -- * Response Lenses
    createReusableDelegationSetResponse_httpStatus,
    createReusableDelegationSetResponse_delegationSet,
    createReusableDelegationSetResponse_location,
  )
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

-- | /See:/ 'newCreateReusableDelegationSet' smart constructor.
data CreateReusableDelegationSet = CreateReusableDelegationSet'
  { -- | If you want to mark the delegation set for an existing hosted zone as
    -- reusable, the ID for that hosted zone.
    CreateReusableDelegationSet -> Maybe ResourceId
hostedZoneId :: Prelude.Maybe ResourceId,
    -- | A unique string that identifies the request, and that allows you to
    -- retry failed @CreateReusableDelegationSet@ requests without the risk of
    -- executing the operation twice. You must use a unique @CallerReference@
    -- string every time you submit a @CreateReusableDelegationSet@ request.
    -- @CallerReference@ can be any unique string, for example a date\/time
    -- stamp.
    CreateReusableDelegationSet -> Text
callerReference :: Prelude.Text
  }
  deriving (CreateReusableDelegationSet -> CreateReusableDelegationSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateReusableDelegationSet -> CreateReusableDelegationSet -> Bool
$c/= :: CreateReusableDelegationSet -> CreateReusableDelegationSet -> Bool
== :: CreateReusableDelegationSet -> CreateReusableDelegationSet -> Bool
$c== :: CreateReusableDelegationSet -> CreateReusableDelegationSet -> Bool
Prelude.Eq, ReadPrec [CreateReusableDelegationSet]
ReadPrec CreateReusableDelegationSet
Int -> ReadS CreateReusableDelegationSet
ReadS [CreateReusableDelegationSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateReusableDelegationSet]
$creadListPrec :: ReadPrec [CreateReusableDelegationSet]
readPrec :: ReadPrec CreateReusableDelegationSet
$creadPrec :: ReadPrec CreateReusableDelegationSet
readList :: ReadS [CreateReusableDelegationSet]
$creadList :: ReadS [CreateReusableDelegationSet]
readsPrec :: Int -> ReadS CreateReusableDelegationSet
$creadsPrec :: Int -> ReadS CreateReusableDelegationSet
Prelude.Read, Int -> CreateReusableDelegationSet -> ShowS
[CreateReusableDelegationSet] -> ShowS
CreateReusableDelegationSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateReusableDelegationSet] -> ShowS
$cshowList :: [CreateReusableDelegationSet] -> ShowS
show :: CreateReusableDelegationSet -> String
$cshow :: CreateReusableDelegationSet -> String
showsPrec :: Int -> CreateReusableDelegationSet -> ShowS
$cshowsPrec :: Int -> CreateReusableDelegationSet -> ShowS
Prelude.Show, forall x.
Rep CreateReusableDelegationSet x -> CreateReusableDelegationSet
forall x.
CreateReusableDelegationSet -> Rep CreateReusableDelegationSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateReusableDelegationSet x -> CreateReusableDelegationSet
$cfrom :: forall x.
CreateReusableDelegationSet -> Rep CreateReusableDelegationSet x
Prelude.Generic)

-- |
-- Create a value of 'CreateReusableDelegationSet' 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:
--
-- 'hostedZoneId', 'createReusableDelegationSet_hostedZoneId' - If you want to mark the delegation set for an existing hosted zone as
-- reusable, the ID for that hosted zone.
--
-- 'callerReference', 'createReusableDelegationSet_callerReference' - A unique string that identifies the request, and that allows you to
-- retry failed @CreateReusableDelegationSet@ requests without the risk of
-- executing the operation twice. You must use a unique @CallerReference@
-- string every time you submit a @CreateReusableDelegationSet@ request.
-- @CallerReference@ can be any unique string, for example a date\/time
-- stamp.
newCreateReusableDelegationSet ::
  -- | 'callerReference'
  Prelude.Text ->
  CreateReusableDelegationSet
newCreateReusableDelegationSet :: Text -> CreateReusableDelegationSet
newCreateReusableDelegationSet Text
pCallerReference_ =
  CreateReusableDelegationSet'
    { $sel:hostedZoneId:CreateReusableDelegationSet' :: Maybe ResourceId
hostedZoneId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:callerReference:CreateReusableDelegationSet' :: Text
callerReference = Text
pCallerReference_
    }

-- | If you want to mark the delegation set for an existing hosted zone as
-- reusable, the ID for that hosted zone.
createReusableDelegationSet_hostedZoneId :: Lens.Lens' CreateReusableDelegationSet (Prelude.Maybe ResourceId)
createReusableDelegationSet_hostedZoneId :: Lens' CreateReusableDelegationSet (Maybe ResourceId)
createReusableDelegationSet_hostedZoneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReusableDelegationSet' {Maybe ResourceId
hostedZoneId :: Maybe ResourceId
$sel:hostedZoneId:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Maybe ResourceId
hostedZoneId} -> Maybe ResourceId
hostedZoneId) (\s :: CreateReusableDelegationSet
s@CreateReusableDelegationSet' {} Maybe ResourceId
a -> CreateReusableDelegationSet
s {$sel:hostedZoneId:CreateReusableDelegationSet' :: Maybe ResourceId
hostedZoneId = Maybe ResourceId
a} :: CreateReusableDelegationSet)

-- | A unique string that identifies the request, and that allows you to
-- retry failed @CreateReusableDelegationSet@ requests without the risk of
-- executing the operation twice. You must use a unique @CallerReference@
-- string every time you submit a @CreateReusableDelegationSet@ request.
-- @CallerReference@ can be any unique string, for example a date\/time
-- stamp.
createReusableDelegationSet_callerReference :: Lens.Lens' CreateReusableDelegationSet Prelude.Text
createReusableDelegationSet_callerReference :: Lens' CreateReusableDelegationSet Text
createReusableDelegationSet_callerReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReusableDelegationSet' {Text
callerReference :: Text
$sel:callerReference:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Text
callerReference} -> Text
callerReference) (\s :: CreateReusableDelegationSet
s@CreateReusableDelegationSet' {} Text
a -> CreateReusableDelegationSet
s {$sel:callerReference:CreateReusableDelegationSet' :: Text
callerReference = Text
a} :: CreateReusableDelegationSet)

instance Core.AWSRequest CreateReusableDelegationSet where
  type
    AWSResponse CreateReusableDelegationSet =
      CreateReusableDelegationSetResponse
  request :: (Service -> Service)
-> CreateReusableDelegationSet
-> Request CreateReusableDelegationSet
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateReusableDelegationSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateReusableDelegationSet)))
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 -> Text -> CreateReusableDelegationSetResponse
CreateReusableDelegationSetResponse'
            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")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String a
Data..# HeaderName
"Location")
      )

instance Prelude.Hashable CreateReusableDelegationSet where
  hashWithSalt :: Int -> CreateReusableDelegationSet -> Int
hashWithSalt Int
_salt CreateReusableDelegationSet' {Maybe ResourceId
Text
callerReference :: Text
hostedZoneId :: Maybe ResourceId
$sel:callerReference:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Text
$sel:hostedZoneId:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Maybe ResourceId
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceId
hostedZoneId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
callerReference

instance Prelude.NFData CreateReusableDelegationSet where
  rnf :: CreateReusableDelegationSet -> ()
rnf CreateReusableDelegationSet' {Maybe ResourceId
Text
callerReference :: Text
hostedZoneId :: Maybe ResourceId
$sel:callerReference:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Text
$sel:hostedZoneId:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Maybe ResourceId
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceId
hostedZoneId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
callerReference

instance Data.ToElement CreateReusableDelegationSet where
  toElement :: CreateReusableDelegationSet -> Element
toElement =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{https://route53.amazonaws.com/doc/2013-04-01/}CreateReusableDelegationSetRequest"

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

instance Data.ToPath CreateReusableDelegationSet where
  toPath :: CreateReusableDelegationSet -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2013-04-01/delegationset"

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

instance Data.ToXML CreateReusableDelegationSet where
  toXML :: CreateReusableDelegationSet -> XML
toXML CreateReusableDelegationSet' {Maybe ResourceId
Text
callerReference :: Text
hostedZoneId :: Maybe ResourceId
$sel:callerReference:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Text
$sel:hostedZoneId:CreateReusableDelegationSet' :: CreateReusableDelegationSet -> Maybe ResourceId
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"HostedZoneId" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe ResourceId
hostedZoneId,
        Name
"CallerReference" forall a. ToXML a => Name -> a -> XML
Data.@= Text
callerReference
      ]

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

-- |
-- Create a value of 'CreateReusableDelegationSetResponse' 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', 'createReusableDelegationSetResponse_httpStatus' - The response's http status code.
--
-- 'delegationSet', 'createReusableDelegationSetResponse_delegationSet' - A complex type that contains name server information.
--
-- 'location', 'createReusableDelegationSetResponse_location' - The unique URL representing the new reusable delegation set.
newCreateReusableDelegationSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'delegationSet'
  DelegationSet ->
  -- | 'location'
  Prelude.Text ->
  CreateReusableDelegationSetResponse
newCreateReusableDelegationSetResponse :: Int -> DelegationSet -> Text -> CreateReusableDelegationSetResponse
newCreateReusableDelegationSetResponse
  Int
pHttpStatus_
  DelegationSet
pDelegationSet_
  Text
pLocation_ =
    CreateReusableDelegationSetResponse'
      { $sel:httpStatus:CreateReusableDelegationSetResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:delegationSet:CreateReusableDelegationSetResponse' :: DelegationSet
delegationSet = DelegationSet
pDelegationSet_,
        $sel:location:CreateReusableDelegationSetResponse' :: Text
location = Text
pLocation_
      }

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

-- | A complex type that contains name server information.
createReusableDelegationSetResponse_delegationSet :: Lens.Lens' CreateReusableDelegationSetResponse DelegationSet
createReusableDelegationSetResponse_delegationSet :: Lens' CreateReusableDelegationSetResponse DelegationSet
createReusableDelegationSetResponse_delegationSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReusableDelegationSetResponse' {DelegationSet
delegationSet :: DelegationSet
$sel:delegationSet:CreateReusableDelegationSetResponse' :: CreateReusableDelegationSetResponse -> DelegationSet
delegationSet} -> DelegationSet
delegationSet) (\s :: CreateReusableDelegationSetResponse
s@CreateReusableDelegationSetResponse' {} DelegationSet
a -> CreateReusableDelegationSetResponse
s {$sel:delegationSet:CreateReusableDelegationSetResponse' :: DelegationSet
delegationSet = DelegationSet
a} :: CreateReusableDelegationSetResponse)

-- | The unique URL representing the new reusable delegation set.
createReusableDelegationSetResponse_location :: Lens.Lens' CreateReusableDelegationSetResponse Prelude.Text
createReusableDelegationSetResponse_location :: Lens' CreateReusableDelegationSetResponse Text
createReusableDelegationSetResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReusableDelegationSetResponse' {Text
location :: Text
$sel:location:CreateReusableDelegationSetResponse' :: CreateReusableDelegationSetResponse -> Text
location} -> Text
location) (\s :: CreateReusableDelegationSetResponse
s@CreateReusableDelegationSetResponse' {} Text
a -> CreateReusableDelegationSetResponse
s {$sel:location:CreateReusableDelegationSetResponse' :: Text
location = Text
a} :: CreateReusableDelegationSetResponse)

instance
  Prelude.NFData
    CreateReusableDelegationSetResponse
  where
  rnf :: CreateReusableDelegationSetResponse -> ()
rnf CreateReusableDelegationSetResponse' {Int
Text
DelegationSet
location :: Text
delegationSet :: DelegationSet
httpStatus :: Int
$sel:location:CreateReusableDelegationSetResponse' :: CreateReusableDelegationSetResponse -> Text
$sel:delegationSet:CreateReusableDelegationSetResponse' :: CreateReusableDelegationSetResponse -> DelegationSet
$sel:httpStatus:CreateReusableDelegationSetResponse' :: CreateReusableDelegationSetResponse -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
location