{-# 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.MediaTailor.Types.PlaybackConfiguration
-- 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.MediaTailor.Types.PlaybackConfiguration 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.AvailSuppression
import Amazonka.MediaTailor.Types.Bumper
import Amazonka.MediaTailor.Types.CdnConfiguration
import Amazonka.MediaTailor.Types.DashConfiguration
import Amazonka.MediaTailor.Types.HlsConfiguration
import Amazonka.MediaTailor.Types.LivePreRollConfiguration
import Amazonka.MediaTailor.Types.LogConfiguration
import Amazonka.MediaTailor.Types.ManifestProcessingRules
import qualified Amazonka.Prelude as Prelude

-- | A playback configuration. For information about MediaTailor
-- configurations, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/configurations.html Working with configurations in AWS Elemental MediaTailor>.
--
-- /See:/ 'newPlaybackConfiguration' smart constructor.
data PlaybackConfiguration = PlaybackConfiguration'
  { -- | The URL for the ad decision server (ADS). This includes the
    -- specification of static parameters and placeholders for dynamic
    -- parameters. AWS Elemental MediaTailor substitutes player-specific and
    -- session-specific parameters as needed when calling the ADS. Alternately,
    -- for testing you can provide a static VAST URL. The maximum length is
    -- 25,000 characters.
    PlaybackConfiguration -> Maybe Text
adDecisionServerUrl :: Prelude.Maybe Prelude.Text,
    -- | The configuration for avail suppression, also known as ad suppression.
    -- For more information about ad suppression, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Suppression>.
    PlaybackConfiguration -> Maybe AvailSuppression
availSuppression :: Prelude.Maybe AvailSuppression,
    -- | The configuration for bumpers. Bumpers are short audio or video clips
    -- that play at the start or before the end of an ad break. To learn more
    -- about bumpers, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/bumpers.html Bumpers>.
    PlaybackConfiguration -> Maybe Bumper
bumper :: Prelude.Maybe Bumper,
    -- | The configuration for using a content delivery network (CDN), like
    -- Amazon CloudFront, for content and ad segment management.
    PlaybackConfiguration -> Maybe CdnConfiguration
cdnConfiguration :: Prelude.Maybe CdnConfiguration,
    -- | The player parameters and aliases used as dynamic variables during
    -- session initialization. For more information, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/variables-domain.html Domain Variables>.
    PlaybackConfiguration -> Maybe (HashMap Text (HashMap Text Text))
configurationAliases :: Prelude.Maybe (Prelude.HashMap Prelude.Text (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The configuration for a DASH source.
    PlaybackConfiguration -> Maybe DashConfiguration
dashConfiguration :: Prelude.Maybe DashConfiguration,
    -- | The configuration for HLS content.
    PlaybackConfiguration -> Maybe HlsConfiguration
hlsConfiguration :: Prelude.Maybe HlsConfiguration,
    -- | The configuration for pre-roll ad insertion.
    PlaybackConfiguration -> Maybe LivePreRollConfiguration
livePreRollConfiguration :: Prelude.Maybe LivePreRollConfiguration,
    -- | The Amazon CloudWatch log settings for a playback configuration.
    PlaybackConfiguration -> Maybe LogConfiguration
logConfiguration :: Prelude.Maybe LogConfiguration,
    -- | The configuration for manifest processing rules. Manifest processing
    -- rules enable customization of the personalized manifests created by
    -- MediaTailor.
    PlaybackConfiguration -> Maybe ManifestProcessingRules
manifestProcessingRules :: Prelude.Maybe ManifestProcessingRules,
    -- | The identifier for the playback configuration.
    PlaybackConfiguration -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Defines the maximum duration of underfilled ad time (in seconds) allowed
    -- in an ad break. If the duration of underfilled ad time exceeds the
    -- personalization threshold, then the personalization of the ad break is
    -- abandoned and the underlying content is shown. This feature applies to
    -- /ad replacement/ in live and VOD streams, rather than ad insertion,
    -- because it relies on an underlying content stream. For more information
    -- about ad break behavior, including ad replacement and insertion, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Behavior in AWS Elemental MediaTailor>.
    PlaybackConfiguration -> Maybe Natural
personalizationThresholdSeconds :: Prelude.Maybe Prelude.Natural,
    -- | The Amazon Resource Name (ARN) for the playback configuration.
    PlaybackConfiguration -> Maybe Text
playbackConfigurationArn :: Prelude.Maybe Prelude.Text,
    -- | The URL that the player accesses to get a manifest from AWS Elemental
    -- MediaTailor.
    PlaybackConfiguration -> Maybe Text
playbackEndpointPrefix :: Prelude.Maybe Prelude.Text,
    -- | The URL that the player uses to initialize a session that uses
    -- client-side reporting.
    PlaybackConfiguration -> Maybe Text
sessionInitializationEndpointPrefix :: Prelude.Maybe Prelude.Text,
    -- | The URL for a video asset to transcode and use to fill in time that\'s
    -- not used by ads. AWS Elemental MediaTailor shows the slate to fill in
    -- gaps in media content. Configuring the slate is optional for non-VPAID
    -- playback configurations. For VPAID, the slate is required because
    -- MediaTailor provides it in the slots designated for dynamic ad content.
    -- The slate must be a high-quality asset that contains both audio and
    -- video.
    PlaybackConfiguration -> Maybe Text
slateAdUrl :: Prelude.Maybe Prelude.Text,
    -- | The tags to assign to the playback configuration. Tags are key-value
    -- pairs that you can associate with Amazon resources to help with
    -- organization, access control, and cost tracking. For more information,
    -- see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
    PlaybackConfiguration -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name that is used to associate this playback configuration with a
    -- custom transcode profile. This overrides the dynamic transcoding
    -- defaults of MediaTailor. Use this only if you have already set up custom
    -- profiles with the help of AWS Support.
    PlaybackConfiguration -> Maybe Text
transcodeProfileName :: Prelude.Maybe Prelude.Text,
    -- | The URL prefix for the parent manifest for the stream, minus the asset
    -- ID. The maximum length is 512 characters.
    PlaybackConfiguration -> Maybe Text
videoContentSourceUrl :: Prelude.Maybe Prelude.Text
  }
  deriving (PlaybackConfiguration -> PlaybackConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlaybackConfiguration -> PlaybackConfiguration -> Bool
$c/= :: PlaybackConfiguration -> PlaybackConfiguration -> Bool
== :: PlaybackConfiguration -> PlaybackConfiguration -> Bool
$c== :: PlaybackConfiguration -> PlaybackConfiguration -> Bool
Prelude.Eq, ReadPrec [PlaybackConfiguration]
ReadPrec PlaybackConfiguration
Int -> ReadS PlaybackConfiguration
ReadS [PlaybackConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PlaybackConfiguration]
$creadListPrec :: ReadPrec [PlaybackConfiguration]
readPrec :: ReadPrec PlaybackConfiguration
$creadPrec :: ReadPrec PlaybackConfiguration
readList :: ReadS [PlaybackConfiguration]
$creadList :: ReadS [PlaybackConfiguration]
readsPrec :: Int -> ReadS PlaybackConfiguration
$creadsPrec :: Int -> ReadS PlaybackConfiguration
Prelude.Read, Int -> PlaybackConfiguration -> ShowS
[PlaybackConfiguration] -> ShowS
PlaybackConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlaybackConfiguration] -> ShowS
$cshowList :: [PlaybackConfiguration] -> ShowS
show :: PlaybackConfiguration -> String
$cshow :: PlaybackConfiguration -> String
showsPrec :: Int -> PlaybackConfiguration -> ShowS
$cshowsPrec :: Int -> PlaybackConfiguration -> ShowS
Prelude.Show, forall x. Rep PlaybackConfiguration x -> PlaybackConfiguration
forall x. PlaybackConfiguration -> Rep PlaybackConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlaybackConfiguration x -> PlaybackConfiguration
$cfrom :: forall x. PlaybackConfiguration -> Rep PlaybackConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'PlaybackConfiguration' 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:
--
-- 'adDecisionServerUrl', 'playbackConfiguration_adDecisionServerUrl' - The URL for the ad decision server (ADS). This includes the
-- specification of static parameters and placeholders for dynamic
-- parameters. AWS Elemental MediaTailor substitutes player-specific and
-- session-specific parameters as needed when calling the ADS. Alternately,
-- for testing you can provide a static VAST URL. The maximum length is
-- 25,000 characters.
--
-- 'availSuppression', 'playbackConfiguration_availSuppression' - The configuration for avail suppression, also known as ad suppression.
-- For more information about ad suppression, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Suppression>.
--
-- 'bumper', 'playbackConfiguration_bumper' - The configuration for bumpers. Bumpers are short audio or video clips
-- that play at the start or before the end of an ad break. To learn more
-- about bumpers, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/bumpers.html Bumpers>.
--
-- 'cdnConfiguration', 'playbackConfiguration_cdnConfiguration' - The configuration for using a content delivery network (CDN), like
-- Amazon CloudFront, for content and ad segment management.
--
-- 'configurationAliases', 'playbackConfiguration_configurationAliases' - The player parameters and aliases used as dynamic variables during
-- session initialization. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/variables-domain.html Domain Variables>.
--
-- 'dashConfiguration', 'playbackConfiguration_dashConfiguration' - The configuration for a DASH source.
--
-- 'hlsConfiguration', 'playbackConfiguration_hlsConfiguration' - The configuration for HLS content.
--
-- 'livePreRollConfiguration', 'playbackConfiguration_livePreRollConfiguration' - The configuration for pre-roll ad insertion.
--
-- 'logConfiguration', 'playbackConfiguration_logConfiguration' - The Amazon CloudWatch log settings for a playback configuration.
--
-- 'manifestProcessingRules', 'playbackConfiguration_manifestProcessingRules' - The configuration for manifest processing rules. Manifest processing
-- rules enable customization of the personalized manifests created by
-- MediaTailor.
--
-- 'name', 'playbackConfiguration_name' - The identifier for the playback configuration.
--
-- 'personalizationThresholdSeconds', 'playbackConfiguration_personalizationThresholdSeconds' - Defines the maximum duration of underfilled ad time (in seconds) allowed
-- in an ad break. If the duration of underfilled ad time exceeds the
-- personalization threshold, then the personalization of the ad break is
-- abandoned and the underlying content is shown. This feature applies to
-- /ad replacement/ in live and VOD streams, rather than ad insertion,
-- because it relies on an underlying content stream. For more information
-- about ad break behavior, including ad replacement and insertion, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Behavior in AWS Elemental MediaTailor>.
--
-- 'playbackConfigurationArn', 'playbackConfiguration_playbackConfigurationArn' - The Amazon Resource Name (ARN) for the playback configuration.
--
-- 'playbackEndpointPrefix', 'playbackConfiguration_playbackEndpointPrefix' - The URL that the player accesses to get a manifest from AWS Elemental
-- MediaTailor.
--
-- 'sessionInitializationEndpointPrefix', 'playbackConfiguration_sessionInitializationEndpointPrefix' - The URL that the player uses to initialize a session that uses
-- client-side reporting.
--
-- 'slateAdUrl', 'playbackConfiguration_slateAdUrl' - The URL for a video asset to transcode and use to fill in time that\'s
-- not used by ads. AWS Elemental MediaTailor shows the slate to fill in
-- gaps in media content. Configuring the slate is optional for non-VPAID
-- playback configurations. For VPAID, the slate is required because
-- MediaTailor provides it in the slots designated for dynamic ad content.
-- The slate must be a high-quality asset that contains both audio and
-- video.
--
-- 'tags', 'playbackConfiguration_tags' - The tags to assign to the playback configuration. Tags are key-value
-- pairs that you can associate with Amazon resources to help with
-- organization, access control, and cost tracking. For more information,
-- see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
--
-- 'transcodeProfileName', 'playbackConfiguration_transcodeProfileName' - The name that is used to associate this playback configuration with a
-- custom transcode profile. This overrides the dynamic transcoding
-- defaults of MediaTailor. Use this only if you have already set up custom
-- profiles with the help of AWS Support.
--
-- 'videoContentSourceUrl', 'playbackConfiguration_videoContentSourceUrl' - The URL prefix for the parent manifest for the stream, minus the asset
-- ID. The maximum length is 512 characters.
newPlaybackConfiguration ::
  PlaybackConfiguration
newPlaybackConfiguration :: PlaybackConfiguration
newPlaybackConfiguration =
  PlaybackConfiguration'
    { $sel:adDecisionServerUrl:PlaybackConfiguration' :: Maybe Text
adDecisionServerUrl =
        forall a. Maybe a
Prelude.Nothing,
      $sel:availSuppression:PlaybackConfiguration' :: Maybe AvailSuppression
availSuppression = forall a. Maybe a
Prelude.Nothing,
      $sel:bumper:PlaybackConfiguration' :: Maybe Bumper
bumper = forall a. Maybe a
Prelude.Nothing,
      $sel:cdnConfiguration:PlaybackConfiguration' :: Maybe CdnConfiguration
cdnConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationAliases:PlaybackConfiguration' :: Maybe (HashMap Text (HashMap Text Text))
configurationAliases = forall a. Maybe a
Prelude.Nothing,
      $sel:dashConfiguration:PlaybackConfiguration' :: Maybe DashConfiguration
dashConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:hlsConfiguration:PlaybackConfiguration' :: Maybe HlsConfiguration
hlsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:livePreRollConfiguration:PlaybackConfiguration' :: Maybe LivePreRollConfiguration
livePreRollConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfiguration:PlaybackConfiguration' :: Maybe LogConfiguration
logConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:manifestProcessingRules:PlaybackConfiguration' :: Maybe ManifestProcessingRules
manifestProcessingRules = forall a. Maybe a
Prelude.Nothing,
      $sel:name:PlaybackConfiguration' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:personalizationThresholdSeconds:PlaybackConfiguration' :: Maybe Natural
personalizationThresholdSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:playbackConfigurationArn:PlaybackConfiguration' :: Maybe Text
playbackConfigurationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:playbackEndpointPrefix:PlaybackConfiguration' :: Maybe Text
playbackEndpointPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:sessionInitializationEndpointPrefix:PlaybackConfiguration' :: Maybe Text
sessionInitializationEndpointPrefix =
        forall a. Maybe a
Prelude.Nothing,
      $sel:slateAdUrl:PlaybackConfiguration' :: Maybe Text
slateAdUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:PlaybackConfiguration' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:transcodeProfileName:PlaybackConfiguration' :: Maybe Text
transcodeProfileName = forall a. Maybe a
Prelude.Nothing,
      $sel:videoContentSourceUrl:PlaybackConfiguration' :: Maybe Text
videoContentSourceUrl = forall a. Maybe a
Prelude.Nothing
    }

-- | The URL for the ad decision server (ADS). This includes the
-- specification of static parameters and placeholders for dynamic
-- parameters. AWS Elemental MediaTailor substitutes player-specific and
-- session-specific parameters as needed when calling the ADS. Alternately,
-- for testing you can provide a static VAST URL. The maximum length is
-- 25,000 characters.
playbackConfiguration_adDecisionServerUrl :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_adDecisionServerUrl :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_adDecisionServerUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
adDecisionServerUrl :: Maybe Text
$sel:adDecisionServerUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
adDecisionServerUrl} -> Maybe Text
adDecisionServerUrl) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:adDecisionServerUrl:PlaybackConfiguration' :: Maybe Text
adDecisionServerUrl = Maybe Text
a} :: PlaybackConfiguration)

-- | The configuration for avail suppression, also known as ad suppression.
-- For more information about ad suppression, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Suppression>.
playbackConfiguration_availSuppression :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe AvailSuppression)
playbackConfiguration_availSuppression :: Lens' PlaybackConfiguration (Maybe AvailSuppression)
playbackConfiguration_availSuppression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe AvailSuppression
availSuppression :: Maybe AvailSuppression
$sel:availSuppression:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe AvailSuppression
availSuppression} -> Maybe AvailSuppression
availSuppression) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe AvailSuppression
a -> PlaybackConfiguration
s {$sel:availSuppression:PlaybackConfiguration' :: Maybe AvailSuppression
availSuppression = Maybe AvailSuppression
a} :: PlaybackConfiguration)

-- | The configuration for bumpers. Bumpers are short audio or video clips
-- that play at the start or before the end of an ad break. To learn more
-- about bumpers, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/bumpers.html Bumpers>.
playbackConfiguration_bumper :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Bumper)
playbackConfiguration_bumper :: Lens' PlaybackConfiguration (Maybe Bumper)
playbackConfiguration_bumper = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Bumper
bumper :: Maybe Bumper
$sel:bumper:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Bumper
bumper} -> Maybe Bumper
bumper) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Bumper
a -> PlaybackConfiguration
s {$sel:bumper:PlaybackConfiguration' :: Maybe Bumper
bumper = Maybe Bumper
a} :: PlaybackConfiguration)

-- | The configuration for using a content delivery network (CDN), like
-- Amazon CloudFront, for content and ad segment management.
playbackConfiguration_cdnConfiguration :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe CdnConfiguration)
playbackConfiguration_cdnConfiguration :: Lens' PlaybackConfiguration (Maybe CdnConfiguration)
playbackConfiguration_cdnConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe CdnConfiguration
cdnConfiguration :: Maybe CdnConfiguration
$sel:cdnConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe CdnConfiguration
cdnConfiguration} -> Maybe CdnConfiguration
cdnConfiguration) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe CdnConfiguration
a -> PlaybackConfiguration
s {$sel:cdnConfiguration:PlaybackConfiguration' :: Maybe CdnConfiguration
cdnConfiguration = Maybe CdnConfiguration
a} :: PlaybackConfiguration)

-- | The player parameters and aliases used as dynamic variables during
-- session initialization. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/variables-domain.html Domain Variables>.
playbackConfiguration_configurationAliases :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe (Prelude.HashMap Prelude.Text (Prelude.HashMap Prelude.Text Prelude.Text)))
playbackConfiguration_configurationAliases :: Lens'
  PlaybackConfiguration (Maybe (HashMap Text (HashMap Text Text)))
playbackConfiguration_configurationAliases = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe (HashMap Text (HashMap Text Text))
configurationAliases :: Maybe (HashMap Text (HashMap Text Text))
$sel:configurationAliases:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text (HashMap Text Text))
configurationAliases} -> Maybe (HashMap Text (HashMap Text Text))
configurationAliases) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe (HashMap Text (HashMap Text Text))
a -> PlaybackConfiguration
s {$sel:configurationAliases:PlaybackConfiguration' :: Maybe (HashMap Text (HashMap Text Text))
configurationAliases = Maybe (HashMap Text (HashMap Text Text))
a} :: PlaybackConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The configuration for a DASH source.
playbackConfiguration_dashConfiguration :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe DashConfiguration)
playbackConfiguration_dashConfiguration :: Lens' PlaybackConfiguration (Maybe DashConfiguration)
playbackConfiguration_dashConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe DashConfiguration
dashConfiguration :: Maybe DashConfiguration
$sel:dashConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe DashConfiguration
dashConfiguration} -> Maybe DashConfiguration
dashConfiguration) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe DashConfiguration
a -> PlaybackConfiguration
s {$sel:dashConfiguration:PlaybackConfiguration' :: Maybe DashConfiguration
dashConfiguration = Maybe DashConfiguration
a} :: PlaybackConfiguration)

-- | The configuration for HLS content.
playbackConfiguration_hlsConfiguration :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe HlsConfiguration)
playbackConfiguration_hlsConfiguration :: Lens' PlaybackConfiguration (Maybe HlsConfiguration)
playbackConfiguration_hlsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe HlsConfiguration
hlsConfiguration :: Maybe HlsConfiguration
$sel:hlsConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe HlsConfiguration
hlsConfiguration} -> Maybe HlsConfiguration
hlsConfiguration) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe HlsConfiguration
a -> PlaybackConfiguration
s {$sel:hlsConfiguration:PlaybackConfiguration' :: Maybe HlsConfiguration
hlsConfiguration = Maybe HlsConfiguration
a} :: PlaybackConfiguration)

-- | The configuration for pre-roll ad insertion.
playbackConfiguration_livePreRollConfiguration :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe LivePreRollConfiguration)
playbackConfiguration_livePreRollConfiguration :: Lens' PlaybackConfiguration (Maybe LivePreRollConfiguration)
playbackConfiguration_livePreRollConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe LivePreRollConfiguration
livePreRollConfiguration :: Maybe LivePreRollConfiguration
$sel:livePreRollConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LivePreRollConfiguration
livePreRollConfiguration} -> Maybe LivePreRollConfiguration
livePreRollConfiguration) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe LivePreRollConfiguration
a -> PlaybackConfiguration
s {$sel:livePreRollConfiguration:PlaybackConfiguration' :: Maybe LivePreRollConfiguration
livePreRollConfiguration = Maybe LivePreRollConfiguration
a} :: PlaybackConfiguration)

-- | The Amazon CloudWatch log settings for a playback configuration.
playbackConfiguration_logConfiguration :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe LogConfiguration)
playbackConfiguration_logConfiguration :: Lens' PlaybackConfiguration (Maybe LogConfiguration)
playbackConfiguration_logConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe LogConfiguration
logConfiguration :: Maybe LogConfiguration
$sel:logConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LogConfiguration
logConfiguration} -> Maybe LogConfiguration
logConfiguration) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe LogConfiguration
a -> PlaybackConfiguration
s {$sel:logConfiguration:PlaybackConfiguration' :: Maybe LogConfiguration
logConfiguration = Maybe LogConfiguration
a} :: PlaybackConfiguration)

-- | The configuration for manifest processing rules. Manifest processing
-- rules enable customization of the personalized manifests created by
-- MediaTailor.
playbackConfiguration_manifestProcessingRules :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe ManifestProcessingRules)
playbackConfiguration_manifestProcessingRules :: Lens' PlaybackConfiguration (Maybe ManifestProcessingRules)
playbackConfiguration_manifestProcessingRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe ManifestProcessingRules
manifestProcessingRules :: Maybe ManifestProcessingRules
$sel:manifestProcessingRules:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe ManifestProcessingRules
manifestProcessingRules} -> Maybe ManifestProcessingRules
manifestProcessingRules) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe ManifestProcessingRules
a -> PlaybackConfiguration
s {$sel:manifestProcessingRules:PlaybackConfiguration' :: Maybe ManifestProcessingRules
manifestProcessingRules = Maybe ManifestProcessingRules
a} :: PlaybackConfiguration)

-- | The identifier for the playback configuration.
playbackConfiguration_name :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_name :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
name :: Maybe Text
$sel:name:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
name} -> Maybe Text
name) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:name:PlaybackConfiguration' :: Maybe Text
name = Maybe Text
a} :: PlaybackConfiguration)

-- | Defines the maximum duration of underfilled ad time (in seconds) allowed
-- in an ad break. If the duration of underfilled ad time exceeds the
-- personalization threshold, then the personalization of the ad break is
-- abandoned and the underlying content is shown. This feature applies to
-- /ad replacement/ in live and VOD streams, rather than ad insertion,
-- because it relies on an underlying content stream. For more information
-- about ad break behavior, including ad replacement and insertion, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/ad-behavior.html Ad Behavior in AWS Elemental MediaTailor>.
playbackConfiguration_personalizationThresholdSeconds :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Natural)
playbackConfiguration_personalizationThresholdSeconds :: Lens' PlaybackConfiguration (Maybe Natural)
playbackConfiguration_personalizationThresholdSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Natural
personalizationThresholdSeconds :: Maybe Natural
$sel:personalizationThresholdSeconds:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Natural
personalizationThresholdSeconds} -> Maybe Natural
personalizationThresholdSeconds) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Natural
a -> PlaybackConfiguration
s {$sel:personalizationThresholdSeconds:PlaybackConfiguration' :: Maybe Natural
personalizationThresholdSeconds = Maybe Natural
a} :: PlaybackConfiguration)

-- | The Amazon Resource Name (ARN) for the playback configuration.
playbackConfiguration_playbackConfigurationArn :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_playbackConfigurationArn :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_playbackConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
playbackConfigurationArn :: Maybe Text
$sel:playbackConfigurationArn:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
playbackConfigurationArn} -> Maybe Text
playbackConfigurationArn) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:playbackConfigurationArn:PlaybackConfiguration' :: Maybe Text
playbackConfigurationArn = Maybe Text
a} :: PlaybackConfiguration)

-- | The URL that the player accesses to get a manifest from AWS Elemental
-- MediaTailor.
playbackConfiguration_playbackEndpointPrefix :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_playbackEndpointPrefix :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_playbackEndpointPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
playbackEndpointPrefix :: Maybe Text
$sel:playbackEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
playbackEndpointPrefix} -> Maybe Text
playbackEndpointPrefix) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:playbackEndpointPrefix:PlaybackConfiguration' :: Maybe Text
playbackEndpointPrefix = Maybe Text
a} :: PlaybackConfiguration)

-- | The URL that the player uses to initialize a session that uses
-- client-side reporting.
playbackConfiguration_sessionInitializationEndpointPrefix :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_sessionInitializationEndpointPrefix :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_sessionInitializationEndpointPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
sessionInitializationEndpointPrefix :: Maybe Text
$sel:sessionInitializationEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
sessionInitializationEndpointPrefix} -> Maybe Text
sessionInitializationEndpointPrefix) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:sessionInitializationEndpointPrefix:PlaybackConfiguration' :: Maybe Text
sessionInitializationEndpointPrefix = Maybe Text
a} :: PlaybackConfiguration)

-- | The URL for a video asset to transcode and use to fill in time that\'s
-- not used by ads. AWS Elemental MediaTailor shows the slate to fill in
-- gaps in media content. Configuring the slate is optional for non-VPAID
-- playback configurations. For VPAID, the slate is required because
-- MediaTailor provides it in the slots designated for dynamic ad content.
-- The slate must be a high-quality asset that contains both audio and
-- video.
playbackConfiguration_slateAdUrl :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_slateAdUrl :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_slateAdUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
slateAdUrl :: Maybe Text
$sel:slateAdUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
slateAdUrl} -> Maybe Text
slateAdUrl) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:slateAdUrl:PlaybackConfiguration' :: Maybe Text
slateAdUrl = Maybe Text
a} :: PlaybackConfiguration)

-- | The tags to assign to the playback configuration. Tags are key-value
-- pairs that you can associate with Amazon resources to help with
-- organization, access control, and cost tracking. For more information,
-- see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
playbackConfiguration_tags :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
playbackConfiguration_tags :: Lens' PlaybackConfiguration (Maybe (HashMap Text Text))
playbackConfiguration_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe (HashMap Text Text)
a -> PlaybackConfiguration
s {$sel:tags:PlaybackConfiguration' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: PlaybackConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name that is used to associate this playback configuration with a
-- custom transcode profile. This overrides the dynamic transcoding
-- defaults of MediaTailor. Use this only if you have already set up custom
-- profiles with the help of AWS Support.
playbackConfiguration_transcodeProfileName :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_transcodeProfileName :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_transcodeProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
transcodeProfileName :: Maybe Text
$sel:transcodeProfileName:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
transcodeProfileName} -> Maybe Text
transcodeProfileName) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:transcodeProfileName:PlaybackConfiguration' :: Maybe Text
transcodeProfileName = Maybe Text
a} :: PlaybackConfiguration)

-- | The URL prefix for the parent manifest for the stream, minus the asset
-- ID. The maximum length is 512 characters.
playbackConfiguration_videoContentSourceUrl :: Lens.Lens' PlaybackConfiguration (Prelude.Maybe Prelude.Text)
playbackConfiguration_videoContentSourceUrl :: Lens' PlaybackConfiguration (Maybe Text)
playbackConfiguration_videoContentSourceUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlaybackConfiguration' {Maybe Text
videoContentSourceUrl :: Maybe Text
$sel:videoContentSourceUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
videoContentSourceUrl} -> Maybe Text
videoContentSourceUrl) (\s :: PlaybackConfiguration
s@PlaybackConfiguration' {} Maybe Text
a -> PlaybackConfiguration
s {$sel:videoContentSourceUrl:PlaybackConfiguration' :: Maybe Text
videoContentSourceUrl = Maybe Text
a} :: PlaybackConfiguration)

instance Data.FromJSON PlaybackConfiguration where
  parseJSON :: Value -> Parser PlaybackConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"PlaybackConfiguration"
      ( \Object
x ->
          Maybe Text
-> Maybe AvailSuppression
-> Maybe Bumper
-> Maybe CdnConfiguration
-> Maybe (HashMap Text (HashMap Text Text))
-> Maybe DashConfiguration
-> Maybe HlsConfiguration
-> Maybe LivePreRollConfiguration
-> Maybe LogConfiguration
-> Maybe ManifestProcessingRules
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe Text
-> PlaybackConfiguration
PlaybackConfiguration'
            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
"AdDecisionServerUrl")
            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
"AvailSuppression")
            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
"Bumper")
            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
"CdnConfiguration")
            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
"ConfigurationAliases"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"DashConfiguration")
            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
"HlsConfiguration")
            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
"LivePreRollConfiguration")
            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
"LogConfiguration")
            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
"ManifestProcessingRules")
            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
"Name")
            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
"PersonalizationThresholdSeconds")
            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
"PlaybackConfigurationArn")
            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
"PlaybackEndpointPrefix")
            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
"SessionInitializationEndpointPrefix")
            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
"SlateAdUrl")
            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
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"TranscodeProfileName")
            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
"VideoContentSourceUrl")
      )

instance Prelude.Hashable PlaybackConfiguration where
  hashWithSalt :: Int -> PlaybackConfiguration -> Int
hashWithSalt Int
_salt PlaybackConfiguration' {Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (HashMap Text (HashMap Text Text))
Maybe Bumper
Maybe CdnConfiguration
Maybe HlsConfiguration
Maybe LivePreRollConfiguration
Maybe LogConfiguration
Maybe ManifestProcessingRules
Maybe AvailSuppression
Maybe DashConfiguration
videoContentSourceUrl :: Maybe Text
transcodeProfileName :: Maybe Text
tags :: Maybe (HashMap Text Text)
slateAdUrl :: Maybe Text
sessionInitializationEndpointPrefix :: Maybe Text
playbackEndpointPrefix :: Maybe Text
playbackConfigurationArn :: Maybe Text
personalizationThresholdSeconds :: Maybe Natural
name :: Maybe Text
manifestProcessingRules :: Maybe ManifestProcessingRules
logConfiguration :: Maybe LogConfiguration
livePreRollConfiguration :: Maybe LivePreRollConfiguration
hlsConfiguration :: Maybe HlsConfiguration
dashConfiguration :: Maybe DashConfiguration
configurationAliases :: Maybe (HashMap Text (HashMap Text Text))
cdnConfiguration :: Maybe CdnConfiguration
bumper :: Maybe Bumper
availSuppression :: Maybe AvailSuppression
adDecisionServerUrl :: Maybe Text
$sel:videoContentSourceUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:transcodeProfileName:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:tags:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text Text)
$sel:slateAdUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:sessionInitializationEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:playbackEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:playbackConfigurationArn:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:personalizationThresholdSeconds:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Natural
$sel:name:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:manifestProcessingRules:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe ManifestProcessingRules
$sel:logConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LogConfiguration
$sel:livePreRollConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LivePreRollConfiguration
$sel:hlsConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe HlsConfiguration
$sel:dashConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe DashConfiguration
$sel:configurationAliases:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text (HashMap Text Text))
$sel:cdnConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe CdnConfiguration
$sel:bumper:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Bumper
$sel:availSuppression:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe AvailSuppression
$sel:adDecisionServerUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
adDecisionServerUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AvailSuppression
availSuppression
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bumper
bumper
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CdnConfiguration
cdnConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text (HashMap Text Text))
configurationAliases
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashConfiguration
dashConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsConfiguration
hlsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LivePreRollConfiguration
livePreRollConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogConfiguration
logConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ManifestProcessingRules
manifestProcessingRules
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
personalizationThresholdSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
playbackConfigurationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
playbackEndpointPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sessionInitializationEndpointPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
slateAdUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transcodeProfileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
videoContentSourceUrl

instance Prelude.NFData PlaybackConfiguration where
  rnf :: PlaybackConfiguration -> ()
rnf PlaybackConfiguration' {Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (HashMap Text (HashMap Text Text))
Maybe Bumper
Maybe CdnConfiguration
Maybe HlsConfiguration
Maybe LivePreRollConfiguration
Maybe LogConfiguration
Maybe ManifestProcessingRules
Maybe AvailSuppression
Maybe DashConfiguration
videoContentSourceUrl :: Maybe Text
transcodeProfileName :: Maybe Text
tags :: Maybe (HashMap Text Text)
slateAdUrl :: Maybe Text
sessionInitializationEndpointPrefix :: Maybe Text
playbackEndpointPrefix :: Maybe Text
playbackConfigurationArn :: Maybe Text
personalizationThresholdSeconds :: Maybe Natural
name :: Maybe Text
manifestProcessingRules :: Maybe ManifestProcessingRules
logConfiguration :: Maybe LogConfiguration
livePreRollConfiguration :: Maybe LivePreRollConfiguration
hlsConfiguration :: Maybe HlsConfiguration
dashConfiguration :: Maybe DashConfiguration
configurationAliases :: Maybe (HashMap Text (HashMap Text Text))
cdnConfiguration :: Maybe CdnConfiguration
bumper :: Maybe Bumper
availSuppression :: Maybe AvailSuppression
adDecisionServerUrl :: Maybe Text
$sel:videoContentSourceUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:transcodeProfileName:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:tags:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text Text)
$sel:slateAdUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:sessionInitializationEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:playbackEndpointPrefix:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:playbackConfigurationArn:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:personalizationThresholdSeconds:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Natural
$sel:name:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
$sel:manifestProcessingRules:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe ManifestProcessingRules
$sel:logConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LogConfiguration
$sel:livePreRollConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe LivePreRollConfiguration
$sel:hlsConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe HlsConfiguration
$sel:dashConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe DashConfiguration
$sel:configurationAliases:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe (HashMap Text (HashMap Text Text))
$sel:cdnConfiguration:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe CdnConfiguration
$sel:bumper:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Bumper
$sel:availSuppression:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe AvailSuppression
$sel:adDecisionServerUrl:PlaybackConfiguration' :: PlaybackConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
adDecisionServerUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AvailSuppression
availSuppression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bumper
bumper
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CdnConfiguration
cdnConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text (HashMap Text Text))
configurationAliases
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashConfiguration
dashConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsConfiguration
hlsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LivePreRollConfiguration
livePreRollConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogConfiguration
logConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ManifestProcessingRules
manifestProcessingRules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
personalizationThresholdSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
playbackConfigurationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
playbackEndpointPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sessionInitializationEndpointPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
slateAdUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transcodeProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
videoContentSourceUrl