{-# 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.AppConfigData.GetLatestConfiguration
-- 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 the latest deployed configuration. This API may return empty
-- configuration data if the client already has the latest version. For
-- more information about this API action and to view example CLI commands
-- that show how to use it with the StartConfigurationSession API action,
-- see
-- <http://docs.aws.amazon.com/appconfig/latest/userguide/appconfig-retrieving-the-configuration Receiving the configuration>
-- in the /AppConfig User Guide/.
--
-- Note the following important information.
--
-- -   Each configuration token is only valid for one call to
--     @GetLatestConfiguration@. The @GetLatestConfiguration@ response
--     includes a @NextPollConfigurationToken@ that should always replace
--     the token used for the just-completed call in preparation for the
--     next one.
--
-- -   @GetLatestConfiguration@ is a priced call. For more information, see
--     <https://aws.amazon.com/systems-manager/pricing/ Pricing>.
module Amazonka.AppConfigData.GetLatestConfiguration
  ( -- * Creating a Request
    GetLatestConfiguration (..),
    newGetLatestConfiguration,

    -- * Request Lenses
    getLatestConfiguration_configurationToken,

    -- * Destructuring the Response
    GetLatestConfigurationResponse (..),
    newGetLatestConfigurationResponse,

    -- * Response Lenses
    getLatestConfigurationResponse_configuration,
    getLatestConfigurationResponse_contentType,
    getLatestConfigurationResponse_nextPollConfigurationToken,
    getLatestConfigurationResponse_nextPollIntervalInSeconds,
    getLatestConfigurationResponse_httpStatus,
  )
where

import Amazonka.AppConfigData.Types
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

-- | /See:/ 'newGetLatestConfiguration' smart constructor.
data GetLatestConfiguration = GetLatestConfiguration'
  { -- | Token describing the current state of the configuration session. To
    -- obtain a token, first call the StartConfigurationSession API. Note that
    -- every call to @GetLatestConfiguration@ will return a new
    -- @ConfigurationToken@ (@NextPollConfigurationToken@ in the response) and
    -- MUST be provided to subsequent @GetLatestConfiguration@ API calls.
    GetLatestConfiguration -> Text
configurationToken :: Prelude.Text
  }
  deriving (GetLatestConfiguration -> GetLatestConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLatestConfiguration -> GetLatestConfiguration -> Bool
$c/= :: GetLatestConfiguration -> GetLatestConfiguration -> Bool
== :: GetLatestConfiguration -> GetLatestConfiguration -> Bool
$c== :: GetLatestConfiguration -> GetLatestConfiguration -> Bool
Prelude.Eq, ReadPrec [GetLatestConfiguration]
ReadPrec GetLatestConfiguration
Int -> ReadS GetLatestConfiguration
ReadS [GetLatestConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLatestConfiguration]
$creadListPrec :: ReadPrec [GetLatestConfiguration]
readPrec :: ReadPrec GetLatestConfiguration
$creadPrec :: ReadPrec GetLatestConfiguration
readList :: ReadS [GetLatestConfiguration]
$creadList :: ReadS [GetLatestConfiguration]
readsPrec :: Int -> ReadS GetLatestConfiguration
$creadsPrec :: Int -> ReadS GetLatestConfiguration
Prelude.Read, Int -> GetLatestConfiguration -> ShowS
[GetLatestConfiguration] -> ShowS
GetLatestConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLatestConfiguration] -> ShowS
$cshowList :: [GetLatestConfiguration] -> ShowS
show :: GetLatestConfiguration -> String
$cshow :: GetLatestConfiguration -> String
showsPrec :: Int -> GetLatestConfiguration -> ShowS
$cshowsPrec :: Int -> GetLatestConfiguration -> ShowS
Prelude.Show, forall x. Rep GetLatestConfiguration x -> GetLatestConfiguration
forall x. GetLatestConfiguration -> Rep GetLatestConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLatestConfiguration x -> GetLatestConfiguration
$cfrom :: forall x. GetLatestConfiguration -> Rep GetLatestConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetLatestConfiguration' 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:
--
-- 'configurationToken', 'getLatestConfiguration_configurationToken' - Token describing the current state of the configuration session. To
-- obtain a token, first call the StartConfigurationSession API. Note that
-- every call to @GetLatestConfiguration@ will return a new
-- @ConfigurationToken@ (@NextPollConfigurationToken@ in the response) and
-- MUST be provided to subsequent @GetLatestConfiguration@ API calls.
newGetLatestConfiguration ::
  -- | 'configurationToken'
  Prelude.Text ->
  GetLatestConfiguration
newGetLatestConfiguration :: Text -> GetLatestConfiguration
newGetLatestConfiguration Text
pConfigurationToken_ =
  GetLatestConfiguration'
    { $sel:configurationToken:GetLatestConfiguration' :: Text
configurationToken =
        Text
pConfigurationToken_
    }

-- | Token describing the current state of the configuration session. To
-- obtain a token, first call the StartConfigurationSession API. Note that
-- every call to @GetLatestConfiguration@ will return a new
-- @ConfigurationToken@ (@NextPollConfigurationToken@ in the response) and
-- MUST be provided to subsequent @GetLatestConfiguration@ API calls.
getLatestConfiguration_configurationToken :: Lens.Lens' GetLatestConfiguration Prelude.Text
getLatestConfiguration_configurationToken :: Lens' GetLatestConfiguration Text
getLatestConfiguration_configurationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLatestConfiguration' {Text
configurationToken :: Text
$sel:configurationToken:GetLatestConfiguration' :: GetLatestConfiguration -> Text
configurationToken} -> Text
configurationToken) (\s :: GetLatestConfiguration
s@GetLatestConfiguration' {} Text
a -> GetLatestConfiguration
s {$sel:configurationToken:GetLatestConfiguration' :: Text
configurationToken = Text
a} :: GetLatestConfiguration)

instance Core.AWSRequest GetLatestConfiguration where
  type
    AWSResponse GetLatestConfiguration =
      GetLatestConfigurationResponse
  request :: (Service -> Service)
-> GetLatestConfiguration -> Request GetLatestConfiguration
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 GetLatestConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetLatestConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders -> ByteString -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBytes
      ( \Int
s ResponseHeaders
h ByteString
x ->
          Maybe (Sensitive ByteString)
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Int
-> GetLatestConfigurationResponse
GetLatestConfigurationResponse'
            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. a -> Maybe a
Prelude.Just (coerce :: forall a b. Coercible a b => a -> b
Prelude.coerce ByteString
x)))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Content-Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Next-Poll-Configuration-Token")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Next-Poll-Interval-In-Seconds")
            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 GetLatestConfiguration where
  hashWithSalt :: Int -> GetLatestConfiguration -> Int
hashWithSalt Int
_salt GetLatestConfiguration' {Text
configurationToken :: Text
$sel:configurationToken:GetLatestConfiguration' :: GetLatestConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationToken

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

instance Data.ToHeaders GetLatestConfiguration where
  toHeaders :: GetLatestConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetLatestConfiguration where
  toPath :: GetLatestConfiguration -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/configuration"

instance Data.ToQuery GetLatestConfiguration where
  toQuery :: GetLatestConfiguration -> QueryString
toQuery GetLatestConfiguration' {Text
configurationToken :: Text
$sel:configurationToken:GetLatestConfiguration' :: GetLatestConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"configuration_token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
configurationToken]

