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

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

-- | An object that determines whether any cookies in viewer requests (and if
-- so, which cookies) are included in the cache key and automatically
-- included in requests that CloudFront sends to the origin.
--
-- /See:/ 'newCachePolicyCookiesConfig' smart constructor.
data CachePolicyCookiesConfig = CachePolicyCookiesConfig'
  { CachePolicyCookiesConfig -> Maybe CookieNames
cookies :: Prelude.Maybe CookieNames,
    -- | Determines whether any cookies in viewer requests are included in the
    -- cache key and automatically included in requests that CloudFront sends
    -- to the origin. Valid values are:
    --
    -- -   @none@ – Cookies in viewer requests are not included in the cache
    --     key and are not automatically included in requests that CloudFront
    --     sends to the origin. Even when this field is set to @none@, any
    --     cookies that are listed in an @OriginRequestPolicy@ /are/ included
    --     in origin requests.
    --
    -- -   @whitelist@ – The cookies in viewer requests that are listed in the
    --     @CookieNames@ type are included in the cache key and automatically
    --     included in requests that CloudFront sends to the origin.
    --
    -- -   @allExcept@ – All cookies in viewer requests that are /__not__/
    --     listed in the @CookieNames@ type are included in the cache key and
    --     automatically included in requests that CloudFront sends to the
    --     origin.
    --
    -- -   @all@ – All cookies in viewer requests are included in the cache key
    --     and are automatically included in requests that CloudFront sends to
    --     the origin.
    CachePolicyCookiesConfig -> CachePolicyCookieBehavior
cookieBehavior :: CachePolicyCookieBehavior
  }
  deriving (CachePolicyCookiesConfig -> CachePolicyCookiesConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CachePolicyCookiesConfig -> CachePolicyCookiesConfig -> Bool
$c/= :: CachePolicyCookiesConfig -> CachePolicyCookiesConfig -> Bool
== :: CachePolicyCookiesConfig -> CachePolicyCookiesConfig -> Bool
$c== :: CachePolicyCookiesConfig -> CachePolicyCookiesConfig -> Bool
Prelude.Eq, ReadPrec [CachePolicyCookiesConfig]
ReadPrec CachePolicyCookiesConfig
Int -> ReadS CachePolicyCookiesConfig
ReadS [CachePolicyCookiesConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CachePolicyCookiesConfig]
$creadListPrec :: ReadPrec [CachePolicyCookiesConfig]
readPrec :: ReadPrec CachePolicyCookiesConfig
$creadPrec :: ReadPrec CachePolicyCookiesConfig
readList :: ReadS [CachePolicyCookiesConfig]
$creadList :: ReadS [CachePolicyCookiesConfig]
readsPrec :: Int -> ReadS CachePolicyCookiesConfig
$creadsPrec :: Int -> ReadS CachePolicyCookiesConfig
Prelude.Read, Int -> CachePolicyCookiesConfig -> ShowS
[CachePolicyCookiesConfig] -> ShowS
CachePolicyCookiesConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CachePolicyCookiesConfig] -> ShowS
$cshowList :: [CachePolicyCookiesConfig] -> ShowS
show :: CachePolicyCookiesConfig -> String
$cshow :: CachePolicyCookiesConfig -> String
showsPrec :: Int -> CachePolicyCookiesConfig -> ShowS
$cshowsPrec :: Int -> CachePolicyCookiesConfig -> ShowS
Prelude.Show, forall x.
Rep CachePolicyCookiesConfig x -> CachePolicyCookiesConfig
forall x.
CachePolicyCookiesConfig -> Rep CachePolicyCookiesConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CachePolicyCookiesConfig x -> CachePolicyCookiesConfig
$cfrom :: forall x.
CachePolicyCookiesConfig -> Rep CachePolicyCookiesConfig x
Prelude.Generic)

-- |
-- Create a value of 'CachePolicyCookiesConfig' 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:
--
-- 'cookies', 'cachePolicyCookiesConfig_cookies' - Undocumented member.
--
-- 'cookieBehavior', 'cachePolicyCookiesConfig_cookieBehavior' - Determines whether any cookies in viewer requests are included in the
-- cache key and automatically included in requests that CloudFront sends
-- to the origin. Valid values are:
--
-- -   @none@ – Cookies in viewer requests are not included in the cache
--     key and are not automatically included in requests that CloudFront
--     sends to the origin. Even when this field is set to @none@, any
--     cookies that are listed in an @OriginRequestPolicy@ /are/ included
--     in origin requests.
--
-- -   @whitelist@ – The cookies in viewer requests that are listed in the
--     @CookieNames@ type are included in the cache key and automatically
--     included in requests that CloudFront sends to the origin.
--
-- -   @allExcept@ – All cookies in viewer requests that are /__not__/
--     listed in the @CookieNames@ type are included in the cache key and
--     automatically included in requests that CloudFront sends to the
--     origin.
--
-- -   @all@ – All cookies in viewer requests are included in the cache key
--     and are automatically included in requests that CloudFront sends to
--     the origin.
newCachePolicyCookiesConfig ::
  -- | 'cookieBehavior'
  CachePolicyCookieBehavior ->
  CachePolicyCookiesConfig
newCachePolicyCookiesConfig :: CachePolicyCookieBehavior -> CachePolicyCookiesConfig
newCachePolicyCookiesConfig CachePolicyCookieBehavior
pCookieBehavior_ =
  CachePolicyCookiesConfig'
    { $sel:cookies:CachePolicyCookiesConfig' :: Maybe CookieNames
cookies =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookieBehavior
cookieBehavior = CachePolicyCookieBehavior
pCookieBehavior_
    }

-- | Undocumented member.
cachePolicyCookiesConfig_cookies :: Lens.Lens' CachePolicyCookiesConfig (Prelude.Maybe CookieNames)
cachePolicyCookiesConfig_cookies :: Lens' CachePolicyCookiesConfig (Maybe CookieNames)
cachePolicyCookiesConfig_cookies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CachePolicyCookiesConfig' {Maybe CookieNames
cookies :: Maybe CookieNames
$sel:cookies:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> Maybe CookieNames
cookies} -> Maybe CookieNames
cookies) (\s :: CachePolicyCookiesConfig
s@CachePolicyCookiesConfig' {} Maybe CookieNames
a -> CachePolicyCookiesConfig
s {$sel:cookies:CachePolicyCookiesConfig' :: Maybe CookieNames
cookies = Maybe CookieNames
a} :: CachePolicyCookiesConfig)

-- | Determines whether any cookies in viewer requests are included in the
-- cache key and automatically included in requests that CloudFront sends
-- to the origin. Valid values are:
--
-- -   @none@ – Cookies in viewer requests are not included in the cache
--     key and are not automatically included in requests that CloudFront
--     sends to the origin. Even when this field is set to @none@, any
--     cookies that are listed in an @OriginRequestPolicy@ /are/ included
--     in origin requests.
--
-- -   @whitelist@ – The cookies in viewer requests that are listed in the
--     @CookieNames@ type are included in the cache key and automatically
--     included in requests that CloudFront sends to the origin.
--
-- -   @allExcept@ – All cookies in viewer requests that are /__not__/
--     listed in the @CookieNames@ type are included in the cache key and
--     automatically included in requests that CloudFront sends to the
--     origin.
--
-- -   @all@ – All cookies in viewer requests are included in the cache key
--     and are automatically included in requests that CloudFront sends to
--     the origin.
cachePolicyCookiesConfig_cookieBehavior :: Lens.Lens' CachePolicyCookiesConfig CachePolicyCookieBehavior
cachePolicyCookiesConfig_cookieBehavior :: Lens' CachePolicyCookiesConfig CachePolicyCookieBehavior
cachePolicyCookiesConfig_cookieBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CachePolicyCookiesConfig' {CachePolicyCookieBehavior
cookieBehavior :: CachePolicyCookieBehavior
$sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> CachePolicyCookieBehavior
cookieBehavior} -> CachePolicyCookieBehavior
cookieBehavior) (\s :: CachePolicyCookiesConfig
s@CachePolicyCookiesConfig' {} CachePolicyCookieBehavior
a -> CachePolicyCookiesConfig
s {$sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookieBehavior
cookieBehavior = CachePolicyCookieBehavior
a} :: CachePolicyCookiesConfig)

instance Data.FromXML CachePolicyCookiesConfig where
  parseXML :: [Node] -> Either String CachePolicyCookiesConfig
parseXML [Node]
x =
    Maybe CookieNames
-> CachePolicyCookieBehavior -> CachePolicyCookiesConfig
CachePolicyCookiesConfig'
      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
"Cookies")
      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
"CookieBehavior")

instance Prelude.Hashable CachePolicyCookiesConfig where
  hashWithSalt :: Int -> CachePolicyCookiesConfig -> Int
hashWithSalt Int
_salt CachePolicyCookiesConfig' {Maybe CookieNames
CachePolicyCookieBehavior
cookieBehavior :: CachePolicyCookieBehavior
cookies :: Maybe CookieNames
$sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> CachePolicyCookieBehavior
$sel:cookies:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> Maybe CookieNames
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CookieNames
cookies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CachePolicyCookieBehavior
cookieBehavior

instance Prelude.NFData CachePolicyCookiesConfig where
  rnf :: CachePolicyCookiesConfig -> ()
rnf CachePolicyCookiesConfig' {Maybe CookieNames
CachePolicyCookieBehavior
cookieBehavior :: CachePolicyCookieBehavior
cookies :: Maybe CookieNames
$sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> CachePolicyCookieBehavior
$sel:cookies:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> Maybe CookieNames
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CookieNames
cookies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CachePolicyCookieBehavior
cookieBehavior

instance Data.ToXML CachePolicyCookiesConfig where
  toXML :: CachePolicyCookiesConfig -> XML
toXML CachePolicyCookiesConfig' {Maybe CookieNames
CachePolicyCookieBehavior
cookieBehavior :: CachePolicyCookieBehavior
cookies :: Maybe CookieNames
$sel:cookieBehavior:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> CachePolicyCookieBehavior
$sel:cookies:CachePolicyCookiesConfig' :: CachePolicyCookiesConfig -> Maybe CookieNames
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"Cookies" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe CookieNames
cookies,
        Name
"CookieBehavior" forall a. ToXML a => Name -> a -> XML
Data.@= CachePolicyCookieBehavior
cookieBehavior
      ]