{-# 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.APIGateway.Types.MethodSetting
-- 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.APIGateway.Types.MethodSetting where

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

-- | Specifies the method setting properties.
--
-- /See:/ 'newMethodSetting' smart constructor.
data MethodSetting = MethodSetting'
  { -- | Specifies whether the cached responses are encrypted. The PATCH path for
    -- this setting is @\/{method_setting_key}\/caching\/dataEncrypted@, and
    -- the value is a Boolean.
    MethodSetting -> Maybe Bool
cacheDataEncrypted :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the time to live (TTL), in seconds, for cached responses. The
    -- higher the TTL, the longer the response will be cached. The PATCH path
    -- for this setting is @\/{method_setting_key}\/caching\/ttlInSeconds@, and
    -- the value is an integer.
    MethodSetting -> Maybe Int
cacheTtlInSeconds :: Prelude.Maybe Prelude.Int,
    -- | Specifies whether responses should be cached and returned for requests.
    -- A cache cluster must be enabled on the stage for responses to be cached.
    -- The PATCH path for this setting is
    -- @\/{method_setting_key}\/caching\/enabled@, and the value is a Boolean.
    MethodSetting -> Maybe Bool
cachingEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether data trace logging is enabled for this method, which
    -- affects the log entries pushed to Amazon CloudWatch Logs. The PATCH path
    -- for this setting is @\/{method_setting_key}\/logging\/dataTrace@, and
    -- the value is a Boolean.
    MethodSetting -> Maybe Bool
dataTraceEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the logging level for this method, which affects the log
    -- entries pushed to Amazon CloudWatch Logs. The PATCH path for this
    -- setting is @\/{method_setting_key}\/logging\/loglevel@, and the
    -- available levels are @OFF@, @ERROR@, and @INFO@. Choose @ERROR@ to write
    -- only error-level entries to CloudWatch Logs, or choose @INFO@ to include
    -- all @ERROR@ events as well as extra informational events.
    MethodSetting -> Maybe Text
loggingLevel :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether Amazon CloudWatch metrics are enabled for this method.
    -- The PATCH path for this setting is
    -- @\/{method_setting_key}\/metrics\/enabled@, and the value is a Boolean.
    MethodSetting -> Maybe Bool
metricsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether authorization is required for a cache invalidation
    -- request. The PATCH path for this setting is
    -- @\/{method_setting_key}\/caching\/requireAuthorizationForCacheControl@,
    -- and the value is a Boolean.
    MethodSetting -> Maybe Bool
requireAuthorizationForCacheControl :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the throttling burst limit. The PATCH path for this setting is
    -- @\/{method_setting_key}\/throttling\/burstLimit@, and the value is an
    -- integer.
    MethodSetting -> Maybe Int
throttlingBurstLimit :: Prelude.Maybe Prelude.Int,
    -- | Specifies the throttling rate limit. The PATCH path for this setting is
    -- @\/{method_setting_key}\/throttling\/rateLimit@, and the value is a
    -- double.
    MethodSetting -> Maybe Double
throttlingRateLimit :: Prelude.Maybe Prelude.Double,
    -- | Specifies how to handle unauthorized requests for cache invalidation.
    -- The PATCH path for this setting is
    -- @\/{method_setting_key}\/caching\/unauthorizedCacheControlHeaderStrategy@,
    -- and the available values are @FAIL_WITH_403@,
    -- @SUCCEED_WITH_RESPONSE_HEADER@, @SUCCEED_WITHOUT_RESPONSE_HEADER@.
    MethodSetting -> Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy :: Prelude.Maybe UnauthorizedCacheControlHeaderStrategy
  }
  deriving (MethodSetting -> MethodSetting -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodSetting -> MethodSetting -> Bool
$c/= :: MethodSetting -> MethodSetting -> Bool
== :: MethodSetting -> MethodSetting -> Bool
$c== :: MethodSetting -> MethodSetting -> Bool
Prelude.Eq, ReadPrec [MethodSetting]
ReadPrec MethodSetting
Int -> ReadS MethodSetting
ReadS [MethodSetting]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodSetting]
$creadListPrec :: ReadPrec [MethodSetting]
readPrec :: ReadPrec MethodSetting
$creadPrec :: ReadPrec MethodSetting
readList :: ReadS [MethodSetting]
$creadList :: ReadS [MethodSetting]
readsPrec :: Int -> ReadS MethodSetting
$creadsPrec :: Int -> ReadS MethodSetting
Prelude.Read, Int -> MethodSetting -> ShowS
[MethodSetting] -> ShowS
MethodSetting -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MethodSetting] -> ShowS
$cshowList :: [MethodSetting] -> ShowS
show :: MethodSetting -> String
$cshow :: MethodSetting -> String
showsPrec :: Int -> MethodSetting -> ShowS
$cshowsPrec :: Int -> MethodSetting -> ShowS
Prelude.Show, forall x. Rep MethodSetting x -> MethodSetting
forall x. MethodSetting -> Rep MethodSetting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MethodSetting x -> MethodSetting
$cfrom :: forall x. MethodSetting -> Rep MethodSetting x
Prelude.Generic)

-- |
-- Create a value of 'MethodSetting' 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:
--
-- 'cacheDataEncrypted', 'methodSetting_cacheDataEncrypted' - Specifies whether the cached responses are encrypted. The PATCH path for
-- this setting is @\/{method_setting_key}\/caching\/dataEncrypted@, and
-- the value is a Boolean.
--
-- 'cacheTtlInSeconds', 'methodSetting_cacheTtlInSeconds' - Specifies the time to live (TTL), in seconds, for cached responses. The
-- higher the TTL, the longer the response will be cached. The PATCH path
-- for this setting is @\/{method_setting_key}\/caching\/ttlInSeconds@, and
-- the value is an integer.
--
-- 'cachingEnabled', 'methodSetting_cachingEnabled' - Specifies whether responses should be cached and returned for requests.
-- A cache cluster must be enabled on the stage for responses to be cached.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/enabled@, and the value is a Boolean.
--
-- 'dataTraceEnabled', 'methodSetting_dataTraceEnabled' - Specifies whether data trace logging is enabled for this method, which
-- affects the log entries pushed to Amazon CloudWatch Logs. The PATCH path
-- for this setting is @\/{method_setting_key}\/logging\/dataTrace@, and
-- the value is a Boolean.
--
-- 'loggingLevel', 'methodSetting_loggingLevel' - Specifies the logging level for this method, which affects the log
-- entries pushed to Amazon CloudWatch Logs. The PATCH path for this
-- setting is @\/{method_setting_key}\/logging\/loglevel@, and the
-- available levels are @OFF@, @ERROR@, and @INFO@. Choose @ERROR@ to write
-- only error-level entries to CloudWatch Logs, or choose @INFO@ to include
-- all @ERROR@ events as well as extra informational events.
--
-- 'metricsEnabled', 'methodSetting_metricsEnabled' - Specifies whether Amazon CloudWatch metrics are enabled for this method.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/metrics\/enabled@, and the value is a Boolean.
--
-- 'requireAuthorizationForCacheControl', 'methodSetting_requireAuthorizationForCacheControl' - Specifies whether authorization is required for a cache invalidation
-- request. The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/requireAuthorizationForCacheControl@,
-- and the value is a Boolean.
--
-- 'throttlingBurstLimit', 'methodSetting_throttlingBurstLimit' - Specifies the throttling burst limit. The PATCH path for this setting is
-- @\/{method_setting_key}\/throttling\/burstLimit@, and the value is an
-- integer.
--
-- 'throttlingRateLimit', 'methodSetting_throttlingRateLimit' - Specifies the throttling rate limit. The PATCH path for this setting is
-- @\/{method_setting_key}\/throttling\/rateLimit@, and the value is a
-- double.
--
-- 'unauthorizedCacheControlHeaderStrategy', 'methodSetting_unauthorizedCacheControlHeaderStrategy' - Specifies how to handle unauthorized requests for cache invalidation.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/unauthorizedCacheControlHeaderStrategy@,
-- and the available values are @FAIL_WITH_403@,
-- @SUCCEED_WITH_RESPONSE_HEADER@, @SUCCEED_WITHOUT_RESPONSE_HEADER@.
newMethodSetting ::
  MethodSetting
newMethodSetting :: MethodSetting
newMethodSetting =
  MethodSetting'
    { $sel:cacheDataEncrypted:MethodSetting' :: Maybe Bool
cacheDataEncrypted =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cacheTtlInSeconds:MethodSetting' :: Maybe Int
cacheTtlInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:cachingEnabled:MethodSetting' :: Maybe Bool
cachingEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:dataTraceEnabled:MethodSetting' :: Maybe Bool
dataTraceEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingLevel:MethodSetting' :: Maybe Text
loggingLevel = forall a. Maybe a
Prelude.Nothing,
      $sel:metricsEnabled:MethodSetting' :: Maybe Bool
metricsEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:requireAuthorizationForCacheControl:MethodSetting' :: Maybe Bool
requireAuthorizationForCacheControl =
        forall a. Maybe a
Prelude.Nothing,
      $sel:throttlingBurstLimit:MethodSetting' :: Maybe Int
throttlingBurstLimit = forall a. Maybe a
Prelude.Nothing,
      $sel:throttlingRateLimit:MethodSetting' :: Maybe Double
throttlingRateLimit = forall a. Maybe a
Prelude.Nothing,
      $sel:unauthorizedCacheControlHeaderStrategy:MethodSetting' :: Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy =
        forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies whether the cached responses are encrypted. The PATCH path for
-- this setting is @\/{method_setting_key}\/caching\/dataEncrypted@, and
-- the value is a Boolean.
methodSetting_cacheDataEncrypted :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Bool)
methodSetting_cacheDataEncrypted :: Lens' MethodSetting (Maybe Bool)
methodSetting_cacheDataEncrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Bool
cacheDataEncrypted :: Maybe Bool
$sel:cacheDataEncrypted:MethodSetting' :: MethodSetting -> Maybe Bool
cacheDataEncrypted} -> Maybe Bool
cacheDataEncrypted) (\s :: MethodSetting
s@MethodSetting' {} Maybe Bool
a -> MethodSetting
s {$sel:cacheDataEncrypted:MethodSetting' :: Maybe Bool
cacheDataEncrypted = Maybe Bool
a} :: MethodSetting)

-- | Specifies the time to live (TTL), in seconds, for cached responses. The
-- higher the TTL, the longer the response will be cached. The PATCH path
-- for this setting is @\/{method_setting_key}\/caching\/ttlInSeconds@, and
-- the value is an integer.
methodSetting_cacheTtlInSeconds :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Int)
methodSetting_cacheTtlInSeconds :: Lens' MethodSetting (Maybe Int)
methodSetting_cacheTtlInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Int
cacheTtlInSeconds :: Maybe Int
$sel:cacheTtlInSeconds:MethodSetting' :: MethodSetting -> Maybe Int
cacheTtlInSeconds} -> Maybe Int
cacheTtlInSeconds) (\s :: MethodSetting
s@MethodSetting' {} Maybe Int
a -> MethodSetting
s {$sel:cacheTtlInSeconds:MethodSetting' :: Maybe Int
cacheTtlInSeconds = Maybe Int
a} :: MethodSetting)

-- | Specifies whether responses should be cached and returned for requests.
-- A cache cluster must be enabled on the stage for responses to be cached.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/enabled@, and the value is a Boolean.
methodSetting_cachingEnabled :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Bool)
methodSetting_cachingEnabled :: Lens' MethodSetting (Maybe Bool)
methodSetting_cachingEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Bool
cachingEnabled :: Maybe Bool
$sel:cachingEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
cachingEnabled} -> Maybe Bool
cachingEnabled) (\s :: MethodSetting
s@MethodSetting' {} Maybe Bool
a -> MethodSetting
s {$sel:cachingEnabled:MethodSetting' :: Maybe Bool
cachingEnabled = Maybe Bool
a} :: MethodSetting)

-- | Specifies whether data trace logging is enabled for this method, which
-- affects the log entries pushed to Amazon CloudWatch Logs. The PATCH path
-- for this setting is @\/{method_setting_key}\/logging\/dataTrace@, and
-- the value is a Boolean.
methodSetting_dataTraceEnabled :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Bool)
methodSetting_dataTraceEnabled :: Lens' MethodSetting (Maybe Bool)
methodSetting_dataTraceEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Bool
dataTraceEnabled :: Maybe Bool
$sel:dataTraceEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
dataTraceEnabled} -> Maybe Bool
dataTraceEnabled) (\s :: MethodSetting
s@MethodSetting' {} Maybe Bool
a -> MethodSetting
s {$sel:dataTraceEnabled:MethodSetting' :: Maybe Bool
dataTraceEnabled = Maybe Bool
a} :: MethodSetting)

-- | Specifies the logging level for this method, which affects the log
-- entries pushed to Amazon CloudWatch Logs. The PATCH path for this
-- setting is @\/{method_setting_key}\/logging\/loglevel@, and the
-- available levels are @OFF@, @ERROR@, and @INFO@. Choose @ERROR@ to write
-- only error-level entries to CloudWatch Logs, or choose @INFO@ to include
-- all @ERROR@ events as well as extra informational events.
methodSetting_loggingLevel :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Text)
methodSetting_loggingLevel :: Lens' MethodSetting (Maybe Text)
methodSetting_loggingLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Text
loggingLevel :: Maybe Text
$sel:loggingLevel:MethodSetting' :: MethodSetting -> Maybe Text
loggingLevel} -> Maybe Text
loggingLevel) (\s :: MethodSetting
s@MethodSetting' {} Maybe Text
a -> MethodSetting
s {$sel:loggingLevel:MethodSetting' :: Maybe Text
loggingLevel = Maybe Text
a} :: MethodSetting)

-- | Specifies whether Amazon CloudWatch metrics are enabled for this method.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/metrics\/enabled@, and the value is a Boolean.
methodSetting_metricsEnabled :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Bool)
methodSetting_metricsEnabled :: Lens' MethodSetting (Maybe Bool)
methodSetting_metricsEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Bool
metricsEnabled :: Maybe Bool
$sel:metricsEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
metricsEnabled} -> Maybe Bool
metricsEnabled) (\s :: MethodSetting
s@MethodSetting' {} Maybe Bool
a -> MethodSetting
s {$sel:metricsEnabled:MethodSetting' :: Maybe Bool
metricsEnabled = Maybe Bool
a} :: MethodSetting)

-- | Specifies whether authorization is required for a cache invalidation
-- request. The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/requireAuthorizationForCacheControl@,
-- and the value is a Boolean.
methodSetting_requireAuthorizationForCacheControl :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Bool)
methodSetting_requireAuthorizationForCacheControl :: Lens' MethodSetting (Maybe Bool)
methodSetting_requireAuthorizationForCacheControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Bool
requireAuthorizationForCacheControl :: Maybe Bool
$sel:requireAuthorizationForCacheControl:MethodSetting' :: MethodSetting -> Maybe Bool
requireAuthorizationForCacheControl} -> Maybe Bool
requireAuthorizationForCacheControl) (\s :: MethodSetting
s@MethodSetting' {} Maybe Bool
a -> MethodSetting
s {$sel:requireAuthorizationForCacheControl:MethodSetting' :: Maybe Bool
requireAuthorizationForCacheControl = Maybe Bool
a} :: MethodSetting)

-- | Specifies the throttling burst limit. The PATCH path for this setting is
-- @\/{method_setting_key}\/throttling\/burstLimit@, and the value is an
-- integer.
methodSetting_throttlingBurstLimit :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Int)
methodSetting_throttlingBurstLimit :: Lens' MethodSetting (Maybe Int)
methodSetting_throttlingBurstLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Int
throttlingBurstLimit :: Maybe Int
$sel:throttlingBurstLimit:MethodSetting' :: MethodSetting -> Maybe Int
throttlingBurstLimit} -> Maybe Int
throttlingBurstLimit) (\s :: MethodSetting
s@MethodSetting' {} Maybe Int
a -> MethodSetting
s {$sel:throttlingBurstLimit:MethodSetting' :: Maybe Int
throttlingBurstLimit = Maybe Int
a} :: MethodSetting)

-- | Specifies the throttling rate limit. The PATCH path for this setting is
-- @\/{method_setting_key}\/throttling\/rateLimit@, and the value is a
-- double.
methodSetting_throttlingRateLimit :: Lens.Lens' MethodSetting (Prelude.Maybe Prelude.Double)
methodSetting_throttlingRateLimit :: Lens' MethodSetting (Maybe Double)
methodSetting_throttlingRateLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe Double
throttlingRateLimit :: Maybe Double
$sel:throttlingRateLimit:MethodSetting' :: MethodSetting -> Maybe Double
throttlingRateLimit} -> Maybe Double
throttlingRateLimit) (\s :: MethodSetting
s@MethodSetting' {} Maybe Double
a -> MethodSetting
s {$sel:throttlingRateLimit:MethodSetting' :: Maybe Double
throttlingRateLimit = Maybe Double
a} :: MethodSetting)

-- | Specifies how to handle unauthorized requests for cache invalidation.
-- The PATCH path for this setting is
-- @\/{method_setting_key}\/caching\/unauthorizedCacheControlHeaderStrategy@,
-- and the available values are @FAIL_WITH_403@,
-- @SUCCEED_WITH_RESPONSE_HEADER@, @SUCCEED_WITHOUT_RESPONSE_HEADER@.
methodSetting_unauthorizedCacheControlHeaderStrategy :: Lens.Lens' MethodSetting (Prelude.Maybe UnauthorizedCacheControlHeaderStrategy)
methodSetting_unauthorizedCacheControlHeaderStrategy :: Lens' MethodSetting (Maybe UnauthorizedCacheControlHeaderStrategy)
methodSetting_unauthorizedCacheControlHeaderStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MethodSetting' {Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy :: Maybe UnauthorizedCacheControlHeaderStrategy
$sel:unauthorizedCacheControlHeaderStrategy:MethodSetting' :: MethodSetting -> Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy} -> Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy) (\s :: MethodSetting
s@MethodSetting' {} Maybe UnauthorizedCacheControlHeaderStrategy
a -> MethodSetting
s {$sel:unauthorizedCacheControlHeaderStrategy:MethodSetting' :: Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy = Maybe UnauthorizedCacheControlHeaderStrategy
a} :: MethodSetting)

instance Data.FromJSON MethodSetting where
  parseJSON :: Value -> Parser MethodSetting
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MethodSetting"
      ( \Object
x ->
          Maybe Bool
-> Maybe Int
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Double
-> Maybe UnauthorizedCacheControlHeaderStrategy
-> MethodSetting
MethodSetting'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"cacheDataEncrypted")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"cacheTtlInSeconds")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"cachingEnabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"dataTraceEnabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"loggingLevel")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"metricsEnabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"requireAuthorizationForCacheControl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"throttlingBurstLimit")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"throttlingRateLimit")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"unauthorizedCacheControlHeaderStrategy"
                        )
      )

instance Prelude.Hashable MethodSetting where
  hashWithSalt :: Int -> MethodSetting -> Int
hashWithSalt Int
_salt MethodSetting' {Maybe Bool
Maybe Double
Maybe Int
Maybe Text
Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy :: Maybe UnauthorizedCacheControlHeaderStrategy
throttlingRateLimit :: Maybe Double
throttlingBurstLimit :: Maybe Int
requireAuthorizationForCacheControl :: Maybe Bool
metricsEnabled :: Maybe Bool
loggingLevel :: Maybe Text
dataTraceEnabled :: Maybe Bool
cachingEnabled :: Maybe Bool
cacheTtlInSeconds :: Maybe Int
cacheDataEncrypted :: Maybe Bool
$sel:unauthorizedCacheControlHeaderStrategy:MethodSetting' :: MethodSetting -> Maybe UnauthorizedCacheControlHeaderStrategy
$sel:throttlingRateLimit:MethodSetting' :: MethodSetting -> Maybe Double
$sel:throttlingBurstLimit:MethodSetting' :: MethodSetting -> Maybe Int
$sel:requireAuthorizationForCacheControl:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:metricsEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:loggingLevel:MethodSetting' :: MethodSetting -> Maybe Text
$sel:dataTraceEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:cachingEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:cacheTtlInSeconds:MethodSetting' :: MethodSetting -> Maybe Int
$sel:cacheDataEncrypted:MethodSetting' :: MethodSetting -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
cacheDataEncrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
cacheTtlInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
cachingEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dataTraceEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
loggingLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
metricsEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
requireAuthorizationForCacheControl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
throttlingBurstLimit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
throttlingRateLimit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy

instance Prelude.NFData MethodSetting where
  rnf :: MethodSetting -> ()
rnf MethodSetting' {Maybe Bool
Maybe Double
Maybe Int
Maybe Text
Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy :: Maybe UnauthorizedCacheControlHeaderStrategy
throttlingRateLimit :: Maybe Double
throttlingBurstLimit :: Maybe Int
requireAuthorizationForCacheControl :: Maybe Bool
metricsEnabled :: Maybe Bool
loggingLevel :: Maybe Text
dataTraceEnabled :: Maybe Bool
cachingEnabled :: Maybe Bool
cacheTtlInSeconds :: Maybe Int
cacheDataEncrypted :: Maybe Bool
$sel:unauthorizedCacheControlHeaderStrategy:MethodSetting' :: MethodSetting -> Maybe UnauthorizedCacheControlHeaderStrategy
$sel:throttlingRateLimit:MethodSetting' :: MethodSetting -> Maybe Double
$sel:throttlingBurstLimit:MethodSetting' :: MethodSetting -> Maybe Int
$sel:requireAuthorizationForCacheControl:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:metricsEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:loggingLevel:MethodSetting' :: MethodSetting -> Maybe Text
$sel:dataTraceEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:cachingEnabled:MethodSetting' :: MethodSetting -> Maybe Bool
$sel:cacheTtlInSeconds:MethodSetting' :: MethodSetting -> Maybe Int
$sel:cacheDataEncrypted:MethodSetting' :: MethodSetting -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
cacheDataEncrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
cacheTtlInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
cachingEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dataTraceEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
loggingLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
metricsEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
requireAuthorizationForCacheControl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
throttlingBurstLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
throttlingRateLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UnauthorizedCacheControlHeaderStrategy
unauthorizedCacheControlHeaderStrategy