-- | /See:/ 'newGetLatestConfigurationResponse' smart constructor.
data GetLatestConfigurationResponse = GetLatestConfigurationResponse'
  { -- | The data of the configuration. This may be empty if the client already
    -- has the latest version of configuration.
    GetLatestConfigurationResponse -> Maybe (Sensitive ByteString)
configuration :: Prelude.Maybe (Data.Sensitive Prelude.ByteString),
    -- | A standard MIME type describing the format of the configuration content.
    GetLatestConfigurationResponse -> Maybe Text
contentType :: Prelude.Maybe Prelude.Text,
    -- | The latest token describing the current state of the configuration
    -- session. This MUST be provided to the next call to
    -- @GetLatestConfiguration.@
    GetLatestConfigurationResponse -> Maybe Text
nextPollConfigurationToken :: Prelude.Maybe Prelude.Text,
    -- | The amount of time the client should wait before polling for
    -- configuration updates again. Use @RequiredMinimumPollIntervalInSeconds@
    -- to set the desired poll interval.
    GetLatestConfigurationResponse -> Maybe Int
nextPollIntervalInSeconds :: Prelude.Maybe Prelude.Int,
    -- | The response's http status code.
    GetLatestConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetLatestConfigurationResponse
-> GetLatestConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLatestConfigurationResponse
-> GetLatestConfigurationResponse -> Bool
$c/= :: GetLatestConfigurationResponse
-> GetLatestConfigurationResponse -> Bool
== :: GetLatestConfigurationResponse
-> GetLatestConfigurationResponse -> Bool
$c== :: GetLatestConfigurationResponse
-> GetLatestConfigurationResponse -> Bool
Prelude.Eq, Int -> GetLatestConfigurationResponse -> ShowS
[GetLatestConfigurationResponse] -> ShowS
GetLatestConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLatestConfigurationResponse] -> ShowS
$cshowList :: [GetLatestConfigurationResponse] -> ShowS
show :: GetLatestConfigurationResponse -> String
$cshow :: GetLatestConfigurationResponse -> String
showsPrec :: Int -> GetLatestConfigurationResponse -> ShowS
$cshowsPrec :: Int -> GetLatestConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep GetLatestConfigurationResponse x
-> GetLatestConfigurationResponse
forall x.
GetLatestConfigurationResponse
-> Rep GetLatestConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetLatestConfigurationResponse x
-> GetLatestConfigurationResponse
$cfrom :: forall x.
GetLatestConfigurationResponse
-> Rep GetLatestConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetLatestConfigurationResponse' 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:
--
-- 'configuration', 'getLatestConfigurationResponse_configuration' - The data of the configuration. This may be empty if the client already
-- has the latest version of configuration.
--
-- 'contentType', 'getLatestConfigurationResponse_contentType' - A standard MIME type describing the format of the configuration content.
--
-- 'nextPollConfigurationToken', 'getLatestConfigurationResponse_nextPollConfigurationToken' - The latest token describing the current state of the configuration
-- session. This MUST be provided to the next call to
-- @GetLatestConfiguration.@
--
-- 'nextPollIntervalInSeconds', 'getLatestConfigurationResponse_nextPollIntervalInSeconds' - The amount of time the client should wait before polling for
-- configuration updates again. Use @RequiredMinimumPollIntervalInSeconds@
-- to set the desired poll interval.
--
-- 'httpStatus', 'getLatestConfigurationResponse_httpStatus' - The response's http status code.
newGetLatestConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetLatestConfigurationResponse
newGetLatestConfigurationResponse :: Int -> GetLatestConfigurationResponse
newGetLatestConfigurationResponse Int
pHttpStatus_ =
  GetLatestConfigurationResponse'
    { $sel:configuration:GetLatestConfigurationResponse' :: Maybe (Sensitive ByteString)
configuration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contentType:GetLatestConfigurationResponse' :: Maybe Text
contentType = forall a. Maybe a
Prelude.Nothing,
      $sel:nextPollConfigurationToken:GetLatestConfigurationResponse' :: Maybe Text
nextPollConfigurationToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextPollIntervalInSeconds:GetLatestConfigurationResponse' :: Maybe Int
nextPollIntervalInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetLatestConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The data of the configuration. This may be empty if the client already
-- has the latest version of configuration.
getLatestConfigurationResponse_configuration :: Lens.Lens' GetLatestConfigurationResponse (Prelude.Maybe Prelude.ByteString)
getLatestConfigurationResponse_configuration :: Lens' GetLatestConfigurationResponse (Maybe ByteString)
getLatestConfigurationResponse_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLatestConfigurationResponse' {Maybe (Sensitive ByteString)
configuration :: Maybe (Sensitive ByteString)
$sel:configuration:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe (Sensitive ByteString)
configuration} -> Maybe (Sensitive ByteString)
configuration) (\s :: GetLatestConfigurationResponse
s@GetLatestConfigurationResponse' {} Maybe (Sensitive ByteString)
a -> GetLatestConfigurationResponse
s {$sel:configuration:GetLatestConfigurationResponse' :: Maybe (Sensitive ByteString)
configuration = Maybe (Sensitive ByteString)
a} :: GetLatestConfigurationResponse) 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

-- | A standard MIME type describing the format of the configuration content.
getLatestConfigurationResponse_contentType :: Lens.Lens' GetLatestConfigurationResponse (Prelude.Maybe Prelude.Text)
getLatestConfigurationResponse_contentType :: Lens' GetLatestConfigurationResponse (Maybe Text)
getLatestConfigurationResponse_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLatestConfigurationResponse' {Maybe Text
contentType :: Maybe Text
$sel:contentType:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Text
contentType} -> Maybe Text
contentType) (\s :: GetLatestConfigurationResponse
s@GetLatestConfigurationResponse' {} Maybe Text
a -> GetLatestConfigurationResponse
s {$sel:contentType:GetLatestConfigurationResponse' :: Maybe Text
contentType = Maybe Text
a} :: GetLatestConfigurationResponse)

-- | The latest token describing the current state of the configuration
-- session. This MUST be provided to the next call to
-- @GetLatestConfiguration.@
getLatestConfigurationResponse_nextPollConfigurationToken :: Lens.Lens' GetLatestConfigurationResponse (Prelude.Maybe Prelude.Text)
getLatestConfigurationResponse_nextPollConfigurationToken :: Lens' GetLatestConfigurationResponse (Maybe Text)
getLatestConfigurationResponse_nextPollConfigurationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLatestConfigurationResponse' {Maybe Text
nextPollConfigurationToken :: Maybe Text
$sel:nextPollConfigurationToken:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Text
nextPollConfigurationToken} -> Maybe Text
nextPollConfigurationToken) (\s :: GetLatestConfigurationResponse
s@GetLatestConfigurationResponse' {} Maybe Text
a -> GetLatestConfigurationResponse
s {$sel:nextPollConfigurationToken:GetLatestConfigurationResponse' :: Maybe Text
nextPollConfigurationToken = Maybe Text
a} :: GetLatestConfigurationResponse)

-- | The amount of time the client should wait before polling for
-- configuration updates again. Use @RequiredMinimumPollIntervalInSeconds@
-- to set the desired poll interval.
getLatestConfigurationResponse_nextPollIntervalInSeconds :: Lens.Lens' GetLatestConfigurationResponse (Prelude.Maybe Prelude.Int)
getLatestConfigurationResponse_nextPollIntervalInSeconds :: Lens' GetLatestConfigurationResponse (Maybe Int)
getLatestConfigurationResponse_nextPollIntervalInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLatestConfigurationResponse' {Maybe Int
nextPollIntervalInSeconds :: Maybe Int
$sel:nextPollIntervalInSeconds:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Int
nextPollIntervalInSeconds} -> Maybe Int
nextPollIntervalInSeconds) (\s :: GetLatestConfigurationResponse
s@GetLatestConfigurationResponse' {} Maybe Int
a -> GetLatestConfigurationResponse
s {$sel:nextPollIntervalInSeconds:GetLatestConfigurationResponse' :: Maybe Int
nextPollIntervalInSeconds = Maybe Int
a} :: GetLatestConfigurationResponse)

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

instance
  Prelude.NFData
    GetLatestConfigurationResponse
  where
  rnf :: GetLatestConfigurationResponse -> ()
rnf GetLatestConfigurationResponse' {Int
Maybe Int
Maybe Text
Maybe (Sensitive ByteString)
httpStatus :: Int
nextPollIntervalInSeconds :: Maybe Int
nextPollConfigurationToken :: Maybe Text
contentType :: Maybe Text
configuration :: Maybe (Sensitive ByteString)
$sel:httpStatus:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Int
$sel:nextPollIntervalInSeconds:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Int
$sel:nextPollConfigurationToken:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Text
$sel:contentType:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe Text
$sel:configuration:GetLatestConfigurationResponse' :: GetLatestConfigurationResponse -> Maybe (Sensitive ByteString)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive ByteString)
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPollConfigurationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
nextPollIntervalInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus