{-# 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.CookiePreference
-- 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.CookiePreference where

import Amazonka.CloudFront.Types.CookieNames
import Amazonka.CloudFront.Types.ItemSelection
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

-- | This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field.
--
-- If you want to include cookies in the cache key, use @CookiesConfig@ in
-- a cache policy. See @CachePolicy@.
--
-- If you want to send cookies to the origin but not include them in the
-- cache key, use @CookiesConfig@ in an origin request policy. See
-- @OriginRequestPolicy@.
--
-- A complex type that specifies whether you want CloudFront to forward
-- cookies to the origin and, if so, which ones. For more information about
-- forwarding cookies to the origin, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/Cookies.html Caching Content Based on Cookies>
-- in the /Amazon CloudFront Developer Guide/.
--
-- /See:/ 'newCookiePreference' smart constructor.
data CookiePreference = CookiePreference'
  { -- | This field is deprecated. We recommend that you use a cache policy or an
    -- origin request policy instead of this field.
    --
    -- If you want to include cookies 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>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- If you want to send cookies 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>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- Required if you specify @whitelist@ for the value of @Forward@. A
    -- complex type that specifies how many different cookies you want
    -- CloudFront to forward to the origin for this cache behavior and, if you
    -- want to forward selected cookies, the names of those cookies.
    --
    -- If you specify @all@ or @none@ for the value of @Forward@, omit
    -- @WhitelistedNames@. If you change the value of @Forward@ from
    -- @whitelist@ to @all@ or @none@ and you don\'t delete the
    -- @WhitelistedNames@ element and its child elements, CloudFront deletes
    -- them automatically.
    --
    -- For the current limit on the number of cookie names that you can
    -- whitelist for each cache behavior, see
    -- <https://docs.aws.amazon.com/general/latest/gr/xrefaws_service_limits.html#limits_cloudfront CloudFront Limits>
    -- in the /Amazon Web Services General Reference/.
    CookiePreference -> Maybe CookieNames
whitelistedNames :: Prelude.Maybe CookieNames,
    -- | This field is deprecated. We recommend that you use a cache policy or an
    -- origin request policy instead of this field.
    --
    -- If you want to include cookies 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>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- If you want to send cookies to the origin but not include them in the
    -- cache key, use 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>
    -- in the /Amazon CloudFront Developer Guide/.
    --
    -- Specifies which cookies to forward to the origin for this cache
    -- behavior: all, none, or the list of cookies specified in the
    -- @WhitelistedNames@ complex type.
    --
    -- Amazon S3 doesn\'t process cookies. When the cache behavior is
    -- forwarding requests to an Amazon S3 origin, specify none for the
    -- @Forward@ element.
    CookiePreference -> ItemSelection
forward :: ItemSelection
  }
  deriving (CookiePreference -> CookiePreference -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CookiePreference -> CookiePreference -> Bool
$c/= :: CookiePreference -> CookiePreference -> Bool
== :: CookiePreference -> CookiePreference -> Bool
$c== :: CookiePreference -> CookiePreference -> Bool
Prelude.Eq, ReadPrec [CookiePreference]
ReadPrec CookiePreference
Int -> ReadS CookiePreference
ReadS [CookiePreference]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CookiePreference]
$creadListPrec :: ReadPrec [CookiePreference]
readPrec :: ReadPrec CookiePreference
$creadPrec :: ReadPrec CookiePreference
readList :: ReadS [CookiePreference]
$creadList :: ReadS [CookiePreference]
readsPrec :: Int -> ReadS CookiePreference
$creadsPrec :: Int -> ReadS CookiePreference
Prelude.Read, Int -> CookiePreference -> ShowS
[CookiePreference] -> ShowS
CookiePreference -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CookiePreference] -> ShowS
$cshowList :: [CookiePreference] -> ShowS
show :: CookiePreference -> String
$cshow :: CookiePreference -> String
showsPrec :: Int -> CookiePreference -> ShowS
$cshowsPrec :: Int -> CookiePreference -> ShowS
Prelude.Show, forall x. Rep CookiePreference x -> CookiePreference
forall x. CookiePreference -> Rep CookiePreference x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CookiePreference x -> CookiePreference
$cfrom :: forall x. CookiePreference -> Rep CookiePreference x
Prelude.Generic)

-- |
-- Create a value of 'CookiePreference' 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:
--
-- 'whitelistedNames', 'cookiePreference_whitelistedNames' - This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field.
--
-- If you want to include cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- Required if you specify @whitelist@ for the value of @Forward@. A
-- complex type that specifies how many different cookies you want
-- CloudFront to forward to the origin for this cache behavior and, if you
-- want to forward selected cookies, the names of those cookies.
--
-- If you specify @all@ or @none@ for the value of @Forward@, omit
-- @WhitelistedNames@. If you change the value of @Forward@ from
-- @whitelist@ to @all@ or @none@ and you don\'t delete the
-- @WhitelistedNames@ element and its child elements, CloudFront deletes
-- them automatically.
--
-- For the current limit on the number of cookie names that you can
-- whitelist for each cache behavior, see
-- <https://docs.aws.amazon.com/general/latest/gr/xrefaws_service_limits.html#limits_cloudfront CloudFront Limits>
-- in the /Amazon Web Services General Reference/.
--
-- 'forward', 'cookiePreference_forward' - This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field.
--
-- If you want to include cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send cookies to the origin but not include them in the
-- cache key, use 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- Specifies which cookies to forward to the origin for this cache
-- behavior: all, none, or the list of cookies specified in the
-- @WhitelistedNames@ complex type.
--
-- Amazon S3 doesn\'t process cookies. When the cache behavior is
-- forwarding requests to an Amazon S3 origin, specify none for the
-- @Forward@ element.
newCookiePreference ::
  -- | 'forward'
  ItemSelection ->
  CookiePreference
newCookiePreference :: ItemSelection -> CookiePreference
newCookiePreference ItemSelection
pForward_ =
  CookiePreference'
    { $sel:whitelistedNames:CookiePreference' :: Maybe CookieNames
whitelistedNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:forward:CookiePreference' :: ItemSelection
forward = ItemSelection
pForward_
    }

-- | This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field.
--
-- If you want to include cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- Required if you specify @whitelist@ for the value of @Forward@. A
-- complex type that specifies how many different cookies you want
-- CloudFront to forward to the origin for this cache behavior and, if you
-- want to forward selected cookies, the names of those cookies.
--
-- If you specify @all@ or @none@ for the value of @Forward@, omit
-- @WhitelistedNames@. If you change the value of @Forward@ from
-- @whitelist@ to @all@ or @none@ and you don\'t delete the
-- @WhitelistedNames@ element and its child elements, CloudFront deletes
-- them automatically.
--
-- For the current limit on the number of cookie names that you can
-- whitelist for each cache behavior, see
-- <https://docs.aws.amazon.com/general/latest/gr/xrefaws_service_limits.html#limits_cloudfront CloudFront Limits>
-- in the /Amazon Web Services General Reference/.
cookiePreference_whitelistedNames :: Lens.Lens' CookiePreference (Prelude.Maybe CookieNames)
cookiePreference_whitelistedNames :: Lens' CookiePreference (Maybe CookieNames)
cookiePreference_whitelistedNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CookiePreference' {Maybe CookieNames
whitelistedNames :: Maybe CookieNames
$sel:whitelistedNames:CookiePreference' :: CookiePreference -> Maybe CookieNames
whitelistedNames} -> Maybe CookieNames
whitelistedNames) (\s :: CookiePreference
s@CookiePreference' {} Maybe CookieNames
a -> CookiePreference
s {$sel:whitelistedNames:CookiePreference' :: Maybe CookieNames
whitelistedNames = Maybe CookieNames
a} :: CookiePreference)

-- | This field is deprecated. We recommend that you use a cache policy or an
-- origin request policy instead of this field.
--
-- If you want to include cookies 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- If you want to send cookies to the origin but not include them in the
-- cache key, use 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>
-- in the /Amazon CloudFront Developer Guide/.
--
-- Specifies which cookies to forward to the origin for this cache
-- behavior: all, none, or the list of cookies specified in the
-- @WhitelistedNames@ complex type.
--
-- Amazon S3 doesn\'t process cookies. When the cache behavior is
-- forwarding requests to an Amazon S3 origin, specify none for the
-- @Forward@ element.
cookiePreference_forward :: Lens.Lens' CookiePreference ItemSelection
cookiePreference_forward :: Lens' CookiePreference ItemSelection
cookiePreference_forward = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CookiePreference' {ItemSelection
forward :: ItemSelection
$sel:forward:CookiePreference' :: CookiePreference -> ItemSelection
forward} -> ItemSelection
forward) (\s :: CookiePreference
s@CookiePreference' {} ItemSelection
a -> CookiePreference
s {$sel:forward:CookiePreference' :: ItemSelection
forward = ItemSelection
a} :: CookiePreference)

instance Data.FromXML CookiePreference where
  parseXML :: [Node] -> Either String CookiePreference
parseXML [Node]
x =
    Maybe CookieNames -> ItemSelection -> CookiePreference
CookiePreference'
      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
"WhitelistedNames")
      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
"Forward")

instance Prelude.Hashable CookiePreference where
  hashWithSalt :: Int -> CookiePreference -> Int
hashWithSalt Int
_salt CookiePreference' {Maybe CookieNames
ItemSelection
forward :: ItemSelection
whitelistedNames :: Maybe CookieNames
$sel:forward:CookiePreference' :: CookiePreference -> ItemSelection
$sel:whitelistedNames:CookiePreference' :: CookiePreference -> Maybe CookieNames
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CookieNames
whitelistedNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ItemSelection
forward

instance Prelude.NFData CookiePreference where
  rnf :: CookiePreference -> ()
rnf CookiePreference' {Maybe CookieNames
ItemSelection
forward :: ItemSelection
whitelistedNames :: Maybe CookieNames
$sel:forward:CookiePreference' :: CookiePreference -> ItemSelection
$sel:whitelistedNames:CookiePreference' :: CookiePreference -> Maybe CookieNames
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CookieNames
whitelistedNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ItemSelection
forward

instance Data.ToXML CookiePreference where
  toXML :: CookiePreference -> XML
toXML CookiePreference' {Maybe CookieNames
ItemSelection
forward :: ItemSelection
whitelistedNames :: Maybe CookieNames
$sel:forward:CookiePreference' :: CookiePreference -> ItemSelection
$sel:whitelistedNames:CookiePreference' :: CookiePreference -> Maybe CookieNames
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"WhitelistedNames" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe CookieNames
whitelistedNames,
        Name
"Forward" forall a. ToXML a => Name -> a -> XML
Data.@= ItemSelection
forward
      ]