{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.DefaultCacheBehavior
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CloudFront.Types.DefaultCacheBehavior where

import Amazonka.CloudFront.Types.AllowedMethods
import Amazonka.CloudFront.Types.ForwardedValues
import Amazonka.CloudFront.Types.FunctionAssociations
import Amazonka.CloudFront.Types.LambdaFunctionAssociations
import Amazonka.CloudFront.Types.TrustedKeyGroups
import Amazonka.CloudFront.Types.TrustedSigners
import Amazonka.CloudFront.Types.ViewerProtocolPolicy
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

-- | A complex type that describes the default cache behavior if you don\'t
-- specify a @CacheBehavior@ element or if request URLs don\'t match any of
-- the values of @PathPattern@ in @CacheBehavior@ elements. You must create
-- exactly one default cache behavior.
--
-- /See:/ 'newDefaultCacheBehavior' smart constructor.
data DefaultCacheBehavior = DefaultCacheBehavior'
  { DefaultCacheBehavior -> Maybe AllowedMethods
allowedMethods :: Prelude.Maybe AllowedMethods,
    -- | The unique identifier of the cache policy that is attached to the
    -- default cache behavior. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
    -- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
    DefaultCacheBehavior -> Maybe Text
cachePolicyId :: Prelude.Maybe Prelude.Text,
    -- | Whether you want CloudFront to automatically compress certain files for
    -- this cache behavior. If so, specify @true@; if not, specify @false@. For
    -- more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/ServingCompressedFiles.html Serving Compressed Files>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe Bool
compress :: Prelude.Maybe Prelude.Bool,
    -- | This field is deprecated. We recommend that you use the @DefaultTTL@
    -- field in a cache policy instead of this field. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- The default amount of time that you want objects to stay in CloudFront
    -- caches before CloudFront forwards another request to your origin to
    -- determine whether the object has been updated. The value that you
    -- specify applies only when your origin does not add HTTP headers such as
    -- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
    -- objects. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe Integer
defaultTTL :: Prelude.Maybe Prelude.Integer,
    -- | The value of @ID@ for the field-level encryption configuration that you
    -- want CloudFront to use for encrypting specific fields of data for the
    -- default cache behavior.
    DefaultCacheBehavior -> Maybe Text
fieldLevelEncryptionId :: Prelude.Maybe Prelude.Text,
    -- | This field is deprecated. We recommend that you use a cache policy or an
    -- origin request policy instead of this field. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/working-with-policies.html Working with policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- If you want to include values in the cache key, use a cache policy. For
    -- more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- If you want to send values to the origin but not include them in the
    -- cache key, use an origin request policy. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
    -- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
    --
    -- A complex type that specifies how CloudFront handles query strings,
    -- cookies, and HTTP headers.
    DefaultCacheBehavior -> Maybe ForwardedValues
forwardedValues :: Prelude.Maybe ForwardedValues,
    -- | A list of CloudFront functions that are associated with this cache
    -- behavior. CloudFront functions must be published to the @LIVE@ stage to
    -- associate them with a cache behavior.
    DefaultCacheBehavior -> Maybe FunctionAssociations
functionAssociations :: Prelude.Maybe FunctionAssociations,
    -- | A complex type that contains zero or more Lambda\@Edge function
    -- associations for a cache behavior.
    DefaultCacheBehavior -> Maybe LambdaFunctionAssociations
lambdaFunctionAssociations :: Prelude.Maybe LambdaFunctionAssociations,
    -- | This field is deprecated. We recommend that you use the @MaxTTL@ field
    -- in a cache policy instead of this field. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- The maximum amount of time that you want objects to stay in CloudFront
    -- caches before CloudFront forwards another request to your origin to
    -- determine whether the object has been updated. The value that you
    -- specify applies only when your origin adds HTTP headers such as
    -- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
    -- objects. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe Integer
maxTTL :: Prelude.Maybe Prelude.Integer,
    -- | This field is deprecated. We recommend that you use the @MinTTL@ field
    -- in a cache policy instead of this field. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- The minimum amount of time that you want objects to stay in CloudFront
    -- caches before CloudFront forwards another request to your origin to
    -- determine whether the object has been updated. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- You must specify @0@ for @MinTTL@ if you configure CloudFront to forward
    -- all headers to your origin (under @Headers@, if you specify @1@ for
    -- @Quantity@ and @*@ for @Name@).
    DefaultCacheBehavior -> Maybe Integer
minTTL :: Prelude.Maybe Prelude.Integer,
    -- | The unique identifier of the origin request policy that is attached to
    -- the default cache behavior. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
    -- or
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe Text
originRequestPolicyId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the real-time log configuration that
    -- is attached to this cache behavior. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html Real-time logs>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe Text
realtimeLogConfigArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier for a response headers policy.
    DefaultCacheBehavior -> Maybe Text
responseHeadersPolicyId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether you want to distribute media files in the Microsoft
    -- Smooth Streaming format using the origin that is associated with this
    -- cache behavior. If so, specify @true@; if not, specify @false@. If you
    -- specify @true@ for @SmoothStreaming@, you can still distribute other
    -- content using this cache behavior if the content matches the value of
    -- @PathPattern@.
    DefaultCacheBehavior -> Maybe Bool
smoothStreaming :: Prelude.Maybe Prelude.Bool,
    -- | A list of key groups that CloudFront can use to validate signed URLs or
    -- signed cookies.
    --
    -- When a cache behavior contains trusted key groups, CloudFront requires
    -- signed URLs or signed cookies for all requests that match the cache
    -- behavior. The URLs or cookies must be signed with a private key whose
    -- corresponding public key is in the key group. The signed URL or cookie
    -- contains information about which public key CloudFront should use to
    -- verify the signature. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe TrustedKeyGroups
trustedKeyGroups :: Prelude.Maybe TrustedKeyGroups,
    -- | We recommend using @TrustedKeyGroups@ instead of @TrustedSigners@.
    --
    -- A list of Amazon Web Services account IDs whose public keys CloudFront
    -- can use to validate signed URLs or signed cookies.
    --
    -- When a cache behavior contains trusted signers, CloudFront requires
    -- signed URLs or signed cookies for all requests that match the cache
    -- behavior. The URLs or cookies must be signed with the private key of a
    -- CloudFront key pair in a trusted signer\'s Amazon Web Services account.
    -- The signed URL or cookie contains information about which public key
    -- CloudFront should use to verify the signature. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> Maybe TrustedSigners
trustedSigners :: Prelude.Maybe TrustedSigners,
    -- | The value of @ID@ for the origin that you want CloudFront to route
    -- requests to when they use the default cache behavior.
    DefaultCacheBehavior -> Text
targetOriginId :: Prelude.Text,
    -- | The protocol that viewers can use to access the files in the origin
    -- specified by @TargetOriginId@ when a request matches the path pattern in
    -- @PathPattern@. You can specify the following options:
    --
    -- -   @allow-all@: Viewers can use HTTP or HTTPS.
    --
    -- -   @redirect-to-https@: If a viewer submits an HTTP request, CloudFront
    --     returns an HTTP status code of 301 (Moved Permanently) to the viewer
    --     along with the HTTPS URL. The viewer then resubmits the request
    --     using the new URL.
    --
    -- -   @https-only@: If a viewer sends an HTTP request, CloudFront returns
    --     an HTTP status code of 403 (Forbidden).
    --
    -- For more information about requiring the HTTPS protocol, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-https-viewers-to-cloudfront.html Requiring HTTPS Between Viewers and CloudFront>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- The only way to guarantee that viewers retrieve an object that was
    -- fetched from the origin using HTTPS is never to use any other protocol
    -- to fetch the object. If you have recently changed from HTTP to HTTPS, we
    -- recommend that you clear your objects\' cache because cached objects are
    -- protocol agnostic. That means that an edge location will return an
    -- object from the cache regardless of whether the current request protocol
    -- matches the protocol used previously. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing Cache Expiration>
    -- in the /Amazon CloudFront Developer Guide/.
    DefaultCacheBehavior -> ViewerProtocolPolicy
viewerProtocolPolicy :: ViewerProtocolPolicy
  }
  deriving (DefaultCacheBehavior -> DefaultCacheBehavior -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefaultCacheBehavior -> DefaultCacheBehavior -> Bool
$c/= :: DefaultCacheBehavior -> DefaultCacheBehavior -> Bool
== :: DefaultCacheBehavior -> DefaultCacheBehavior -> Bool
$c== :: DefaultCacheBehavior -> DefaultCacheBehavior -> Bool
Prelude.Eq, ReadPrec [DefaultCacheBehavior]
ReadPrec DefaultCacheBehavior
Int -> ReadS DefaultCacheBehavior
ReadS [DefaultCacheBehavior]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DefaultCacheBehavior]
$creadListPrec :: ReadPrec [DefaultCacheBehavior]
readPrec :: ReadPrec DefaultCacheBehavior
$creadPrec :: ReadPrec DefaultCacheBehavior
readList :: ReadS [DefaultCacheBehavior]
$creadList :: ReadS [DefaultCacheBehavior]
readsPrec :: Int -> ReadS DefaultCacheBehavior
$creadsPrec :: Int -> ReadS DefaultCacheBehavior
Prelude.Read, Int -> DefaultCacheBehavior -> ShowS
[DefaultCacheBehavior] -> ShowS
DefaultCacheBehavior -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DefaultCacheBehavior] -> ShowS
$cshowList :: [DefaultCacheBehavior] -> ShowS
show :: DefaultCacheBehavior -> String
$cshow :: DefaultCacheBehavior -> String
showsPrec :: Int -> DefaultCacheBehavior -> ShowS
$cshowsPrec :: Int -> DefaultCacheBehavior -> ShowS
Prelude.Show, forall x. Rep DefaultCacheBehavior x -> DefaultCacheBehavior
forall x. DefaultCacheBehavior -> Rep DefaultCacheBehavior x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DefaultCacheBehavior x -> DefaultCacheBehavior
$cfrom :: forall x. DefaultCacheBehavior -> Rep DefaultCacheBehavior x
Prelude.Generic)

-- |
-- Create a value of 'DefaultCacheBehavior' 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:
--
-- 'allowedMethods', 'defaultCacheBehavior_allowedMethods' - Undocumented member.
--
-- 'cachePolicyId', 'defaultCacheBehavior_cachePolicyId' - The unique identifier of the cache policy that is attached to the
-- default cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
-- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
--
-- 'compress', 'defaultCacheBehavior_compress' - Whether you want CloudFront to automatically compress certain files for
-- this cache behavior. If so, specify @true@; if not, specify @false@. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/ServingCompressedFiles.html Serving Compressed Files>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'defaultTTL', 'defaultCacheBehavior_defaultTTL' - This field is deprecated. We recommend that you use the @DefaultTTL@
-- field in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The default amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. The value that you
-- specify applies only when your origin does not add HTTP headers such as
-- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
-- objects. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'fieldLevelEncryptionId', 'defaultCacheBehavior_fieldLevelEncryptionId' - The value of @ID@ for the field-level encryption configuration that you
-- want CloudFront to use for encrypting specific fields of data for the
-- default cache behavior.
--
-- 'forwardedValues', 'defaultCacheBehavior_forwardedValues' - This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/working-with-policies.html Working with policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to include values in the cache key, use a cache policy. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send values to the origin but not include them in the
-- cache key, use an origin request policy. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
-- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
--
-- A complex type that specifies how CloudFront handles query strings,
-- cookies, and HTTP headers.
--
-- 'functionAssociations', 'defaultCacheBehavior_functionAssociations' - A list of CloudFront functions that are associated with this cache
-- behavior. CloudFront functions must be published to the @LIVE@ stage to
-- associate them with a cache behavior.
--
-- 'lambdaFunctionAssociations', 'defaultCacheBehavior_lambdaFunctionAssociations' - A complex type that contains zero or more Lambda\@Edge function
-- associations for a cache behavior.
--
-- 'maxTTL', 'defaultCacheBehavior_maxTTL' - This field is deprecated. We recommend that you use the @MaxTTL@ field
-- in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The maximum amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. The value that you
-- specify applies only when your origin adds HTTP headers such as
-- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
-- objects. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'minTTL', 'defaultCacheBehavior_minTTL' - This field is deprecated. We recommend that you use the @MinTTL@ field
-- in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The minimum amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
--
-- You must specify @0@ for @MinTTL@ if you configure CloudFront to forward
-- all headers to your origin (under @Headers@, if you specify @1@ for
-- @Quantity@ and @*@ for @Name@).
--
-- 'originRequestPolicyId', 'defaultCacheBehavior_originRequestPolicyId' - The unique identifier of the origin request policy that is attached to
-- the default cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'realtimeLogConfigArn', 'defaultCacheBehavior_realtimeLogConfigArn' - The Amazon Resource Name (ARN) of the real-time log configuration that
-- is attached to this cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html Real-time logs>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'responseHeadersPolicyId', 'defaultCacheBehavior_responseHeadersPolicyId' - The identifier for a response headers policy.
--
-- 'smoothStreaming', 'defaultCacheBehavior_smoothStreaming' - Indicates whether you want to distribute media files in the Microsoft
-- Smooth Streaming format using the origin that is associated with this
-- cache behavior. If so, specify @true@; if not, specify @false@. If you
-- specify @true@ for @SmoothStreaming@, you can still distribute other
-- content using this cache behavior if the content matches the value of
-- @PathPattern@.
--
-- 'trustedKeyGroups', 'defaultCacheBehavior_trustedKeyGroups' - A list of key groups that CloudFront can use to validate signed URLs or
-- signed cookies.
--
-- When a cache behavior contains trusted key groups, CloudFront requires
-- signed URLs or signed cookies for all requests that match the cache
-- behavior. The URLs or cookies must be signed with a private key whose
-- corresponding public key is in the key group. The signed URL or cookie
-- contains information about which public key CloudFront should use to
-- verify the signature. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'trustedSigners', 'defaultCacheBehavior_trustedSigners' - We recommend using @TrustedKeyGroups@ instead of @TrustedSigners@.
--
-- A list of Amazon Web Services account IDs whose public keys CloudFront
-- can use to validate signed URLs or signed cookies.
--
-- When a cache behavior contains trusted signers, CloudFront requires
-- signed URLs or signed cookies for all requests that match the cache
-- behavior. The URLs or cookies must be signed with the private key of a
-- CloudFront key pair in a trusted signer\'s Amazon Web Services account.
-- The signed URL or cookie contains information about which public key
-- CloudFront should use to verify the signature. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'targetOriginId', 'defaultCacheBehavior_targetOriginId' - The value of @ID@ for the origin that you want CloudFront to route
-- requests to when they use the default cache behavior.
--
-- 'viewerProtocolPolicy', 'defaultCacheBehavior_viewerProtocolPolicy' - The protocol that viewers can use to access the files in the origin
-- specified by @TargetOriginId@ when a request matches the path pattern in
-- @PathPattern@. You can specify the following options:
--
-- -   @allow-all@: Viewers can use HTTP or HTTPS.
--
-- -   @redirect-to-https@: If a viewer submits an HTTP request, CloudFront
--     returns an HTTP status code of 301 (Moved Permanently) to the viewer
--     along with the HTTPS URL. The viewer then resubmits the request
--     using the new URL.
--
-- -   @https-only@: If a viewer sends an HTTP request, CloudFront returns
--     an HTTP status code of 403 (Forbidden).
--
-- For more information about requiring the HTTPS protocol, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-https-viewers-to-cloudfront.html Requiring HTTPS Between Viewers and CloudFront>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The only way to guarantee that viewers retrieve an object that was
-- fetched from the origin using HTTPS is never to use any other protocol
-- to fetch the object. If you have recently changed from HTTP to HTTPS, we
-- recommend that you clear your objects\' cache because cached objects are
-- protocol agnostic. That means that an edge location will return an
-- object from the cache regardless of whether the current request protocol
-- matches the protocol used previously. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing Cache Expiration>
-- in the /Amazon CloudFront Developer Guide/.
newDefaultCacheBehavior ::
  -- | 'targetOriginId'
  Prelude.Text ->
  -- | 'viewerProtocolPolicy'
  ViewerProtocolPolicy ->
  DefaultCacheBehavior
newDefaultCacheBehavior :: Text -> ViewerProtocolPolicy -> DefaultCacheBehavior
newDefaultCacheBehavior
  Text
pTargetOriginId_
  ViewerProtocolPolicy
pViewerProtocolPolicy_ =
    DefaultCacheBehavior'
      { $sel:allowedMethods:DefaultCacheBehavior' :: Maybe AllowedMethods
allowedMethods =
          forall a. Maybe a
Prelude.Nothing,
        $sel:cachePolicyId:DefaultCacheBehavior' :: Maybe Text
cachePolicyId = forall a. Maybe a
Prelude.Nothing,
        $sel:compress:DefaultCacheBehavior' :: Maybe Bool
compress = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultTTL:DefaultCacheBehavior' :: Maybe Integer
defaultTTL = forall a. Maybe a
Prelude.Nothing,
        $sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: Maybe Text
fieldLevelEncryptionId = forall a. Maybe a
Prelude.Nothing,
        $sel:forwardedValues:DefaultCacheBehavior' :: Maybe ForwardedValues
forwardedValues = forall a. Maybe a
Prelude.Nothing,
        $sel:functionAssociations:DefaultCacheBehavior' :: Maybe FunctionAssociations
functionAssociations = forall a. Maybe a
Prelude.Nothing,
        $sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: Maybe LambdaFunctionAssociations
lambdaFunctionAssociations = forall a. Maybe a
Prelude.Nothing,
        $sel:maxTTL:DefaultCacheBehavior' :: Maybe Integer
maxTTL = forall a. Maybe a
Prelude.Nothing,
        $sel:minTTL:DefaultCacheBehavior' :: Maybe Integer
minTTL = forall a. Maybe a
Prelude.Nothing,
        $sel:originRequestPolicyId:DefaultCacheBehavior' :: Maybe Text
originRequestPolicyId = forall a. Maybe a
Prelude.Nothing,
        $sel:realtimeLogConfigArn:DefaultCacheBehavior' :: Maybe Text
realtimeLogConfigArn = forall a. Maybe a
Prelude.Nothing,
        $sel:responseHeadersPolicyId:DefaultCacheBehavior' :: Maybe Text
responseHeadersPolicyId = forall a. Maybe a
Prelude.Nothing,
        $sel:smoothStreaming:DefaultCacheBehavior' :: Maybe Bool
smoothStreaming = forall a. Maybe a
Prelude.Nothing,
        $sel:trustedKeyGroups:DefaultCacheBehavior' :: Maybe TrustedKeyGroups
trustedKeyGroups = forall a. Maybe a
Prelude.Nothing,
        $sel:trustedSigners:DefaultCacheBehavior' :: Maybe TrustedSigners
trustedSigners = forall a. Maybe a
Prelude.Nothing,
        $sel:targetOriginId:DefaultCacheBehavior' :: Text
targetOriginId = Text
pTargetOriginId_,
        $sel:viewerProtocolPolicy:DefaultCacheBehavior' :: ViewerProtocolPolicy
viewerProtocolPolicy = ViewerProtocolPolicy
pViewerProtocolPolicy_
      }

-- | Undocumented member.
defaultCacheBehavior_allowedMethods :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe AllowedMethods)
defaultCacheBehavior_allowedMethods :: Lens' DefaultCacheBehavior (Maybe AllowedMethods)
defaultCacheBehavior_allowedMethods = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe AllowedMethods
allowedMethods :: Maybe AllowedMethods
$sel:allowedMethods:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe AllowedMethods
allowedMethods} -> Maybe AllowedMethods
allowedMethods) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe AllowedMethods
a -> DefaultCacheBehavior
s {$sel:allowedMethods:DefaultCacheBehavior' :: Maybe AllowedMethods
allowedMethods = Maybe AllowedMethods
a} :: DefaultCacheBehavior)

-- | The unique identifier of the cache policy that is attached to the
-- default cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
-- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
defaultCacheBehavior_cachePolicyId :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Text)
defaultCacheBehavior_cachePolicyId :: Lens' DefaultCacheBehavior (Maybe Text)
defaultCacheBehavior_cachePolicyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Text
cachePolicyId :: Maybe Text
$sel:cachePolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
cachePolicyId} -> Maybe Text
cachePolicyId) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Text
a -> DefaultCacheBehavior
s {$sel:cachePolicyId:DefaultCacheBehavior' :: Maybe Text
cachePolicyId = Maybe Text
a} :: DefaultCacheBehavior)

-- | Whether you want CloudFront to automatically compress certain files for
-- this cache behavior. If so, specify @true@; if not, specify @false@. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/ServingCompressedFiles.html Serving Compressed Files>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_compress :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Bool)
defaultCacheBehavior_compress :: Lens' DefaultCacheBehavior (Maybe Bool)
defaultCacheBehavior_compress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Bool
compress :: Maybe Bool
$sel:compress:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
compress} -> Maybe Bool
compress) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Bool
a -> DefaultCacheBehavior
s {$sel:compress:DefaultCacheBehavior' :: Maybe Bool
compress = Maybe Bool
a} :: DefaultCacheBehavior)

-- | This field is deprecated. We recommend that you use the @DefaultTTL@
-- field in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The default amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. The value that you
-- specify applies only when your origin does not add HTTP headers such as
-- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
-- objects. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_defaultTTL :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Integer)
defaultCacheBehavior_defaultTTL :: Lens' DefaultCacheBehavior (Maybe Integer)
defaultCacheBehavior_defaultTTL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Integer
defaultTTL :: Maybe Integer
$sel:defaultTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
defaultTTL} -> Maybe Integer
defaultTTL) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Integer
a -> DefaultCacheBehavior
s {$sel:defaultTTL:DefaultCacheBehavior' :: Maybe Integer
defaultTTL = Maybe Integer
a} :: DefaultCacheBehavior)

-- | The value of @ID@ for the field-level encryption configuration that you
-- want CloudFront to use for encrypting specific fields of data for the
-- default cache behavior.
defaultCacheBehavior_fieldLevelEncryptionId :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Text)
defaultCacheBehavior_fieldLevelEncryptionId :: Lens' DefaultCacheBehavior (Maybe Text)
defaultCacheBehavior_fieldLevelEncryptionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Text
fieldLevelEncryptionId :: Maybe Text
$sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
fieldLevelEncryptionId} -> Maybe Text
fieldLevelEncryptionId) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Text
a -> DefaultCacheBehavior
s {$sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: Maybe Text
fieldLevelEncryptionId = Maybe Text
a} :: DefaultCacheBehavior)

-- | This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/working-with-policies.html Working with policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to include values in the cache key, use a cache policy. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send values to the origin but not include them in the
-- cache key, use an origin request policy. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- A @DefaultCacheBehavior@ must include either a @CachePolicyId@ or
-- @ForwardedValues@. We recommend that you use a @CachePolicyId@.
--
-- A complex type that specifies how CloudFront handles query strings,
-- cookies, and HTTP headers.
defaultCacheBehavior_forwardedValues :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe ForwardedValues)
defaultCacheBehavior_forwardedValues :: Lens' DefaultCacheBehavior (Maybe ForwardedValues)
defaultCacheBehavior_forwardedValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe ForwardedValues
forwardedValues :: Maybe ForwardedValues
$sel:forwardedValues:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe ForwardedValues
forwardedValues} -> Maybe ForwardedValues
forwardedValues) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe ForwardedValues
a -> DefaultCacheBehavior
s {$sel:forwardedValues:DefaultCacheBehavior' :: Maybe ForwardedValues
forwardedValues = Maybe ForwardedValues
a} :: DefaultCacheBehavior)

-- | A list of CloudFront functions that are associated with this cache
-- behavior. CloudFront functions must be published to the @LIVE@ stage to
-- associate them with a cache behavior.
defaultCacheBehavior_functionAssociations :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe FunctionAssociations)
defaultCacheBehavior_functionAssociations :: Lens' DefaultCacheBehavior (Maybe FunctionAssociations)
defaultCacheBehavior_functionAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe FunctionAssociations
functionAssociations :: Maybe FunctionAssociations
$sel:functionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe FunctionAssociations
functionAssociations} -> Maybe FunctionAssociations
functionAssociations) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe FunctionAssociations
a -> DefaultCacheBehavior
s {$sel:functionAssociations:DefaultCacheBehavior' :: Maybe FunctionAssociations
functionAssociations = Maybe FunctionAssociations
a} :: DefaultCacheBehavior)

-- | A complex type that contains zero or more Lambda\@Edge function
-- associations for a cache behavior.
defaultCacheBehavior_lambdaFunctionAssociations :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe LambdaFunctionAssociations)
defaultCacheBehavior_lambdaFunctionAssociations :: Lens' DefaultCacheBehavior (Maybe LambdaFunctionAssociations)
defaultCacheBehavior_lambdaFunctionAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe LambdaFunctionAssociations
lambdaFunctionAssociations :: Maybe LambdaFunctionAssociations
$sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe LambdaFunctionAssociations
lambdaFunctionAssociations} -> Maybe LambdaFunctionAssociations
lambdaFunctionAssociations) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe LambdaFunctionAssociations
a -> DefaultCacheBehavior
s {$sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: Maybe LambdaFunctionAssociations
lambdaFunctionAssociations = Maybe LambdaFunctionAssociations
a} :: DefaultCacheBehavior)

-- | This field is deprecated. We recommend that you use the @MaxTTL@ field
-- in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The maximum amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. The value that you
-- specify applies only when your origin adds HTTP headers such as
-- @Cache-Control max-age@, @Cache-Control s-maxage@, and @Expires@ to
-- objects. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_maxTTL :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Integer)
defaultCacheBehavior_maxTTL :: Lens' DefaultCacheBehavior (Maybe Integer)
defaultCacheBehavior_maxTTL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Integer
maxTTL :: Maybe Integer
$sel:maxTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
maxTTL} -> Maybe Integer
maxTTL) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Integer
a -> DefaultCacheBehavior
s {$sel:maxTTL:DefaultCacheBehavior' :: Maybe Integer
maxTTL = Maybe Integer
a} :: DefaultCacheBehavior)

-- | This field is deprecated. We recommend that you use the @MinTTL@ field
-- in a cache policy instead of this field. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-the-cache-key.html#cache-key-create-cache-policy Creating cache policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-cache-policies.html Using the managed cache policies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The minimum amount of time that you want objects to stay in CloudFront
-- caches before CloudFront forwards another request to your origin to
-- determine whether the object has been updated. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing How Long Content Stays in an Edge Cache (Expiration)>
-- in the /Amazon CloudFront Developer Guide/.
--
-- You must specify @0@ for @MinTTL@ if you configure CloudFront to forward
-- all headers to your origin (under @Headers@, if you specify @1@ for
-- @Quantity@ and @*@ for @Name@).
defaultCacheBehavior_minTTL :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Integer)
defaultCacheBehavior_minTTL :: Lens' DefaultCacheBehavior (Maybe Integer)
defaultCacheBehavior_minTTL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Integer
minTTL :: Maybe Integer
$sel:minTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
minTTL} -> Maybe Integer
minTTL) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Integer
a -> DefaultCacheBehavior
s {$sel:minTTL:DefaultCacheBehavior' :: Maybe Integer
minTTL = Maybe Integer
a} :: DefaultCacheBehavior)

-- | The unique identifier of the origin request policy that is attached to
-- the default cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/controlling-origin-requests.html#origin-request-create-origin-request-policy Creating origin request policies>
-- or
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-managed-origin-request-policies.html Using the managed origin request policies>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_originRequestPolicyId :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Text)
defaultCacheBehavior_originRequestPolicyId :: Lens' DefaultCacheBehavior (Maybe Text)
defaultCacheBehavior_originRequestPolicyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Text
originRequestPolicyId :: Maybe Text
$sel:originRequestPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
originRequestPolicyId} -> Maybe Text
originRequestPolicyId) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Text
a -> DefaultCacheBehavior
s {$sel:originRequestPolicyId:DefaultCacheBehavior' :: Maybe Text
originRequestPolicyId = Maybe Text
a} :: DefaultCacheBehavior)

-- | The Amazon Resource Name (ARN) of the real-time log configuration that
-- is attached to this cache behavior. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html Real-time logs>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_realtimeLogConfigArn :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Text)
defaultCacheBehavior_realtimeLogConfigArn :: Lens' DefaultCacheBehavior (Maybe Text)
defaultCacheBehavior_realtimeLogConfigArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Text
realtimeLogConfigArn :: Maybe Text
$sel:realtimeLogConfigArn:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
realtimeLogConfigArn} -> Maybe Text
realtimeLogConfigArn) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Text
a -> DefaultCacheBehavior
s {$sel:realtimeLogConfigArn:DefaultCacheBehavior' :: Maybe Text
realtimeLogConfigArn = Maybe Text
a} :: DefaultCacheBehavior)

-- | The identifier for a response headers policy.
defaultCacheBehavior_responseHeadersPolicyId :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Text)
defaultCacheBehavior_responseHeadersPolicyId :: Lens' DefaultCacheBehavior (Maybe Text)
defaultCacheBehavior_responseHeadersPolicyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Text
responseHeadersPolicyId :: Maybe Text
$sel:responseHeadersPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
responseHeadersPolicyId} -> Maybe Text
responseHeadersPolicyId) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Text
a -> DefaultCacheBehavior
s {$sel:responseHeadersPolicyId:DefaultCacheBehavior' :: Maybe Text
responseHeadersPolicyId = Maybe Text
a} :: DefaultCacheBehavior)

-- | Indicates whether you want to distribute media files in the Microsoft
-- Smooth Streaming format using the origin that is associated with this
-- cache behavior. If so, specify @true@; if not, specify @false@. If you
-- specify @true@ for @SmoothStreaming@, you can still distribute other
-- content using this cache behavior if the content matches the value of
-- @PathPattern@.
defaultCacheBehavior_smoothStreaming :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe Prelude.Bool)
defaultCacheBehavior_smoothStreaming :: Lens' DefaultCacheBehavior (Maybe Bool)
defaultCacheBehavior_smoothStreaming = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe Bool
smoothStreaming :: Maybe Bool
$sel:smoothStreaming:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
smoothStreaming} -> Maybe Bool
smoothStreaming) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe Bool
a -> DefaultCacheBehavior
s {$sel:smoothStreaming:DefaultCacheBehavior' :: Maybe Bool
smoothStreaming = Maybe Bool
a} :: DefaultCacheBehavior)

-- | A list of key groups that CloudFront can use to validate signed URLs or
-- signed cookies.
--
-- When a cache behavior contains trusted key groups, CloudFront requires
-- signed URLs or signed cookies for all requests that match the cache
-- behavior. The URLs or cookies must be signed with a private key whose
-- corresponding public key is in the key group. The signed URL or cookie
-- contains information about which public key CloudFront should use to
-- verify the signature. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_trustedKeyGroups :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe TrustedKeyGroups)
defaultCacheBehavior_trustedKeyGroups :: Lens' DefaultCacheBehavior (Maybe TrustedKeyGroups)
defaultCacheBehavior_trustedKeyGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe TrustedKeyGroups
trustedKeyGroups :: Maybe TrustedKeyGroups
$sel:trustedKeyGroups:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedKeyGroups
trustedKeyGroups} -> Maybe TrustedKeyGroups
trustedKeyGroups) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe TrustedKeyGroups
a -> DefaultCacheBehavior
s {$sel:trustedKeyGroups:DefaultCacheBehavior' :: Maybe TrustedKeyGroups
trustedKeyGroups = Maybe TrustedKeyGroups
a} :: DefaultCacheBehavior)

-- | We recommend using @TrustedKeyGroups@ instead of @TrustedSigners@.
--
-- A list of Amazon Web Services account IDs whose public keys CloudFront
-- can use to validate signed URLs or signed cookies.
--
-- When a cache behavior contains trusted signers, CloudFront requires
-- signed URLs or signed cookies for all requests that match the cache
-- behavior. The URLs or cookies must be signed with the private key of a
-- CloudFront key pair in a trusted signer\'s Amazon Web Services account.
-- The signed URL or cookie contains information about which public key
-- CloudFront should use to verify the signature. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving private content>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_trustedSigners :: Lens.Lens' DefaultCacheBehavior (Prelude.Maybe TrustedSigners)
defaultCacheBehavior_trustedSigners :: Lens' DefaultCacheBehavior (Maybe TrustedSigners)
defaultCacheBehavior_trustedSigners = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Maybe TrustedSigners
trustedSigners :: Maybe TrustedSigners
$sel:trustedSigners:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedSigners
trustedSigners} -> Maybe TrustedSigners
trustedSigners) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Maybe TrustedSigners
a -> DefaultCacheBehavior
s {$sel:trustedSigners:DefaultCacheBehavior' :: Maybe TrustedSigners
trustedSigners = Maybe TrustedSigners
a} :: DefaultCacheBehavior)

-- | The value of @ID@ for the origin that you want CloudFront to route
-- requests to when they use the default cache behavior.
defaultCacheBehavior_targetOriginId :: Lens.Lens' DefaultCacheBehavior Prelude.Text
defaultCacheBehavior_targetOriginId :: Lens' DefaultCacheBehavior Text
defaultCacheBehavior_targetOriginId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {Text
targetOriginId :: Text
$sel:targetOriginId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Text
targetOriginId} -> Text
targetOriginId) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} Text
a -> DefaultCacheBehavior
s {$sel:targetOriginId:DefaultCacheBehavior' :: Text
targetOriginId = Text
a} :: DefaultCacheBehavior)

-- | The protocol that viewers can use to access the files in the origin
-- specified by @TargetOriginId@ when a request matches the path pattern in
-- @PathPattern@. You can specify the following options:
--
-- -   @allow-all@: Viewers can use HTTP or HTTPS.
--
-- -   @redirect-to-https@: If a viewer submits an HTTP request, CloudFront
--     returns an HTTP status code of 301 (Moved Permanently) to the viewer
--     along with the HTTPS URL. The viewer then resubmits the request
--     using the new URL.
--
-- -   @https-only@: If a viewer sends an HTTP request, CloudFront returns
--     an HTTP status code of 403 (Forbidden).
--
-- For more information about requiring the HTTPS protocol, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/using-https-viewers-to-cloudfront.html Requiring HTTPS Between Viewers and CloudFront>
-- in the /Amazon CloudFront Developer Guide/.
--
-- The only way to guarantee that viewers retrieve an object that was
-- fetched from the origin using HTTPS is never to use any other protocol
-- to fetch the object. If you have recently changed from HTTP to HTTPS, we
-- recommend that you clear your objects\' cache because cached objects are
-- protocol agnostic. That means that an edge location will return an
-- object from the cache regardless of whether the current request protocol
-- matches the protocol used previously. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Expiration.html Managing Cache Expiration>
-- in the /Amazon CloudFront Developer Guide/.
defaultCacheBehavior_viewerProtocolPolicy :: Lens.Lens' DefaultCacheBehavior ViewerProtocolPolicy
defaultCacheBehavior_viewerProtocolPolicy :: Lens' DefaultCacheBehavior ViewerProtocolPolicy
defaultCacheBehavior_viewerProtocolPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DefaultCacheBehavior' {ViewerProtocolPolicy
viewerProtocolPolicy :: ViewerProtocolPolicy
$sel:viewerProtocolPolicy:DefaultCacheBehavior' :: DefaultCacheBehavior -> ViewerProtocolPolicy
viewerProtocolPolicy} -> ViewerProtocolPolicy
viewerProtocolPolicy) (\s :: DefaultCacheBehavior
s@DefaultCacheBehavior' {} ViewerProtocolPolicy
a -> DefaultCacheBehavior
s {$sel:viewerProtocolPolicy:DefaultCacheBehavior' :: ViewerProtocolPolicy
viewerProtocolPolicy = ViewerProtocolPolicy
a} :: DefaultCacheBehavior)

instance Data.FromXML DefaultCacheBehavior where
  parseXML :: [Node] -> Either String DefaultCacheBehavior
parseXML [Node]
x =
    Maybe AllowedMethods
-> Maybe Text
-> Maybe Bool
-> Maybe Integer
-> Maybe Text
-> Maybe ForwardedValues
-> Maybe FunctionAssociations
-> Maybe LambdaFunctionAssociations
-> Maybe Integer
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe TrustedKeyGroups
-> Maybe TrustedSigners
-> Text
-> ViewerProtocolPolicy
-> DefaultCacheBehavior
DefaultCacheBehavior'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AllowedMethods")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CachePolicyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Compress")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DefaultTTL")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"FieldLevelEncryptionId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ForwardedValues")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"FunctionAssociations")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LambdaFunctionAssociations")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MaxTTL")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MinTTL")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OriginRequestPolicyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"RealtimeLogConfigArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ResponseHeadersPolicyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SmoothStreaming")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TrustedKeyGroups")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TrustedSigners")
      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
"TargetOriginId")
      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
"ViewerProtocolPolicy")

instance Prelude.Hashable DefaultCacheBehavior where
  hashWithSalt :: Int -> DefaultCacheBehavior -> Int
hashWithSalt Int
_salt DefaultCacheBehavior' {Maybe Bool
Maybe Integer
Maybe Text
Maybe FunctionAssociations
Maybe LambdaFunctionAssociations
Maybe AllowedMethods
Maybe ForwardedValues
Maybe TrustedKeyGroups
Maybe TrustedSigners
Text
ViewerProtocolPolicy
viewerProtocolPolicy :: ViewerProtocolPolicy
targetOriginId :: Text
trustedSigners :: Maybe TrustedSigners
trustedKeyGroups :: Maybe TrustedKeyGroups
smoothStreaming :: Maybe Bool
responseHeadersPolicyId :: Maybe Text
realtimeLogConfigArn :: Maybe Text
originRequestPolicyId :: Maybe Text
minTTL :: Maybe Integer
maxTTL :: Maybe Integer
lambdaFunctionAssociations :: Maybe LambdaFunctionAssociations
functionAssociations :: Maybe FunctionAssociations
forwardedValues :: Maybe ForwardedValues
fieldLevelEncryptionId :: Maybe Text
defaultTTL :: Maybe Integer
compress :: Maybe Bool
cachePolicyId :: Maybe Text
allowedMethods :: Maybe AllowedMethods
$sel:viewerProtocolPolicy:DefaultCacheBehavior' :: DefaultCacheBehavior -> ViewerProtocolPolicy
$sel:targetOriginId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Text
$sel:trustedSigners:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedSigners
$sel:trustedKeyGroups:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedKeyGroups
$sel:smoothStreaming:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:responseHeadersPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:realtimeLogConfigArn:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:originRequestPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:minTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:maxTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe LambdaFunctionAssociations
$sel:functionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe FunctionAssociations
$sel:forwardedValues:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe ForwardedValues
$sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:defaultTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:compress:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:cachePolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:allowedMethods:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe AllowedMethods
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AllowedMethods
allowedMethods
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cachePolicyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
compress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
defaultTTL
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fieldLevelEncryptionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ForwardedValues
forwardedValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FunctionAssociations
functionAssociations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionAssociations
lambdaFunctionAssociations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
maxTTL
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
minTTL
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
originRequestPolicyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
realtimeLogConfigArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
responseHeadersPolicyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
smoothStreaming
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrustedKeyGroups
trustedKeyGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrustedSigners
trustedSigners
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetOriginId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ViewerProtocolPolicy
viewerProtocolPolicy

instance Prelude.NFData DefaultCacheBehavior where
  rnf :: DefaultCacheBehavior -> ()
rnf DefaultCacheBehavior' {Maybe Bool
Maybe Integer
Maybe Text
Maybe FunctionAssociations
Maybe LambdaFunctionAssociations
Maybe AllowedMethods
Maybe ForwardedValues
Maybe TrustedKeyGroups
Maybe TrustedSigners
Text
ViewerProtocolPolicy
viewerProtocolPolicy :: ViewerProtocolPolicy
targetOriginId :: Text
trustedSigners :: Maybe TrustedSigners
trustedKeyGroups :: Maybe TrustedKeyGroups
smoothStreaming :: Maybe Bool
responseHeadersPolicyId :: Maybe Text
realtimeLogConfigArn :: Maybe Text
originRequestPolicyId :: Maybe Text
minTTL :: Maybe Integer
maxTTL :: Maybe Integer
lambdaFunctionAssociations :: Maybe LambdaFunctionAssociations
functionAssociations :: Maybe FunctionAssociations
forwardedValues :: Maybe ForwardedValues
fieldLevelEncryptionId :: Maybe Text
defaultTTL :: Maybe Integer
compress :: Maybe Bool
cachePolicyId :: Maybe Text
allowedMethods :: Maybe AllowedMethods
$sel:viewerProtocolPolicy:DefaultCacheBehavior' :: DefaultCacheBehavior -> ViewerProtocolPolicy
$sel:targetOriginId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Text
$sel:trustedSigners:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedSigners
$sel:trustedKeyGroups:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedKeyGroups
$sel:smoothStreaming:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:responseHeadersPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:realtimeLogConfigArn:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:originRequestPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:minTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:maxTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe LambdaFunctionAssociations
$sel:functionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe FunctionAssociations
$sel:forwardedValues:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe ForwardedValues
$sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:defaultTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:compress:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:cachePolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:allowedMethods:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe AllowedMethods
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AllowedMethods
allowedMethods
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cachePolicyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
compress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
defaultTTL
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fieldLevelEncryptionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ForwardedValues
forwardedValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FunctionAssociations
functionAssociations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaFunctionAssociations
lambdaFunctionAssociations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
maxTTL
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
minTTL
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
originRequestPolicyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
realtimeLogConfigArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
responseHeadersPolicyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
smoothStreaming
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustedKeyGroups
trustedKeyGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustedSigners
trustedSigners
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetOriginId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ViewerProtocolPolicy
viewerProtocolPolicy

instance Data.ToXML DefaultCacheBehavior where
  toXML :: DefaultCacheBehavior -> XML
toXML DefaultCacheBehavior' {Maybe Bool
Maybe Integer
Maybe Text
Maybe FunctionAssociations
Maybe LambdaFunctionAssociations
Maybe AllowedMethods
Maybe ForwardedValues
Maybe TrustedKeyGroups
Maybe TrustedSigners
Text
ViewerProtocolPolicy
viewerProtocolPolicy :: ViewerProtocolPolicy
targetOriginId :: Text
trustedSigners :: Maybe TrustedSigners
trustedKeyGroups :: Maybe TrustedKeyGroups
smoothStreaming :: Maybe Bool
responseHeadersPolicyId :: Maybe Text
realtimeLogConfigArn :: Maybe Text
originRequestPolicyId :: Maybe Text
minTTL :: Maybe Integer
maxTTL :: Maybe Integer
lambdaFunctionAssociations :: Maybe LambdaFunctionAssociations
functionAssociations :: Maybe FunctionAssociations
forwardedValues :: Maybe ForwardedValues
fieldLevelEncryptionId :: Maybe Text
defaultTTL :: Maybe Integer
compress :: Maybe Bool
cachePolicyId :: Maybe Text
allowedMethods :: Maybe AllowedMethods
$sel:viewerProtocolPolicy:DefaultCacheBehavior' :: DefaultCacheBehavior -> ViewerProtocolPolicy
$sel:targetOriginId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Text
$sel:trustedSigners:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedSigners
$sel:trustedKeyGroups:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe TrustedKeyGroups
$sel:smoothStreaming:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:responseHeadersPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:realtimeLogConfigArn:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:originRequestPolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:minTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:maxTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:lambdaFunctionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe LambdaFunctionAssociations
$sel:functionAssociations:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe FunctionAssociations
$sel:forwardedValues:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe ForwardedValues
$sel:fieldLevelEncryptionId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:defaultTTL:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Integer
$sel:compress:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Bool
$sel:cachePolicyId:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe Text
$sel:allowedMethods:DefaultCacheBehavior' :: DefaultCacheBehavior -> Maybe AllowedMethods
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"AllowedMethods" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe AllowedMethods
allowedMethods,
        Name
"CachePolicyId" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
cachePolicyId,
        Name
"Compress" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Bool
compress,
        Name
"DefaultTTL" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
defaultTTL,
        Name
"FieldLevelEncryptionId"
          forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
fieldLevelEncryptionId,
        Name
"ForwardedValues" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe ForwardedValues
forwardedValues,
        Name
"FunctionAssociations" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe FunctionAssociations
functionAssociations,
        Name
"LambdaFunctionAssociations"
          forall a. ToXML a => Name -> a -> XML
Data.@= Maybe LambdaFunctionAssociations
lambdaFunctionAssociations,
        Name
"MaxTTL" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
maxTTL,
        Name
"MinTTL" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
minTTL,
        Name
"OriginRequestPolicyId"
          forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
originRequestPolicyId,
        Name
"RealtimeLogConfigArn" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
realtimeLogConfigArn,
        Name
"ResponseHeadersPolicyId"
          forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
responseHeadersPolicyId,
        Name
"SmoothStreaming" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Bool
smoothStreaming,
        Name
"TrustedKeyGroups" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe TrustedKeyGroups
trustedKeyGroups,
        Name
"TrustedSigners" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe TrustedSigners
trustedSigners,
        Name
"TargetOriginId" forall a. ToXML a => Name -> a -> XML
Data.@= Text
targetOriginId,
        Name
"ViewerProtocolPolicy" forall a. ToXML a => Name -> a -> XML
Data.@= ViewerProtocolPolicy
viewerProtocolPolicy
      ]