{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.MediaTailor.ConfigureLogsForPlaybackConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Amazon CloudWatch log settings for a playback configuration.
module Amazonka.MediaTailor.ConfigureLogsForPlaybackConfiguration
  ( -- * Creating a Request
    ConfigureLogsForPlaybackConfiguration (..),
    newConfigureLogsForPlaybackConfiguration,

    -- * Request Lenses
    configureLogsForPlaybackConfiguration_percentEnabled,
    configureLogsForPlaybackConfiguration_playbackConfigurationName,

    -- * Destructuring the Response
    ConfigureLogsForPlaybackConfigurationResponse (..),
    newConfigureLogsForPlaybackConfigurationResponse,

    -- * Response Lenses
    configureLogsForPlaybackConfigurationResponse_playbackConfigurationName,
    configureLogsForPlaybackConfigurationResponse_httpStatus,
    configureLogsForPlaybackConfigurationResponse_percentEnabled,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaTailor.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Configures Amazon CloudWatch log settings for a playback configuration.
--
-- /See:/ 'newConfigureLogsForPlaybackConfiguration' smart constructor.
data ConfigureLogsForPlaybackConfiguration = ConfigureLogsForPlaybackConfiguration'
  { -- | The percentage of session logs that MediaTailor sends to your Cloudwatch
    -- Logs account. For example, if your playback configuration has 1000
    -- sessions and percentEnabled is set to @60@, MediaTailor sends logs for
    -- 600 of the sessions to CloudWatch Logs. MediaTailor decides at random
    -- which of the playback configuration sessions to send logs for. If you
    -- want to view logs for a specific session, you can use the
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/debug-log-mode.html debug log mode>.
    --
    -- Valid values: @0@ - @100@
    ConfigureLogsForPlaybackConfiguration -> Int
percentEnabled :: Prelude.Int,
    -- | The name of the playback configuration.
    ConfigureLogsForPlaybackConfiguration -> Text
playbackConfigurationName :: Prelude.Text
  }
  deriving (ConfigureLogsForPlaybackConfiguration
-> ConfigureLogsForPlaybackConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigureLogsForPlaybackConfiguration
-> ConfigureLogsForPlaybackConfiguration -> Bool
$c/= :: ConfigureLogsForPlaybackConfiguration
-> ConfigureLogsForPlaybackConfiguration -> Bool
== :: ConfigureLogsForPlaybackConfiguration
-> ConfigureLogsForPlaybackConfiguration -> Bool
$c== :: ConfigureLogsForPlaybackConfiguration
-> ConfigureLogsForPlaybackConfiguration -> Bool
Prelude.Eq, ReadPrec [ConfigureLogsForPlaybackConfiguration]
ReadPrec ConfigureLogsForPlaybackConfiguration
Int -> ReadS ConfigureLogsForPlaybackConfiguration
ReadS [ConfigureLogsForPlaybackConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigureLogsForPlaybackConfiguration]
$creadListPrec :: ReadPrec [ConfigureLogsForPlaybackConfiguration]
readPrec :: ReadPrec ConfigureLogsForPlaybackConfiguration
$creadPrec :: ReadPrec ConfigureLogsForPlaybackConfiguration
readList :: ReadS [ConfigureLogsForPlaybackConfiguration]
$creadList :: ReadS [ConfigureLogsForPlaybackConfiguration]
readsPrec :: Int -> ReadS ConfigureLogsForPlaybackConfiguration
$creadsPrec :: Int -> ReadS ConfigureLogsForPlaybackConfiguration
Prelude.Read, Int -> ConfigureLogsForPlaybackConfiguration -> ShowS
[ConfigureLogsForPlaybackConfiguration] -> ShowS
ConfigureLogsForPlaybackConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigureLogsForPlaybackConfiguration] -> ShowS
$cshowList :: [ConfigureLogsForPlaybackConfiguration] -> ShowS
show :: ConfigureLogsForPlaybackConfiguration -> String
$cshow :: ConfigureLogsForPlaybackConfiguration -> String
showsPrec :: Int -> ConfigureLogsForPlaybackConfiguration -> ShowS
$cshowsPrec :: Int -> ConfigureLogsForPlaybackConfiguration -> ShowS
Prelude.Show, forall x.
Rep ConfigureLogsForPlaybackConfiguration x
-> ConfigureLogsForPlaybackConfiguration
forall x.
ConfigureLogsForPlaybackConfiguration
-> Rep ConfigureLogsForPlaybackConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConfigureLogsForPlaybackConfiguration x
-> ConfigureLogsForPlaybackConfiguration
$cfrom :: forall x.
ConfigureLogsForPlaybackConfiguration
-> Rep ConfigureLogsForPlaybackConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'ConfigureLogsForPlaybackConfiguration' 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:
--
-- 'percentEnabled', 'configureLogsForPlaybackConfiguration_percentEnabled' - The percentage of session logs that MediaTailor sends to your Cloudwatch
-- Logs account. For example, if your playback configuration has 1000
-- sessions and percentEnabled is set to @60@, MediaTailor sends logs for
-- 600 of the sessions to CloudWatch Logs. MediaTailor decides at random
-- which of the playback configuration sessions to send logs for. If you
-- want to view logs for a specific session, you can use the
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/debug-log-mode.html debug log mode>.
--
-- Valid values: @0@ - @100@
--
-- 'playbackConfigurationName', 'configureLogsForPlaybackConfiguration_playbackConfigurationName' - The name of the playback configuration.
newConfigureLogsForPlaybackConfiguration ::
  -- | 'percentEnabled'
  Prelude.Int ->
  -- | 'playbackConfigurationName'
  Prelude.Text ->
  ConfigureLogsForPlaybackConfiguration
newConfigureLogsForPlaybackConfiguration :: Int -> Text -> ConfigureLogsForPlaybackConfiguration
newConfigureLogsForPlaybackConfiguration
  Int
pPercentEnabled_
  Text
pPlaybackConfigurationName_ =
    ConfigureLogsForPlaybackConfiguration'
      { $sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: Int
percentEnabled =
          Int
pPercentEnabled_,
        $sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: Text
playbackConfigurationName =
          Text
pPlaybackConfigurationName_
      }

-- | The percentage of session logs that MediaTailor sends to your Cloudwatch
-- Logs account. For example, if your playback configuration has 1000
-- sessions and percentEnabled is set to @60@, MediaTailor sends logs for
-- 600 of the sessions to CloudWatch Logs. MediaTailor decides at random
-- which of the playback configuration sessions to send logs for. If you
-- want to view logs for a specific session, you can use the
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/debug-log-mode.html debug log mode>.
--
-- Valid values: @0@ - @100@
configureLogsForPlaybackConfiguration_percentEnabled :: Lens.Lens' ConfigureLogsForPlaybackConfiguration Prelude.Int
configureLogsForPlaybackConfiguration_percentEnabled :: Lens' ConfigureLogsForPlaybackConfiguration Int
configureLogsForPlaybackConfiguration_percentEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigureLogsForPlaybackConfiguration' {Int
percentEnabled :: Int
$sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Int
percentEnabled} -> Int
percentEnabled) (\s :: ConfigureLogsForPlaybackConfiguration
s@ConfigureLogsForPlaybackConfiguration' {} Int
a -> ConfigureLogsForPlaybackConfiguration
s {$sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: Int
percentEnabled = Int
a} :: ConfigureLogsForPlaybackConfiguration)

-- | The name of the playback configuration.
configureLogsForPlaybackConfiguration_playbackConfigurationName :: Lens.Lens' ConfigureLogsForPlaybackConfiguration Prelude.Text
configureLogsForPlaybackConfiguration_playbackConfigurationName :: Lens' ConfigureLogsForPlaybackConfiguration Text
configureLogsForPlaybackConfiguration_playbackConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigureLogsForPlaybackConfiguration' {Text
playbackConfigurationName :: Text
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Text
playbackConfigurationName} -> Text
playbackConfigurationName) (\s :: ConfigureLogsForPlaybackConfiguration
s@ConfigureLogsForPlaybackConfiguration' {} Text
a -> ConfigureLogsForPlaybackConfiguration
s {$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: Text
playbackConfigurationName = Text
a} :: ConfigureLogsForPlaybackConfiguration)

instance
  Core.AWSRequest
    ConfigureLogsForPlaybackConfiguration
  where
  type
    AWSResponse
      ConfigureLogsForPlaybackConfiguration =
      ConfigureLogsForPlaybackConfigurationResponse
  request :: (Service -> Service)
-> ConfigureLogsForPlaybackConfiguration
-> Request ConfigureLogsForPlaybackConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ConfigureLogsForPlaybackConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse ConfigureLogsForPlaybackConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Int -> Int -> ConfigureLogsForPlaybackConfigurationResponse
ConfigureLogsForPlaybackConfigurationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PlaybackConfigurationName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"PercentEnabled")
      )

instance
  Prelude.Hashable
    ConfigureLogsForPlaybackConfiguration
  where
  hashWithSalt :: Int -> ConfigureLogsForPlaybackConfiguration -> Int
hashWithSalt
    Int
_salt
    ConfigureLogsForPlaybackConfiguration' {Int
Text
playbackConfigurationName :: Text
percentEnabled :: Int
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Text
$sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Int
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
percentEnabled
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
playbackConfigurationName

instance
  Prelude.NFData
    ConfigureLogsForPlaybackConfiguration
  where
  rnf :: ConfigureLogsForPlaybackConfiguration -> ()
rnf ConfigureLogsForPlaybackConfiguration' {Int
Text
playbackConfigurationName :: Text
percentEnabled :: Int
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Text
$sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
percentEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
playbackConfigurationName

instance
  Data.ToHeaders
    ConfigureLogsForPlaybackConfiguration
  where
  toHeaders :: ConfigureLogsForPlaybackConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    ConfigureLogsForPlaybackConfiguration
  where
  toJSON :: ConfigureLogsForPlaybackConfiguration -> Value
toJSON ConfigureLogsForPlaybackConfiguration' {Int
Text
playbackConfigurationName :: Text
percentEnabled :: Int
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Text
$sel:percentEnabled:ConfigureLogsForPlaybackConfiguration' :: ConfigureLogsForPlaybackConfiguration -> Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"PercentEnabled" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Int
percentEnabled),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"PlaybackConfigurationName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
playbackConfigurationName
              )
          ]
      )

instance
  Data.ToPath
    ConfigureLogsForPlaybackConfiguration
  where
  toPath :: ConfigureLogsForPlaybackConfiguration -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/configureLogs/playbackConfiguration"

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

-- | /See:/ 'newConfigureLogsForPlaybackConfigurationResponse' smart constructor.
data ConfigureLogsForPlaybackConfigurationResponse = ConfigureLogsForPlaybackConfigurationResponse'
  { -- | The name of the playback configuration.
    ConfigureLogsForPlaybackConfigurationResponse -> Maybe Text
playbackConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ConfigureLogsForPlaybackConfigurationResponse -> Int
httpStatus :: Prelude.Int,
    -- | The percentage of session logs that MediaTailor sends to your Cloudwatch
    -- Logs account.
    ConfigureLogsForPlaybackConfigurationResponse -> Int
percentEnabled :: Prelude.Int
  }
  deriving (ConfigureLogsForPlaybackConfigurationResponse
-> ConfigureLogsForPlaybackConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigureLogsForPlaybackConfigurationResponse
-> ConfigureLogsForPlaybackConfigurationResponse -> Bool
$c/= :: ConfigureLogsForPlaybackConfigurationResponse
-> ConfigureLogsForPlaybackConfigurationResponse -> Bool
== :: ConfigureLogsForPlaybackConfigurationResponse
-> ConfigureLogsForPlaybackConfigurationResponse -> Bool
$c== :: ConfigureLogsForPlaybackConfigurationResponse
-> ConfigureLogsForPlaybackConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [ConfigureLogsForPlaybackConfigurationResponse]
ReadPrec ConfigureLogsForPlaybackConfigurationResponse
Int -> ReadS ConfigureLogsForPlaybackConfigurationResponse
ReadS [ConfigureLogsForPlaybackConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigureLogsForPlaybackConfigurationResponse]
$creadListPrec :: ReadPrec [ConfigureLogsForPlaybackConfigurationResponse]
readPrec :: ReadPrec ConfigureLogsForPlaybackConfigurationResponse
$creadPrec :: ReadPrec ConfigureLogsForPlaybackConfigurationResponse
readList :: ReadS [ConfigureLogsForPlaybackConfigurationResponse]
$creadList :: ReadS [ConfigureLogsForPlaybackConfigurationResponse]
readsPrec :: Int -> ReadS ConfigureLogsForPlaybackConfigurationResponse
$creadsPrec :: Int -> ReadS ConfigureLogsForPlaybackConfigurationResponse
Prelude.Read, Int -> ConfigureLogsForPlaybackConfigurationResponse -> ShowS
[ConfigureLogsForPlaybackConfigurationResponse] -> ShowS
ConfigureLogsForPlaybackConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigureLogsForPlaybackConfigurationResponse] -> ShowS
$cshowList :: [ConfigureLogsForPlaybackConfigurationResponse] -> ShowS
show :: ConfigureLogsForPlaybackConfigurationResponse -> String
$cshow :: ConfigureLogsForPlaybackConfigurationResponse -> String
showsPrec :: Int -> ConfigureLogsForPlaybackConfigurationResponse -> ShowS
$cshowsPrec :: Int -> ConfigureLogsForPlaybackConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep ConfigureLogsForPlaybackConfigurationResponse x
-> ConfigureLogsForPlaybackConfigurationResponse
forall x.
ConfigureLogsForPlaybackConfigurationResponse
-> Rep ConfigureLogsForPlaybackConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConfigureLogsForPlaybackConfigurationResponse x
-> ConfigureLogsForPlaybackConfigurationResponse
$cfrom :: forall x.
ConfigureLogsForPlaybackConfigurationResponse
-> Rep ConfigureLogsForPlaybackConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'ConfigureLogsForPlaybackConfigurationResponse' 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:
--
-- 'playbackConfigurationName', 'configureLogsForPlaybackConfigurationResponse_playbackConfigurationName' - The name of the playback configuration.
--
-- 'httpStatus', 'configureLogsForPlaybackConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'percentEnabled', 'configureLogsForPlaybackConfigurationResponse_percentEnabled' - The percentage of session logs that MediaTailor sends to your Cloudwatch
-- Logs account.
newConfigureLogsForPlaybackConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'percentEnabled'
  Prelude.Int ->
  ConfigureLogsForPlaybackConfigurationResponse
newConfigureLogsForPlaybackConfigurationResponse :: Int -> Int -> ConfigureLogsForPlaybackConfigurationResponse
newConfigureLogsForPlaybackConfigurationResponse
  Int
pHttpStatus_
  Int
pPercentEnabled_ =
    ConfigureLogsForPlaybackConfigurationResponse'
      { $sel:playbackConfigurationName:ConfigureLogsForPlaybackConfigurationResponse' :: Maybe Text
playbackConfigurationName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ConfigureLogsForPlaybackConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:percentEnabled:ConfigureLogsForPlaybackConfigurationResponse' :: Int
percentEnabled =
          Int
pPercentEnabled_
      }

-- | The name of the playback configuration.
configureLogsForPlaybackConfigurationResponse_playbackConfigurationName :: Lens.Lens' ConfigureLogsForPlaybackConfigurationResponse (Prelude.Maybe Prelude.Text)
configureLogsForPlaybackConfigurationResponse_playbackConfigurationName :: Lens' ConfigureLogsForPlaybackConfigurationResponse (Maybe Text)
configureLogsForPlaybackConfigurationResponse_playbackConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigureLogsForPlaybackConfigurationResponse' {Maybe Text
playbackConfigurationName :: Maybe Text
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfigurationResponse' :: ConfigureLogsForPlaybackConfigurationResponse -> Maybe Text
playbackConfigurationName} -> Maybe Text
playbackConfigurationName) (\s :: ConfigureLogsForPlaybackConfigurationResponse
s@ConfigureLogsForPlaybackConfigurationResponse' {} Maybe Text
a -> ConfigureLogsForPlaybackConfigurationResponse
s {$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfigurationResponse' :: Maybe Text
playbackConfigurationName = Maybe Text
a} :: ConfigureLogsForPlaybackConfigurationResponse)

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

-- | The percentage of session logs that MediaTailor sends to your Cloudwatch
-- Logs account.
configureLogsForPlaybackConfigurationResponse_percentEnabled :: Lens.Lens' ConfigureLogsForPlaybackConfigurationResponse Prelude.Int
configureLogsForPlaybackConfigurationResponse_percentEnabled :: Lens' ConfigureLogsForPlaybackConfigurationResponse Int
configureLogsForPlaybackConfigurationResponse_percentEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigureLogsForPlaybackConfigurationResponse' {Int
percentEnabled :: Int
$sel:percentEnabled:ConfigureLogsForPlaybackConfigurationResponse' :: ConfigureLogsForPlaybackConfigurationResponse -> Int
percentEnabled} -> Int
percentEnabled) (\s :: ConfigureLogsForPlaybackConfigurationResponse
s@ConfigureLogsForPlaybackConfigurationResponse' {} Int
a -> ConfigureLogsForPlaybackConfigurationResponse
s {$sel:percentEnabled:ConfigureLogsForPlaybackConfigurationResponse' :: Int
percentEnabled = Int
a} :: ConfigureLogsForPlaybackConfigurationResponse)

instance
  Prelude.NFData
    ConfigureLogsForPlaybackConfigurationResponse
  where
  rnf :: ConfigureLogsForPlaybackConfigurationResponse -> ()
rnf
    ConfigureLogsForPlaybackConfigurationResponse' {Int
Maybe Text
percentEnabled :: Int
httpStatus :: Int
playbackConfigurationName :: Maybe Text
$sel:percentEnabled:ConfigureLogsForPlaybackConfigurationResponse' :: ConfigureLogsForPlaybackConfigurationResponse -> Int
$sel:httpStatus:ConfigureLogsForPlaybackConfigurationResponse' :: ConfigureLogsForPlaybackConfigurationResponse -> Int
$sel:playbackConfigurationName:ConfigureLogsForPlaybackConfigurationResponse' :: ConfigureLogsForPlaybackConfigurationResponse -> Maybe Text
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
playbackConfigurationName
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
percentEnabled