{-# 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.CloudFront.UpdateCachePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a cache policy configuration.
--
-- When you update a cache policy configuration, all the fields are updated
-- with the values provided in the request. You cannot update some fields
-- independent of others. To update a cache policy configuration:
--
-- 1.  Use @GetCachePolicyConfig@ to get the current configuration.
--
-- 2.  Locally modify the fields in the cache policy configuration that you
--     want to update.
--
-- 3.  Call @UpdateCachePolicy@ by providing the entire cache policy
--     configuration, including the fields that you modified and those that
--     you didn\'t.
module Amazonka.CloudFront.UpdateCachePolicy
  ( -- * Creating a Request
    UpdateCachePolicy (..),
    newUpdateCachePolicy,

    -- * Request Lenses
    updateCachePolicy_ifMatch,
    updateCachePolicy_cachePolicyConfig,
    updateCachePolicy_id,

    -- * Destructuring the Response
    UpdateCachePolicyResponse (..),
    newUpdateCachePolicyResponse,

    -- * Response Lenses
    updateCachePolicyResponse_cachePolicy,
    updateCachePolicyResponse_eTag,
    updateCachePolicyResponse_httpStatus,
  )
where

import Amazonka.CloudFront.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:/ 'newUpdateCachePolicy' smart constructor.
data UpdateCachePolicy = UpdateCachePolicy'
  { -- | The version of the cache policy that you are updating. The version is
    -- returned in the cache policy\'s @ETag@ field in the response to
    -- @GetCachePolicyConfig@.
    UpdateCachePolicy -> Maybe Text
ifMatch :: Prelude.Maybe Prelude.Text,
    -- | A cache policy configuration.
    UpdateCachePolicy -> CachePolicyConfig
cachePolicyConfig :: CachePolicyConfig,
    -- | The unique identifier for the cache policy that you are updating. The
    -- identifier is returned in a cache behavior\'s @CachePolicyId@ field in
    -- the response to @GetDistributionConfig@.
    UpdateCachePolicy -> Text
id :: Prelude.Text
  }
  deriving (UpdateCachePolicy -> UpdateCachePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCachePolicy -> UpdateCachePolicy -> Bool
$c/= :: UpdateCachePolicy -> UpdateCachePolicy -> Bool
== :: UpdateCachePolicy -> UpdateCachePolicy -> Bool
$c== :: UpdateCachePolicy -> UpdateCachePolicy -> Bool
Prelude.Eq, ReadPrec [UpdateCachePolicy]
ReadPrec UpdateCachePolicy
Int -> ReadS UpdateCachePolicy
ReadS [UpdateCachePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCachePolicy]
$creadListPrec :: ReadPrec [UpdateCachePolicy]
readPrec :: ReadPrec UpdateCachePolicy
$creadPrec :: ReadPrec UpdateCachePolicy
readList :: ReadS [UpdateCachePolicy]
$creadList :: ReadS [UpdateCachePolicy]
readsPrec :: Int -> ReadS UpdateCachePolicy
$creadsPrec :: Int -> ReadS UpdateCachePolicy
Prelude.Read, Int -> UpdateCachePolicy -> ShowS
[UpdateCachePolicy] -> ShowS
UpdateCachePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCachePolicy] -> ShowS
$cshowList :: [UpdateCachePolicy] -> ShowS
show :: UpdateCachePolicy -> String
$cshow :: UpdateCachePolicy -> String
showsPrec :: Int -> UpdateCachePolicy -> ShowS
$cshowsPrec :: Int -> UpdateCachePolicy -> ShowS
Prelude.Show, forall x. Rep UpdateCachePolicy x -> UpdateCachePolicy
forall x. UpdateCachePolicy -> Rep UpdateCachePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateCachePolicy x -> UpdateCachePolicy
$cfrom :: forall x. UpdateCachePolicy -> Rep UpdateCachePolicy x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCachePolicy' 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:
--
-- 'ifMatch', 'updateCachePolicy_ifMatch' - The version of the cache policy that you are updating. The version is
-- returned in the cache policy\'s @ETag@ field in the response to
-- @GetCachePolicyConfig@.
--
-- 'cachePolicyConfig', 'updateCachePolicy_cachePolicyConfig' - A cache policy configuration.
--
-- 'id', 'updateCachePolicy_id' - The unique identifier for the cache policy that you are updating. The
-- identifier is returned in a cache behavior\'s @CachePolicyId@ field in
-- the response to @GetDistributionConfig@.
newUpdateCachePolicy ::
  -- | 'cachePolicyConfig'
  CachePolicyConfig ->
  -- | 'id'
  Prelude.Text ->
  UpdateCachePolicy
newUpdateCachePolicy :: CachePolicyConfig -> Text -> UpdateCachePolicy
newUpdateCachePolicy CachePolicyConfig
pCachePolicyConfig_ Text
pId_ =
  UpdateCachePolicy'
    { $sel:ifMatch:UpdateCachePolicy' :: Maybe Text
ifMatch = forall a. Maybe a
Prelude.Nothing,
      $sel:cachePolicyConfig:UpdateCachePolicy' :: CachePolicyConfig
cachePolicyConfig = CachePolicyConfig
pCachePolicyConfig_,
      $sel:id:UpdateCachePolicy' :: Text
id = Text
pId_
    }

-- | The version of the cache policy that you are updating. The version is
-- returned in the cache policy\'s @ETag@ field in the response to
-- @GetCachePolicyConfig@.
updateCachePolicy_ifMatch :: Lens.Lens' UpdateCachePolicy (Prelude.Maybe Prelude.Text)
updateCachePolicy_ifMatch :: Lens' UpdateCachePolicy (Maybe Text)
updateCachePolicy_ifMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCachePolicy' {Maybe Text
ifMatch :: Maybe Text
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
ifMatch} -> Maybe Text
ifMatch) (\s :: UpdateCachePolicy
s@UpdateCachePolicy' {} Maybe Text
a -> UpdateCachePolicy
s {$sel:ifMatch:UpdateCachePolicy' :: Maybe Text
ifMatch = Maybe Text
a} :: UpdateCachePolicy)

-- | A cache policy configuration.
updateCachePolicy_cachePolicyConfig :: Lens.Lens' UpdateCachePolicy CachePolicyConfig
updateCachePolicy_cachePolicyConfig :: Lens' UpdateCachePolicy CachePolicyConfig
updateCachePolicy_cachePolicyConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCachePolicy' {CachePolicyConfig
cachePolicyConfig :: CachePolicyConfig
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
cachePolicyConfig} -> CachePolicyConfig
cachePolicyConfig) (\s :: UpdateCachePolicy
s@UpdateCachePolicy' {} CachePolicyConfig
a -> UpdateCachePolicy
s {$sel:cachePolicyConfig:UpdateCachePolicy' :: CachePolicyConfig
cachePolicyConfig = CachePolicyConfig
a} :: UpdateCachePolicy)

-- | The unique identifier for the cache policy that you are updating. The
-- identifier is returned in a cache behavior\'s @CachePolicyId@ field in
-- the response to @GetDistributionConfig@.
updateCachePolicy_id :: Lens.Lens' UpdateCachePolicy Prelude.Text
updateCachePolicy_id :: Lens' UpdateCachePolicy Text
updateCachePolicy_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCachePolicy' {Text
id :: Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
id} -> Text
id) (\s :: UpdateCachePolicy
s@UpdateCachePolicy' {} Text
a -> UpdateCachePolicy
s {$sel:id:UpdateCachePolicy' :: Text
id = Text
a} :: UpdateCachePolicy)

instance Core.AWSRequest UpdateCachePolicy where
  type
    AWSResponse UpdateCachePolicy =
      UpdateCachePolicyResponse
  request :: (Service -> Service)
-> UpdateCachePolicy -> Request UpdateCachePolicy
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.putXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateCachePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateCachePolicy)))
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 ->
          Maybe CachePolicy -> Maybe Text -> Int -> UpdateCachePolicyResponse
UpdateCachePolicyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
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
"ETag")
            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 UpdateCachePolicy where
  hashWithSalt :: Int -> UpdateCachePolicy -> Int
hashWithSalt Int
_salt UpdateCachePolicy' {Maybe Text
Text
CachePolicyConfig
id :: Text
cachePolicyConfig :: CachePolicyConfig
ifMatch :: Maybe Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ifMatch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CachePolicyConfig
cachePolicyConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateCachePolicy where
  rnf :: UpdateCachePolicy -> ()
rnf UpdateCachePolicy' {Maybe Text
Text
CachePolicyConfig
id :: Text
cachePolicyConfig :: CachePolicyConfig
ifMatch :: Maybe Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ifMatch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CachePolicyConfig
cachePolicyConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToElement UpdateCachePolicy where
  toElement :: UpdateCachePolicy -> Element
toElement UpdateCachePolicy' {Maybe Text
Text
CachePolicyConfig
id :: Text
cachePolicyConfig :: CachePolicyConfig
ifMatch :: Maybe Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}CachePolicyConfig"
      CachePolicyConfig
cachePolicyConfig

instance Data.ToHeaders UpdateCachePolicy where
  toHeaders :: UpdateCachePolicy -> ResponseHeaders
toHeaders UpdateCachePolicy' {Maybe Text
Text
CachePolicyConfig
id :: Text
cachePolicyConfig :: CachePolicyConfig
ifMatch :: Maybe Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [HeaderName
"If-Match" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
ifMatch]

instance Data.ToPath UpdateCachePolicy where
  toPath :: UpdateCachePolicy -> ByteString
toPath UpdateCachePolicy' {Maybe Text
Text
CachePolicyConfig
id :: Text
cachePolicyConfig :: CachePolicyConfig
ifMatch :: Maybe Text
$sel:id:UpdateCachePolicy' :: UpdateCachePolicy -> Text
$sel:cachePolicyConfig:UpdateCachePolicy' :: UpdateCachePolicy -> CachePolicyConfig
$sel:ifMatch:UpdateCachePolicy' :: UpdateCachePolicy -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2020-05-31/cache-policy/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | /See:/ 'newUpdateCachePolicyResponse' smart constructor.
data UpdateCachePolicyResponse = UpdateCachePolicyResponse'
  { -- | A cache policy.
    UpdateCachePolicyResponse -> Maybe CachePolicy
cachePolicy :: Prelude.Maybe CachePolicy,
    -- | The current version of the cache policy.
    UpdateCachePolicyResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateCachePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateCachePolicyResponse -> UpdateCachePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCachePolicyResponse -> UpdateCachePolicyResponse -> Bool
$c/= :: UpdateCachePolicyResponse -> UpdateCachePolicyResponse -> Bool
== :: UpdateCachePolicyResponse -> UpdateCachePolicyResponse -> Bool
$c== :: UpdateCachePolicyResponse -> UpdateCachePolicyResponse -> Bool
Prelude.Eq, ReadPrec [UpdateCachePolicyResponse]
ReadPrec UpdateCachePolicyResponse
Int -> ReadS UpdateCachePolicyResponse
ReadS [UpdateCachePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCachePolicyResponse]
$creadListPrec :: ReadPrec [UpdateCachePolicyResponse]
readPrec :: ReadPrec UpdateCachePolicyResponse
$creadPrec :: ReadPrec UpdateCachePolicyResponse
readList :: ReadS [UpdateCachePolicyResponse]
$creadList :: ReadS [UpdateCachePolicyResponse]
readsPrec :: Int -> ReadS UpdateCachePolicyResponse
$creadsPrec :: Int -> ReadS UpdateCachePolicyResponse
Prelude.Read, Int -> UpdateCachePolicyResponse -> ShowS
[UpdateCachePolicyResponse] -> ShowS
UpdateCachePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCachePolicyResponse] -> ShowS
$cshowList :: [UpdateCachePolicyResponse] -> ShowS
show :: UpdateCachePolicyResponse -> String
$cshow :: UpdateCachePolicyResponse -> String
showsPrec :: Int -> UpdateCachePolicyResponse -> ShowS
$cshowsPrec :: Int -> UpdateCachePolicyResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateCachePolicyResponse x -> UpdateCachePolicyResponse
forall x.
UpdateCachePolicyResponse -> Rep UpdateCachePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCachePolicyResponse x -> UpdateCachePolicyResponse
$cfrom :: forall x.
UpdateCachePolicyResponse -> Rep UpdateCachePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCachePolicyResponse' 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:
--
-- 'cachePolicy', 'updateCachePolicyResponse_cachePolicy' - A cache policy.
--
-- 'eTag', 'updateCachePolicyResponse_eTag' - The current version of the cache policy.
--
-- 'httpStatus', 'updateCachePolicyResponse_httpStatus' - The response's http status code.
newUpdateCachePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateCachePolicyResponse
newUpdateCachePolicyResponse :: Int -> UpdateCachePolicyResponse
newUpdateCachePolicyResponse Int
pHttpStatus_ =
  UpdateCachePolicyResponse'
    { $sel:cachePolicy:UpdateCachePolicyResponse' :: Maybe CachePolicy
cachePolicy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:eTag:UpdateCachePolicyResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateCachePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A cache policy.
updateCachePolicyResponse_cachePolicy :: Lens.Lens' UpdateCachePolicyResponse (Prelude.Maybe CachePolicy)
updateCachePolicyResponse_cachePolicy :: Lens' UpdateCachePolicyResponse (Maybe CachePolicy)
updateCachePolicyResponse_cachePolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCachePolicyResponse' {Maybe CachePolicy
cachePolicy :: Maybe CachePolicy
$sel:cachePolicy:UpdateCachePolicyResponse' :: UpdateCachePolicyResponse -> Maybe CachePolicy
cachePolicy} -> Maybe CachePolicy
cachePolicy) (\s :: UpdateCachePolicyResponse
s@UpdateCachePolicyResponse' {} Maybe CachePolicy
a -> UpdateCachePolicyResponse
s {$sel:cachePolicy:UpdateCachePolicyResponse' :: Maybe CachePolicy
cachePolicy = Maybe CachePolicy
a} :: UpdateCachePolicyResponse)

-- | The current version of the cache policy.
updateCachePolicyResponse_eTag :: Lens.Lens' UpdateCachePolicyResponse (Prelude.Maybe Prelude.Text)
updateCachePolicyResponse_eTag :: Lens' UpdateCachePolicyResponse (Maybe Text)
updateCachePolicyResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCachePolicyResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:UpdateCachePolicyResponse' :: UpdateCachePolicyResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: UpdateCachePolicyResponse
s@UpdateCachePolicyResponse' {} Maybe Text
a -> UpdateCachePolicyResponse
s {$sel:eTag:UpdateCachePolicyResponse' :: Maybe Text
eTag = Maybe Text
a} :: UpdateCachePolicyResponse)

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

instance Prelude.NFData UpdateCachePolicyResponse where
  rnf :: UpdateCachePolicyResponse -> ()
rnf UpdateCachePolicyResponse' {Int
Maybe Text
Maybe CachePolicy
httpStatus :: Int
eTag :: Maybe Text
cachePolicy :: Maybe CachePolicy
$sel:httpStatus:UpdateCachePolicyResponse' :: UpdateCachePolicyResponse -> Int
$sel:eTag:UpdateCachePolicyResponse' :: UpdateCachePolicyResponse -> Maybe Text
$sel:cachePolicy:UpdateCachePolicyResponse' :: UpdateCachePolicyResponse -> Maybe CachePolicy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CachePolicy
cachePolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus