{-# 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 #-}
module Amazonka.MediaLive.Types.HlsGroupSettings where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types.CaptionLanguageMapping
import Amazonka.MediaLive.Types.HlsAdMarkers
import Amazonka.MediaLive.Types.HlsCaptionLanguageSetting
import Amazonka.MediaLive.Types.HlsCdnSettings
import Amazonka.MediaLive.Types.HlsClientCache
import Amazonka.MediaLive.Types.HlsCodecSpecification
import Amazonka.MediaLive.Types.HlsDirectoryStructure
import Amazonka.MediaLive.Types.HlsDiscontinuityTags
import Amazonka.MediaLive.Types.HlsEncryptionType
import Amazonka.MediaLive.Types.HlsId3SegmentTaggingState
import Amazonka.MediaLive.Types.HlsIncompleteSegmentBehavior
import Amazonka.MediaLive.Types.HlsIvInManifest
import Amazonka.MediaLive.Types.HlsIvSource
import Amazonka.MediaLive.Types.HlsManifestCompression
import Amazonka.MediaLive.Types.HlsManifestDurationFormat
import Amazonka.MediaLive.Types.HlsMode
import Amazonka.MediaLive.Types.HlsOutputSelection
import Amazonka.MediaLive.Types.HlsProgramDateTime
import Amazonka.MediaLive.Types.HlsProgramDateTimeClock
import Amazonka.MediaLive.Types.HlsRedundantManifest
import Amazonka.MediaLive.Types.HlsSegmentationMode
import Amazonka.MediaLive.Types.HlsStreamInfResolution
import Amazonka.MediaLive.Types.HlsTimedMetadataId3Frame
import Amazonka.MediaLive.Types.HlsTsFileMode
import Amazonka.MediaLive.Types.IFrameOnlyPlaylistType
import Amazonka.MediaLive.Types.InputLossActionForHlsOut
import Amazonka.MediaLive.Types.KeyProviderSettings
import Amazonka.MediaLive.Types.OutputLocationRef
import qualified Amazonka.Prelude as Prelude
data HlsGroupSettings = HlsGroupSettings'
{
HlsGroupSettings -> Maybe [HlsAdMarkers]
adMarkers :: Prelude.Maybe [HlsAdMarkers],
HlsGroupSettings -> Maybe Text
baseUrlContent :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe Text
baseUrlContent1 :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe Text
baseUrlManifest :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe Text
baseUrlManifest1 :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe [CaptionLanguageMapping]
captionLanguageMappings :: Prelude.Maybe [CaptionLanguageMapping],
HlsGroupSettings -> Maybe HlsCaptionLanguageSetting
captionLanguageSetting :: Prelude.Maybe HlsCaptionLanguageSetting,
HlsGroupSettings -> Maybe HlsClientCache
clientCache :: Prelude.Maybe HlsClientCache,
HlsGroupSettings -> Maybe HlsCodecSpecification
codecSpecification :: Prelude.Maybe HlsCodecSpecification,
HlsGroupSettings -> Maybe Text
constantIv :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe HlsDirectoryStructure
directoryStructure :: Prelude.Maybe HlsDirectoryStructure,
HlsGroupSettings -> Maybe HlsDiscontinuityTags
discontinuityTags :: Prelude.Maybe HlsDiscontinuityTags,
HlsGroupSettings -> Maybe HlsEncryptionType
encryptionType :: Prelude.Maybe HlsEncryptionType,
HlsGroupSettings -> Maybe HlsCdnSettings
hlsCdnSettings :: Prelude.Maybe HlsCdnSettings,
HlsGroupSettings -> Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging :: Prelude.Maybe HlsId3SegmentTaggingState,
HlsGroupSettings -> Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists :: Prelude.Maybe IFrameOnlyPlaylistType,
HlsGroupSettings -> Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior :: Prelude.Maybe HlsIncompleteSegmentBehavior,
HlsGroupSettings -> Maybe Natural
indexNSegments :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe InputLossActionForHlsOut
inputLossAction :: Prelude.Maybe InputLossActionForHlsOut,
HlsGroupSettings -> Maybe HlsIvInManifest
ivInManifest :: Prelude.Maybe HlsIvInManifest,
HlsGroupSettings -> Maybe HlsIvSource
ivSource :: Prelude.Maybe HlsIvSource,
HlsGroupSettings -> Maybe Natural
keepSegments :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe Text
keyFormat :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe Text
keyFormatVersions :: Prelude.Maybe Prelude.Text,
HlsGroupSettings -> Maybe KeyProviderSettings
keyProviderSettings :: Prelude.Maybe KeyProviderSettings,
HlsGroupSettings -> Maybe HlsManifestCompression
manifestCompression :: Prelude.Maybe HlsManifestCompression,
HlsGroupSettings -> Maybe HlsManifestDurationFormat
manifestDurationFormat :: Prelude.Maybe HlsManifestDurationFormat,
HlsGroupSettings -> Maybe Natural
minSegmentLength :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe HlsMode
mode :: Prelude.Maybe HlsMode,
HlsGroupSettings -> Maybe HlsOutputSelection
outputSelection :: Prelude.Maybe HlsOutputSelection,
HlsGroupSettings -> Maybe HlsProgramDateTime
programDateTime :: Prelude.Maybe HlsProgramDateTime,
HlsGroupSettings -> Maybe HlsProgramDateTimeClock
programDateTimeClock :: Prelude.Maybe HlsProgramDateTimeClock,
HlsGroupSettings -> Maybe Natural
programDateTimePeriod :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe HlsRedundantManifest
redundantManifest :: Prelude.Maybe HlsRedundantManifest,
HlsGroupSettings -> Maybe Natural
segmentLength :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe HlsSegmentationMode
segmentationMode :: Prelude.Maybe HlsSegmentationMode,
HlsGroupSettings -> Maybe Natural
segmentsPerSubdirectory :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe HlsStreamInfResolution
streamInfResolution :: Prelude.Maybe HlsStreamInfResolution,
HlsGroupSettings -> Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame :: Prelude.Maybe HlsTimedMetadataId3Frame,
HlsGroupSettings -> Maybe Natural
timedMetadataId3Period :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe Natural
timestampDeltaMilliseconds :: Prelude.Maybe Prelude.Natural,
HlsGroupSettings -> Maybe HlsTsFileMode
tsFileMode :: Prelude.Maybe HlsTsFileMode,
HlsGroupSettings -> OutputLocationRef
destination :: OutputLocationRef
}
deriving (HlsGroupSettings -> HlsGroupSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HlsGroupSettings -> HlsGroupSettings -> Bool
$c/= :: HlsGroupSettings -> HlsGroupSettings -> Bool
== :: HlsGroupSettings -> HlsGroupSettings -> Bool
$c== :: HlsGroupSettings -> HlsGroupSettings -> Bool
Prelude.Eq, ReadPrec [HlsGroupSettings]
ReadPrec HlsGroupSettings
Int -> ReadS HlsGroupSettings
ReadS [HlsGroupSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HlsGroupSettings]
$creadListPrec :: ReadPrec [HlsGroupSettings]
readPrec :: ReadPrec HlsGroupSettings
$creadPrec :: ReadPrec HlsGroupSettings
readList :: ReadS [HlsGroupSettings]
$creadList :: ReadS [HlsGroupSettings]
readsPrec :: Int -> ReadS HlsGroupSettings
$creadsPrec :: Int -> ReadS HlsGroupSettings
Prelude.Read, Int -> HlsGroupSettings -> ShowS
[HlsGroupSettings] -> ShowS
HlsGroupSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HlsGroupSettings] -> ShowS
$cshowList :: [HlsGroupSettings] -> ShowS
show :: HlsGroupSettings -> String
$cshow :: HlsGroupSettings -> String
showsPrec :: Int -> HlsGroupSettings -> ShowS
$cshowsPrec :: Int -> HlsGroupSettings -> ShowS
Prelude.Show, forall x. Rep HlsGroupSettings x -> HlsGroupSettings
forall x. HlsGroupSettings -> Rep HlsGroupSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HlsGroupSettings x -> HlsGroupSettings
$cfrom :: forall x. HlsGroupSettings -> Rep HlsGroupSettings x
Prelude.Generic)
newHlsGroupSettings ::
OutputLocationRef ->
HlsGroupSettings
newHlsGroupSettings :: OutputLocationRef -> HlsGroupSettings
newHlsGroupSettings OutputLocationRef
pDestination_ =
HlsGroupSettings'
{ $sel:adMarkers:HlsGroupSettings' :: Maybe [HlsAdMarkers]
adMarkers = forall a. Maybe a
Prelude.Nothing,
$sel:baseUrlContent:HlsGroupSettings' :: Maybe Text
baseUrlContent = forall a. Maybe a
Prelude.Nothing,
$sel:baseUrlContent1:HlsGroupSettings' :: Maybe Text
baseUrlContent1 = forall a. Maybe a
Prelude.Nothing,
$sel:baseUrlManifest:HlsGroupSettings' :: Maybe Text
baseUrlManifest = forall a. Maybe a
Prelude.Nothing,
$sel:baseUrlManifest1:HlsGroupSettings' :: Maybe Text
baseUrlManifest1 = forall a. Maybe a
Prelude.Nothing,
$sel:captionLanguageMappings:HlsGroupSettings' :: Maybe [CaptionLanguageMapping]
captionLanguageMappings = forall a. Maybe a
Prelude.Nothing,
$sel:captionLanguageSetting:HlsGroupSettings' :: Maybe HlsCaptionLanguageSetting
captionLanguageSetting = forall a. Maybe a
Prelude.Nothing,
$sel:clientCache:HlsGroupSettings' :: Maybe HlsClientCache
clientCache = forall a. Maybe a
Prelude.Nothing,
$sel:codecSpecification:HlsGroupSettings' :: Maybe HlsCodecSpecification
codecSpecification = forall a. Maybe a
Prelude.Nothing,
$sel:constantIv:HlsGroupSettings' :: Maybe Text
constantIv = forall a. Maybe a
Prelude.Nothing,
$sel:directoryStructure:HlsGroupSettings' :: Maybe HlsDirectoryStructure
directoryStructure = forall a. Maybe a
Prelude.Nothing,
$sel:discontinuityTags:HlsGroupSettings' :: Maybe HlsDiscontinuityTags
discontinuityTags = forall a. Maybe a
Prelude.Nothing,
$sel:encryptionType:HlsGroupSettings' :: Maybe HlsEncryptionType
encryptionType = forall a. Maybe a
Prelude.Nothing,
$sel:hlsCdnSettings:HlsGroupSettings' :: Maybe HlsCdnSettings
hlsCdnSettings = forall a. Maybe a
Prelude.Nothing,
$sel:hlsId3SegmentTagging:HlsGroupSettings' :: Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging = forall a. Maybe a
Prelude.Nothing,
$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists = forall a. Maybe a
Prelude.Nothing,
$sel:incompleteSegmentBehavior:HlsGroupSettings' :: Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior = forall a. Maybe a
Prelude.Nothing,
$sel:indexNSegments:HlsGroupSettings' :: Maybe Natural
indexNSegments = forall a. Maybe a
Prelude.Nothing,
$sel:inputLossAction:HlsGroupSettings' :: Maybe InputLossActionForHlsOut
inputLossAction = forall a. Maybe a
Prelude.Nothing,
$sel:ivInManifest:HlsGroupSettings' :: Maybe HlsIvInManifest
ivInManifest = forall a. Maybe a
Prelude.Nothing,
$sel:ivSource:HlsGroupSettings' :: Maybe HlsIvSource
ivSource = forall a. Maybe a
Prelude.Nothing,
$sel:keepSegments:HlsGroupSettings' :: Maybe Natural
keepSegments = forall a. Maybe a
Prelude.Nothing,
$sel:keyFormat:HlsGroupSettings' :: Maybe Text
keyFormat = forall a. Maybe a
Prelude.Nothing,
$sel:keyFormatVersions:HlsGroupSettings' :: Maybe Text
keyFormatVersions = forall a. Maybe a
Prelude.Nothing,
$sel:keyProviderSettings:HlsGroupSettings' :: Maybe KeyProviderSettings
keyProviderSettings = forall a. Maybe a
Prelude.Nothing,
$sel:manifestCompression:HlsGroupSettings' :: Maybe HlsManifestCompression
manifestCompression = forall a. Maybe a
Prelude.Nothing,
$sel:manifestDurationFormat:HlsGroupSettings' :: Maybe HlsManifestDurationFormat
manifestDurationFormat = forall a. Maybe a
Prelude.Nothing,
$sel:minSegmentLength:HlsGroupSettings' :: Maybe Natural
minSegmentLength = forall a. Maybe a
Prelude.Nothing,
$sel:mode:HlsGroupSettings' :: Maybe HlsMode
mode = forall a. Maybe a
Prelude.Nothing,
$sel:outputSelection:HlsGroupSettings' :: Maybe HlsOutputSelection
outputSelection = forall a. Maybe a
Prelude.Nothing,
$sel:programDateTime:HlsGroupSettings' :: Maybe HlsProgramDateTime
programDateTime = forall a. Maybe a
Prelude.Nothing,
$sel:programDateTimeClock:HlsGroupSettings' :: Maybe HlsProgramDateTimeClock
programDateTimeClock = forall a. Maybe a
Prelude.Nothing,
$sel:programDateTimePeriod:HlsGroupSettings' :: Maybe Natural
programDateTimePeriod = forall a. Maybe a
Prelude.Nothing,
$sel:redundantManifest:HlsGroupSettings' :: Maybe HlsRedundantManifest
redundantManifest = forall a. Maybe a
Prelude.Nothing,
$sel:segmentLength:HlsGroupSettings' :: Maybe Natural
segmentLength = forall a. Maybe a
Prelude.Nothing,
$sel:segmentationMode:HlsGroupSettings' :: Maybe HlsSegmentationMode
segmentationMode = forall a. Maybe a
Prelude.Nothing,
$sel:segmentsPerSubdirectory:HlsGroupSettings' :: Maybe Natural
segmentsPerSubdirectory = forall a. Maybe a
Prelude.Nothing,
$sel:streamInfResolution:HlsGroupSettings' :: Maybe HlsStreamInfResolution
streamInfResolution = forall a. Maybe a
Prelude.Nothing,
$sel:timedMetadataId3Frame:HlsGroupSettings' :: Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame = forall a. Maybe a
Prelude.Nothing,
$sel:timedMetadataId3Period:HlsGroupSettings' :: Maybe Natural
timedMetadataId3Period = forall a. Maybe a
Prelude.Nothing,
$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: Maybe Natural
timestampDeltaMilliseconds = forall a. Maybe a
Prelude.Nothing,
$sel:tsFileMode:HlsGroupSettings' :: Maybe HlsTsFileMode
tsFileMode = forall a. Maybe a
Prelude.Nothing,
$sel:destination:HlsGroupSettings' :: OutputLocationRef
destination = OutputLocationRef
pDestination_
}
hlsGroupSettings_adMarkers :: Lens.Lens' HlsGroupSettings (Prelude.Maybe [HlsAdMarkers])
hlsGroupSettings_adMarkers :: Lens' HlsGroupSettings (Maybe [HlsAdMarkers])
hlsGroupSettings_adMarkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe [HlsAdMarkers]
adMarkers :: Maybe [HlsAdMarkers]
$sel:adMarkers:HlsGroupSettings' :: HlsGroupSettings -> Maybe [HlsAdMarkers]
adMarkers} -> Maybe [HlsAdMarkers]
adMarkers) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe [HlsAdMarkers]
a -> HlsGroupSettings
s {$sel:adMarkers:HlsGroupSettings' :: Maybe [HlsAdMarkers]
adMarkers = Maybe [HlsAdMarkers]
a} :: HlsGroupSettings) 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
hlsGroupSettings_baseUrlContent :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_baseUrlContent :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_baseUrlContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
baseUrlContent :: Maybe Text
$sel:baseUrlContent:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
baseUrlContent} -> Maybe Text
baseUrlContent) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:baseUrlContent:HlsGroupSettings' :: Maybe Text
baseUrlContent = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_baseUrlContent1 :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_baseUrlContent1 :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_baseUrlContent1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
baseUrlContent1 :: Maybe Text
$sel:baseUrlContent1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
baseUrlContent1} -> Maybe Text
baseUrlContent1) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:baseUrlContent1:HlsGroupSettings' :: Maybe Text
baseUrlContent1 = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_baseUrlManifest :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_baseUrlManifest :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_baseUrlManifest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
baseUrlManifest :: Maybe Text
$sel:baseUrlManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
baseUrlManifest} -> Maybe Text
baseUrlManifest) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:baseUrlManifest:HlsGroupSettings' :: Maybe Text
baseUrlManifest = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_baseUrlManifest1 :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_baseUrlManifest1 :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_baseUrlManifest1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
baseUrlManifest1 :: Maybe Text
$sel:baseUrlManifest1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
baseUrlManifest1} -> Maybe Text
baseUrlManifest1) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:baseUrlManifest1:HlsGroupSettings' :: Maybe Text
baseUrlManifest1 = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_captionLanguageMappings :: Lens.Lens' HlsGroupSettings (Prelude.Maybe [CaptionLanguageMapping])
hlsGroupSettings_captionLanguageMappings :: Lens' HlsGroupSettings (Maybe [CaptionLanguageMapping])
hlsGroupSettings_captionLanguageMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe [CaptionLanguageMapping]
captionLanguageMappings :: Maybe [CaptionLanguageMapping]
$sel:captionLanguageMappings:HlsGroupSettings' :: HlsGroupSettings -> Maybe [CaptionLanguageMapping]
captionLanguageMappings} -> Maybe [CaptionLanguageMapping]
captionLanguageMappings) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe [CaptionLanguageMapping]
a -> HlsGroupSettings
s {$sel:captionLanguageMappings:HlsGroupSettings' :: Maybe [CaptionLanguageMapping]
captionLanguageMappings = Maybe [CaptionLanguageMapping]
a} :: HlsGroupSettings) 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
hlsGroupSettings_captionLanguageSetting :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsCaptionLanguageSetting)
hlsGroupSettings_captionLanguageSetting :: Lens' HlsGroupSettings (Maybe HlsCaptionLanguageSetting)
hlsGroupSettings_captionLanguageSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsCaptionLanguageSetting
captionLanguageSetting :: Maybe HlsCaptionLanguageSetting
$sel:captionLanguageSetting:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCaptionLanguageSetting
captionLanguageSetting} -> Maybe HlsCaptionLanguageSetting
captionLanguageSetting) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsCaptionLanguageSetting
a -> HlsGroupSettings
s {$sel:captionLanguageSetting:HlsGroupSettings' :: Maybe HlsCaptionLanguageSetting
captionLanguageSetting = Maybe HlsCaptionLanguageSetting
a} :: HlsGroupSettings)
hlsGroupSettings_clientCache :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsClientCache)
hlsGroupSettings_clientCache :: Lens' HlsGroupSettings (Maybe HlsClientCache)
hlsGroupSettings_clientCache = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsClientCache
clientCache :: Maybe HlsClientCache
$sel:clientCache:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsClientCache
clientCache} -> Maybe HlsClientCache
clientCache) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsClientCache
a -> HlsGroupSettings
s {$sel:clientCache:HlsGroupSettings' :: Maybe HlsClientCache
clientCache = Maybe HlsClientCache
a} :: HlsGroupSettings)
hlsGroupSettings_codecSpecification :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsCodecSpecification)
hlsGroupSettings_codecSpecification :: Lens' HlsGroupSettings (Maybe HlsCodecSpecification)
hlsGroupSettings_codecSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsCodecSpecification
codecSpecification :: Maybe HlsCodecSpecification
$sel:codecSpecification:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCodecSpecification
codecSpecification} -> Maybe HlsCodecSpecification
codecSpecification) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsCodecSpecification
a -> HlsGroupSettings
s {$sel:codecSpecification:HlsGroupSettings' :: Maybe HlsCodecSpecification
codecSpecification = Maybe HlsCodecSpecification
a} :: HlsGroupSettings)
hlsGroupSettings_constantIv :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_constantIv :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_constantIv = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
constantIv :: Maybe Text
$sel:constantIv:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
constantIv} -> Maybe Text
constantIv) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:constantIv:HlsGroupSettings' :: Maybe Text
constantIv = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_directoryStructure :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsDirectoryStructure)
hlsGroupSettings_directoryStructure :: Lens' HlsGroupSettings (Maybe HlsDirectoryStructure)
hlsGroupSettings_directoryStructure = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsDirectoryStructure
directoryStructure :: Maybe HlsDirectoryStructure
$sel:directoryStructure:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDirectoryStructure
directoryStructure} -> Maybe HlsDirectoryStructure
directoryStructure) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsDirectoryStructure
a -> HlsGroupSettings
s {$sel:directoryStructure:HlsGroupSettings' :: Maybe HlsDirectoryStructure
directoryStructure = Maybe HlsDirectoryStructure
a} :: HlsGroupSettings)
hlsGroupSettings_discontinuityTags :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsDiscontinuityTags)
hlsGroupSettings_discontinuityTags :: Lens' HlsGroupSettings (Maybe HlsDiscontinuityTags)
hlsGroupSettings_discontinuityTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsDiscontinuityTags
discontinuityTags :: Maybe HlsDiscontinuityTags
$sel:discontinuityTags:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDiscontinuityTags
discontinuityTags} -> Maybe HlsDiscontinuityTags
discontinuityTags) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsDiscontinuityTags
a -> HlsGroupSettings
s {$sel:discontinuityTags:HlsGroupSettings' :: Maybe HlsDiscontinuityTags
discontinuityTags = Maybe HlsDiscontinuityTags
a} :: HlsGroupSettings)
hlsGroupSettings_encryptionType :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsEncryptionType)
hlsGroupSettings_encryptionType :: Lens' HlsGroupSettings (Maybe HlsEncryptionType)
hlsGroupSettings_encryptionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsEncryptionType
encryptionType :: Maybe HlsEncryptionType
$sel:encryptionType:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsEncryptionType
encryptionType} -> Maybe HlsEncryptionType
encryptionType) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsEncryptionType
a -> HlsGroupSettings
s {$sel:encryptionType:HlsGroupSettings' :: Maybe HlsEncryptionType
encryptionType = Maybe HlsEncryptionType
a} :: HlsGroupSettings)
hlsGroupSettings_hlsCdnSettings :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsCdnSettings)
hlsGroupSettings_hlsCdnSettings :: Lens' HlsGroupSettings (Maybe HlsCdnSettings)
hlsGroupSettings_hlsCdnSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsCdnSettings
hlsCdnSettings :: Maybe HlsCdnSettings
$sel:hlsCdnSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCdnSettings
hlsCdnSettings} -> Maybe HlsCdnSettings
hlsCdnSettings) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsCdnSettings
a -> HlsGroupSettings
s {$sel:hlsCdnSettings:HlsGroupSettings' :: Maybe HlsCdnSettings
hlsCdnSettings = Maybe HlsCdnSettings
a} :: HlsGroupSettings)
hlsGroupSettings_hlsId3SegmentTagging :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsId3SegmentTaggingState)
hlsGroupSettings_hlsId3SegmentTagging :: Lens' HlsGroupSettings (Maybe HlsId3SegmentTaggingState)
hlsGroupSettings_hlsId3SegmentTagging = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging :: Maybe HlsId3SegmentTaggingState
$sel:hlsId3SegmentTagging:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging} -> Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsId3SegmentTaggingState
a -> HlsGroupSettings
s {$sel:hlsId3SegmentTagging:HlsGroupSettings' :: Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging = Maybe HlsId3SegmentTaggingState
a} :: HlsGroupSettings)
hlsGroupSettings_iFrameOnlyPlaylists :: Lens.Lens' HlsGroupSettings (Prelude.Maybe IFrameOnlyPlaylistType)
hlsGroupSettings_iFrameOnlyPlaylists :: Lens' HlsGroupSettings (Maybe IFrameOnlyPlaylistType)
hlsGroupSettings_iFrameOnlyPlaylists = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists :: Maybe IFrameOnlyPlaylistType
$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: HlsGroupSettings -> Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists} -> Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe IFrameOnlyPlaylistType
a -> HlsGroupSettings
s {$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists = Maybe IFrameOnlyPlaylistType
a} :: HlsGroupSettings)
hlsGroupSettings_incompleteSegmentBehavior :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsIncompleteSegmentBehavior)
hlsGroupSettings_incompleteSegmentBehavior :: Lens' HlsGroupSettings (Maybe HlsIncompleteSegmentBehavior)
hlsGroupSettings_incompleteSegmentBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior :: Maybe HlsIncompleteSegmentBehavior
$sel:incompleteSegmentBehavior:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior} -> Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsIncompleteSegmentBehavior
a -> HlsGroupSettings
s {$sel:incompleteSegmentBehavior:HlsGroupSettings' :: Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior = Maybe HlsIncompleteSegmentBehavior
a} :: HlsGroupSettings)
hlsGroupSettings_indexNSegments :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_indexNSegments :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_indexNSegments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
indexNSegments :: Maybe Natural
$sel:indexNSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
indexNSegments} -> Maybe Natural
indexNSegments) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:indexNSegments:HlsGroupSettings' :: Maybe Natural
indexNSegments = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_inputLossAction :: Lens.Lens' HlsGroupSettings (Prelude.Maybe InputLossActionForHlsOut)
hlsGroupSettings_inputLossAction :: Lens' HlsGroupSettings (Maybe InputLossActionForHlsOut)
hlsGroupSettings_inputLossAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe InputLossActionForHlsOut
inputLossAction :: Maybe InputLossActionForHlsOut
$sel:inputLossAction:HlsGroupSettings' :: HlsGroupSettings -> Maybe InputLossActionForHlsOut
inputLossAction} -> Maybe InputLossActionForHlsOut
inputLossAction) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe InputLossActionForHlsOut
a -> HlsGroupSettings
s {$sel:inputLossAction:HlsGroupSettings' :: Maybe InputLossActionForHlsOut
inputLossAction = Maybe InputLossActionForHlsOut
a} :: HlsGroupSettings)
hlsGroupSettings_ivInManifest :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsIvInManifest)
hlsGroupSettings_ivInManifest :: Lens' HlsGroupSettings (Maybe HlsIvInManifest)
hlsGroupSettings_ivInManifest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsIvInManifest
ivInManifest :: Maybe HlsIvInManifest
$sel:ivInManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvInManifest
ivInManifest} -> Maybe HlsIvInManifest
ivInManifest) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsIvInManifest
a -> HlsGroupSettings
s {$sel:ivInManifest:HlsGroupSettings' :: Maybe HlsIvInManifest
ivInManifest = Maybe HlsIvInManifest
a} :: HlsGroupSettings)
hlsGroupSettings_ivSource :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsIvSource)
hlsGroupSettings_ivSource :: Lens' HlsGroupSettings (Maybe HlsIvSource)
hlsGroupSettings_ivSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsIvSource
ivSource :: Maybe HlsIvSource
$sel:ivSource:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvSource
ivSource} -> Maybe HlsIvSource
ivSource) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsIvSource
a -> HlsGroupSettings
s {$sel:ivSource:HlsGroupSettings' :: Maybe HlsIvSource
ivSource = Maybe HlsIvSource
a} :: HlsGroupSettings)
hlsGroupSettings_keepSegments :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_keepSegments :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_keepSegments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
keepSegments :: Maybe Natural
$sel:keepSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
keepSegments} -> Maybe Natural
keepSegments) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:keepSegments:HlsGroupSettings' :: Maybe Natural
keepSegments = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_keyFormat :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_keyFormat :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_keyFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
keyFormat :: Maybe Text
$sel:keyFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
keyFormat} -> Maybe Text
keyFormat) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:keyFormat:HlsGroupSettings' :: Maybe Text
keyFormat = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_keyFormatVersions :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Text)
hlsGroupSettings_keyFormatVersions :: Lens' HlsGroupSettings (Maybe Text)
hlsGroupSettings_keyFormatVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Text
keyFormatVersions :: Maybe Text
$sel:keyFormatVersions:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
keyFormatVersions} -> Maybe Text
keyFormatVersions) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Text
a -> HlsGroupSettings
s {$sel:keyFormatVersions:HlsGroupSettings' :: Maybe Text
keyFormatVersions = Maybe Text
a} :: HlsGroupSettings)
hlsGroupSettings_keyProviderSettings :: Lens.Lens' HlsGroupSettings (Prelude.Maybe KeyProviderSettings)
hlsGroupSettings_keyProviderSettings :: Lens' HlsGroupSettings (Maybe KeyProviderSettings)
hlsGroupSettings_keyProviderSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe KeyProviderSettings
keyProviderSettings :: Maybe KeyProviderSettings
$sel:keyProviderSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe KeyProviderSettings
keyProviderSettings} -> Maybe KeyProviderSettings
keyProviderSettings) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe KeyProviderSettings
a -> HlsGroupSettings
s {$sel:keyProviderSettings:HlsGroupSettings' :: Maybe KeyProviderSettings
keyProviderSettings = Maybe KeyProviderSettings
a} :: HlsGroupSettings)
hlsGroupSettings_manifestCompression :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsManifestCompression)
hlsGroupSettings_manifestCompression :: Lens' HlsGroupSettings (Maybe HlsManifestCompression)
hlsGroupSettings_manifestCompression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsManifestCompression
manifestCompression :: Maybe HlsManifestCompression
$sel:manifestCompression:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestCompression
manifestCompression} -> Maybe HlsManifestCompression
manifestCompression) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsManifestCompression
a -> HlsGroupSettings
s {$sel:manifestCompression:HlsGroupSettings' :: Maybe HlsManifestCompression
manifestCompression = Maybe HlsManifestCompression
a} :: HlsGroupSettings)
hlsGroupSettings_manifestDurationFormat :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsManifestDurationFormat)
hlsGroupSettings_manifestDurationFormat :: Lens' HlsGroupSettings (Maybe HlsManifestDurationFormat)
hlsGroupSettings_manifestDurationFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsManifestDurationFormat
manifestDurationFormat :: Maybe HlsManifestDurationFormat
$sel:manifestDurationFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestDurationFormat
manifestDurationFormat} -> Maybe HlsManifestDurationFormat
manifestDurationFormat) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsManifestDurationFormat
a -> HlsGroupSettings
s {$sel:manifestDurationFormat:HlsGroupSettings' :: Maybe HlsManifestDurationFormat
manifestDurationFormat = Maybe HlsManifestDurationFormat
a} :: HlsGroupSettings)
hlsGroupSettings_minSegmentLength :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_minSegmentLength :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_minSegmentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
minSegmentLength :: Maybe Natural
$sel:minSegmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
minSegmentLength} -> Maybe Natural
minSegmentLength) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:minSegmentLength:HlsGroupSettings' :: Maybe Natural
minSegmentLength = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_mode :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsMode)
hlsGroupSettings_mode :: Lens' HlsGroupSettings (Maybe HlsMode)
hlsGroupSettings_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsMode
mode :: Maybe HlsMode
$sel:mode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsMode
mode} -> Maybe HlsMode
mode) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsMode
a -> HlsGroupSettings
s {$sel:mode:HlsGroupSettings' :: Maybe HlsMode
mode = Maybe HlsMode
a} :: HlsGroupSettings)
hlsGroupSettings_outputSelection :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsOutputSelection)
hlsGroupSettings_outputSelection :: Lens' HlsGroupSettings (Maybe HlsOutputSelection)
hlsGroupSettings_outputSelection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsOutputSelection
outputSelection :: Maybe HlsOutputSelection
$sel:outputSelection:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsOutputSelection
outputSelection} -> Maybe HlsOutputSelection
outputSelection) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsOutputSelection
a -> HlsGroupSettings
s {$sel:outputSelection:HlsGroupSettings' :: Maybe HlsOutputSelection
outputSelection = Maybe HlsOutputSelection
a} :: HlsGroupSettings)
hlsGroupSettings_programDateTime :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsProgramDateTime)
hlsGroupSettings_programDateTime :: Lens' HlsGroupSettings (Maybe HlsProgramDateTime)
hlsGroupSettings_programDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsProgramDateTime
programDateTime :: Maybe HlsProgramDateTime
$sel:programDateTime:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTime
programDateTime} -> Maybe HlsProgramDateTime
programDateTime) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsProgramDateTime
a -> HlsGroupSettings
s {$sel:programDateTime:HlsGroupSettings' :: Maybe HlsProgramDateTime
programDateTime = Maybe HlsProgramDateTime
a} :: HlsGroupSettings)
hlsGroupSettings_programDateTimeClock :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsProgramDateTimeClock)
hlsGroupSettings_programDateTimeClock :: Lens' HlsGroupSettings (Maybe HlsProgramDateTimeClock)
hlsGroupSettings_programDateTimeClock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsProgramDateTimeClock
programDateTimeClock :: Maybe HlsProgramDateTimeClock
$sel:programDateTimeClock:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTimeClock
programDateTimeClock} -> Maybe HlsProgramDateTimeClock
programDateTimeClock) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsProgramDateTimeClock
a -> HlsGroupSettings
s {$sel:programDateTimeClock:HlsGroupSettings' :: Maybe HlsProgramDateTimeClock
programDateTimeClock = Maybe HlsProgramDateTimeClock
a} :: HlsGroupSettings)
hlsGroupSettings_programDateTimePeriod :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_programDateTimePeriod :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_programDateTimePeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
programDateTimePeriod :: Maybe Natural
$sel:programDateTimePeriod:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
programDateTimePeriod} -> Maybe Natural
programDateTimePeriod) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:programDateTimePeriod:HlsGroupSettings' :: Maybe Natural
programDateTimePeriod = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_redundantManifest :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsRedundantManifest)
hlsGroupSettings_redundantManifest :: Lens' HlsGroupSettings (Maybe HlsRedundantManifest)
hlsGroupSettings_redundantManifest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsRedundantManifest
redundantManifest :: Maybe HlsRedundantManifest
$sel:redundantManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsRedundantManifest
redundantManifest} -> Maybe HlsRedundantManifest
redundantManifest) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsRedundantManifest
a -> HlsGroupSettings
s {$sel:redundantManifest:HlsGroupSettings' :: Maybe HlsRedundantManifest
redundantManifest = Maybe HlsRedundantManifest
a} :: HlsGroupSettings)
hlsGroupSettings_segmentLength :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_segmentLength :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_segmentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
segmentLength :: Maybe Natural
$sel:segmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
segmentLength} -> Maybe Natural
segmentLength) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:segmentLength:HlsGroupSettings' :: Maybe Natural
segmentLength = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_segmentationMode :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsSegmentationMode)
hlsGroupSettings_segmentationMode :: Lens' HlsGroupSettings (Maybe HlsSegmentationMode)
hlsGroupSettings_segmentationMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsSegmentationMode
segmentationMode :: Maybe HlsSegmentationMode
$sel:segmentationMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsSegmentationMode
segmentationMode} -> Maybe HlsSegmentationMode
segmentationMode) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsSegmentationMode
a -> HlsGroupSettings
s {$sel:segmentationMode:HlsGroupSettings' :: Maybe HlsSegmentationMode
segmentationMode = Maybe HlsSegmentationMode
a} :: HlsGroupSettings)
hlsGroupSettings_segmentsPerSubdirectory :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_segmentsPerSubdirectory :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_segmentsPerSubdirectory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
segmentsPerSubdirectory :: Maybe Natural
$sel:segmentsPerSubdirectory:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
segmentsPerSubdirectory} -> Maybe Natural
segmentsPerSubdirectory) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:segmentsPerSubdirectory:HlsGroupSettings' :: Maybe Natural
segmentsPerSubdirectory = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_streamInfResolution :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsStreamInfResolution)
hlsGroupSettings_streamInfResolution :: Lens' HlsGroupSettings (Maybe HlsStreamInfResolution)
hlsGroupSettings_streamInfResolution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsStreamInfResolution
streamInfResolution :: Maybe HlsStreamInfResolution
$sel:streamInfResolution:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsStreamInfResolution
streamInfResolution} -> Maybe HlsStreamInfResolution
streamInfResolution) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsStreamInfResolution
a -> HlsGroupSettings
s {$sel:streamInfResolution:HlsGroupSettings' :: Maybe HlsStreamInfResolution
streamInfResolution = Maybe HlsStreamInfResolution
a} :: HlsGroupSettings)
hlsGroupSettings_timedMetadataId3Frame :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsTimedMetadataId3Frame)
hlsGroupSettings_timedMetadataId3Frame :: Lens' HlsGroupSettings (Maybe HlsTimedMetadataId3Frame)
hlsGroupSettings_timedMetadataId3Frame = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame :: Maybe HlsTimedMetadataId3Frame
$sel:timedMetadataId3Frame:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame} -> Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsTimedMetadataId3Frame
a -> HlsGroupSettings
s {$sel:timedMetadataId3Frame:HlsGroupSettings' :: Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame = Maybe HlsTimedMetadataId3Frame
a} :: HlsGroupSettings)
hlsGroupSettings_timedMetadataId3Period :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_timedMetadataId3Period :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_timedMetadataId3Period = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
timedMetadataId3Period :: Maybe Natural
$sel:timedMetadataId3Period:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
timedMetadataId3Period} -> Maybe Natural
timedMetadataId3Period) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:timedMetadataId3Period:HlsGroupSettings' :: Maybe Natural
timedMetadataId3Period = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_timestampDeltaMilliseconds :: Lens.Lens' HlsGroupSettings (Prelude.Maybe Prelude.Natural)
hlsGroupSettings_timestampDeltaMilliseconds :: Lens' HlsGroupSettings (Maybe Natural)
hlsGroupSettings_timestampDeltaMilliseconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe Natural
timestampDeltaMilliseconds :: Maybe Natural
$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
timestampDeltaMilliseconds} -> Maybe Natural
timestampDeltaMilliseconds) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe Natural
a -> HlsGroupSettings
s {$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: Maybe Natural
timestampDeltaMilliseconds = Maybe Natural
a} :: HlsGroupSettings)
hlsGroupSettings_tsFileMode :: Lens.Lens' HlsGroupSettings (Prelude.Maybe HlsTsFileMode)
hlsGroupSettings_tsFileMode :: Lens' HlsGroupSettings (Maybe HlsTsFileMode)
hlsGroupSettings_tsFileMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {Maybe HlsTsFileMode
tsFileMode :: Maybe HlsTsFileMode
$sel:tsFileMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTsFileMode
tsFileMode} -> Maybe HlsTsFileMode
tsFileMode) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} Maybe HlsTsFileMode
a -> HlsGroupSettings
s {$sel:tsFileMode:HlsGroupSettings' :: Maybe HlsTsFileMode
tsFileMode = Maybe HlsTsFileMode
a} :: HlsGroupSettings)
hlsGroupSettings_destination :: Lens.Lens' HlsGroupSettings OutputLocationRef
hlsGroupSettings_destination :: Lens' HlsGroupSettings OutputLocationRef
hlsGroupSettings_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HlsGroupSettings' {OutputLocationRef
destination :: OutputLocationRef
$sel:destination:HlsGroupSettings' :: HlsGroupSettings -> OutputLocationRef
destination} -> OutputLocationRef
destination) (\s :: HlsGroupSettings
s@HlsGroupSettings' {} OutputLocationRef
a -> HlsGroupSettings
s {$sel:destination:HlsGroupSettings' :: OutputLocationRef
destination = OutputLocationRef
a} :: HlsGroupSettings)
instance Data.FromJSON HlsGroupSettings where
parseJSON :: Value -> Parser HlsGroupSettings
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"HlsGroupSettings"
( \Object
x ->
Maybe [HlsAdMarkers]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [CaptionLanguageMapping]
-> Maybe HlsCaptionLanguageSetting
-> Maybe HlsClientCache
-> Maybe HlsCodecSpecification
-> Maybe Text
-> Maybe HlsDirectoryStructure
-> Maybe HlsDiscontinuityTags
-> Maybe HlsEncryptionType
-> Maybe HlsCdnSettings
-> Maybe HlsId3SegmentTaggingState
-> Maybe IFrameOnlyPlaylistType
-> Maybe HlsIncompleteSegmentBehavior
-> Maybe Natural
-> Maybe InputLossActionForHlsOut
-> Maybe HlsIvInManifest
-> Maybe HlsIvSource
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe KeyProviderSettings
-> Maybe HlsManifestCompression
-> Maybe HlsManifestDurationFormat
-> Maybe Natural
-> Maybe HlsMode
-> Maybe HlsOutputSelection
-> Maybe HlsProgramDateTime
-> Maybe HlsProgramDateTimeClock
-> Maybe Natural
-> Maybe HlsRedundantManifest
-> Maybe Natural
-> Maybe HlsSegmentationMode
-> Maybe Natural
-> Maybe HlsStreamInfResolution
-> Maybe HlsTimedMetadataId3Frame
-> Maybe Natural
-> Maybe Natural
-> Maybe HlsTsFileMode
-> OutputLocationRef
-> HlsGroupSettings
HlsGroupSettings'
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
"adMarkers" 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
"baseUrlContent")
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
"baseUrlContent1")
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
"baseUrlManifest")
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
"baseUrlManifest1")
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
"captionLanguageMappings"
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
"captionLanguageSetting")
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
"clientCache")
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
"codecSpecification")
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
"constantIv")
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
"directoryStructure")
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
"discontinuityTags")
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
"encryptionType")
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
"hlsCdnSettings")
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
"hlsId3SegmentTagging")
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
"iFrameOnlyPlaylists")
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
"incompleteSegmentBehavior")
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
"indexNSegments")
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
"inputLossAction")
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
"ivInManifest")
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
"ivSource")
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
"keepSegments")
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
"keyFormat")
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
"keyFormatVersions")
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
"keyProviderSettings")
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
"manifestCompression")
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
"manifestDurationFormat")
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
"minSegmentLength")
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
"mode")
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
"outputSelection")
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
"programDateTime")
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
"programDateTimeClock")
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
"programDateTimePeriod")
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
"redundantManifest")
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
"segmentLength")
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
"segmentationMode")
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
"segmentsPerSubdirectory")
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
"streamInfResolution")
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
"timedMetadataId3Frame")
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
"timedMetadataId3Period")
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
"timestampDeltaMilliseconds")
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
"tsFileMode")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"destination")
)
instance Prelude.Hashable HlsGroupSettings where
hashWithSalt :: Int -> HlsGroupSettings -> Int
hashWithSalt Int
_salt HlsGroupSettings' {Maybe Natural
Maybe [CaptionLanguageMapping]
Maybe [HlsAdMarkers]
Maybe Text
Maybe HlsCaptionLanguageSetting
Maybe HlsClientCache
Maybe HlsCodecSpecification
Maybe HlsDirectoryStructure
Maybe HlsDiscontinuityTags
Maybe HlsEncryptionType
Maybe HlsId3SegmentTaggingState
Maybe HlsIncompleteSegmentBehavior
Maybe HlsIvInManifest
Maybe HlsIvSource
Maybe HlsManifestCompression
Maybe HlsManifestDurationFormat
Maybe HlsMode
Maybe HlsOutputSelection
Maybe HlsProgramDateTime
Maybe HlsProgramDateTimeClock
Maybe HlsRedundantManifest
Maybe HlsSegmentationMode
Maybe HlsStreamInfResolution
Maybe HlsTimedMetadataId3Frame
Maybe HlsTsFileMode
Maybe IFrameOnlyPlaylistType
Maybe InputLossActionForHlsOut
Maybe HlsCdnSettings
Maybe KeyProviderSettings
OutputLocationRef
destination :: OutputLocationRef
tsFileMode :: Maybe HlsTsFileMode
timestampDeltaMilliseconds :: Maybe Natural
timedMetadataId3Period :: Maybe Natural
timedMetadataId3Frame :: Maybe HlsTimedMetadataId3Frame
streamInfResolution :: Maybe HlsStreamInfResolution
segmentsPerSubdirectory :: Maybe Natural
segmentationMode :: Maybe HlsSegmentationMode
segmentLength :: Maybe Natural
redundantManifest :: Maybe HlsRedundantManifest
programDateTimePeriod :: Maybe Natural
programDateTimeClock :: Maybe HlsProgramDateTimeClock
programDateTime :: Maybe HlsProgramDateTime
outputSelection :: Maybe HlsOutputSelection
mode :: Maybe HlsMode
minSegmentLength :: Maybe Natural
manifestDurationFormat :: Maybe HlsManifestDurationFormat
manifestCompression :: Maybe HlsManifestCompression
keyProviderSettings :: Maybe KeyProviderSettings
keyFormatVersions :: Maybe Text
keyFormat :: Maybe Text
keepSegments :: Maybe Natural
ivSource :: Maybe HlsIvSource
ivInManifest :: Maybe HlsIvInManifest
inputLossAction :: Maybe InputLossActionForHlsOut
indexNSegments :: Maybe Natural
incompleteSegmentBehavior :: Maybe HlsIncompleteSegmentBehavior
iFrameOnlyPlaylists :: Maybe IFrameOnlyPlaylistType
hlsId3SegmentTagging :: Maybe HlsId3SegmentTaggingState
hlsCdnSettings :: Maybe HlsCdnSettings
encryptionType :: Maybe HlsEncryptionType
discontinuityTags :: Maybe HlsDiscontinuityTags
directoryStructure :: Maybe HlsDirectoryStructure
constantIv :: Maybe Text
codecSpecification :: Maybe HlsCodecSpecification
clientCache :: Maybe HlsClientCache
captionLanguageSetting :: Maybe HlsCaptionLanguageSetting
captionLanguageMappings :: Maybe [CaptionLanguageMapping]
baseUrlManifest1 :: Maybe Text
baseUrlManifest :: Maybe Text
baseUrlContent1 :: Maybe Text
baseUrlContent :: Maybe Text
adMarkers :: Maybe [HlsAdMarkers]
$sel:destination:HlsGroupSettings' :: HlsGroupSettings -> OutputLocationRef
$sel:tsFileMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTsFileMode
$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Period:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Frame:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTimedMetadataId3Frame
$sel:streamInfResolution:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsStreamInfResolution
$sel:segmentsPerSubdirectory:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:segmentationMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsSegmentationMode
$sel:segmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:redundantManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsRedundantManifest
$sel:programDateTimePeriod:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:programDateTimeClock:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTimeClock
$sel:programDateTime:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTime
$sel:outputSelection:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsOutputSelection
$sel:mode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsMode
$sel:minSegmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:manifestDurationFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestDurationFormat
$sel:manifestCompression:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestCompression
$sel:keyProviderSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe KeyProviderSettings
$sel:keyFormatVersions:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keyFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keepSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:ivSource:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvSource
$sel:ivInManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvInManifest
$sel:inputLossAction:HlsGroupSettings' :: HlsGroupSettings -> Maybe InputLossActionForHlsOut
$sel:indexNSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:incompleteSegmentBehavior:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIncompleteSegmentBehavior
$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: HlsGroupSettings -> Maybe IFrameOnlyPlaylistType
$sel:hlsId3SegmentTagging:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsId3SegmentTaggingState
$sel:hlsCdnSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCdnSettings
$sel:encryptionType:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsEncryptionType
$sel:discontinuityTags:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDiscontinuityTags
$sel:directoryStructure:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDirectoryStructure
$sel:constantIv:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:codecSpecification:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCodecSpecification
$sel:clientCache:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsClientCache
$sel:captionLanguageSetting:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCaptionLanguageSetting
$sel:captionLanguageMappings:HlsGroupSettings' :: HlsGroupSettings -> Maybe [CaptionLanguageMapping]
$sel:baseUrlManifest1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:adMarkers:HlsGroupSettings' :: HlsGroupSettings -> Maybe [HlsAdMarkers]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [HlsAdMarkers]
adMarkers
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baseUrlContent
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baseUrlContent1
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baseUrlManifest
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baseUrlManifest1
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CaptionLanguageMapping]
captionLanguageMappings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsCaptionLanguageSetting
captionLanguageSetting
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsClientCache
clientCache
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsCodecSpecification
codecSpecification
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
constantIv
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsDirectoryStructure
directoryStructure
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsDiscontinuityTags
discontinuityTags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsEncryptionType
encryptionType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsCdnSettings
hlsCdnSettings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
indexNSegments
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputLossActionForHlsOut
inputLossAction
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsIvInManifest
ivInManifest
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsIvSource
ivSource
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
keepSegments
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyFormat
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyFormatVersions
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KeyProviderSettings
keyProviderSettings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsManifestCompression
manifestCompression
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsManifestDurationFormat
manifestDurationFormat
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
minSegmentLength
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsMode
mode
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsOutputSelection
outputSelection
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsProgramDateTime
programDateTime
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsProgramDateTimeClock
programDateTimeClock
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
programDateTimePeriod
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsRedundantManifest
redundantManifest
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
segmentLength
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsSegmentationMode
segmentationMode
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
segmentsPerSubdirectory
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsStreamInfResolution
streamInfResolution
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timedMetadataId3Period
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timestampDeltaMilliseconds
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsTsFileMode
tsFileMode
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` OutputLocationRef
destination
instance Prelude.NFData HlsGroupSettings where
rnf :: HlsGroupSettings -> ()
rnf HlsGroupSettings' {Maybe Natural
Maybe [CaptionLanguageMapping]
Maybe [HlsAdMarkers]
Maybe Text
Maybe HlsCaptionLanguageSetting
Maybe HlsClientCache
Maybe HlsCodecSpecification
Maybe HlsDirectoryStructure
Maybe HlsDiscontinuityTags
Maybe HlsEncryptionType
Maybe HlsId3SegmentTaggingState
Maybe HlsIncompleteSegmentBehavior
Maybe HlsIvInManifest
Maybe HlsIvSource
Maybe HlsManifestCompression
Maybe HlsManifestDurationFormat
Maybe HlsMode
Maybe HlsOutputSelection
Maybe HlsProgramDateTime
Maybe HlsProgramDateTimeClock
Maybe HlsRedundantManifest
Maybe HlsSegmentationMode
Maybe HlsStreamInfResolution
Maybe HlsTimedMetadataId3Frame
Maybe HlsTsFileMode
Maybe IFrameOnlyPlaylistType
Maybe InputLossActionForHlsOut
Maybe HlsCdnSettings
Maybe KeyProviderSettings
OutputLocationRef
destination :: OutputLocationRef
tsFileMode :: Maybe HlsTsFileMode
timestampDeltaMilliseconds :: Maybe Natural
timedMetadataId3Period :: Maybe Natural
timedMetadataId3Frame :: Maybe HlsTimedMetadataId3Frame
streamInfResolution :: Maybe HlsStreamInfResolution
segmentsPerSubdirectory :: Maybe Natural
segmentationMode :: Maybe HlsSegmentationMode
segmentLength :: Maybe Natural
redundantManifest :: Maybe HlsRedundantManifest
programDateTimePeriod :: Maybe Natural
programDateTimeClock :: Maybe HlsProgramDateTimeClock
programDateTime :: Maybe HlsProgramDateTime
outputSelection :: Maybe HlsOutputSelection
mode :: Maybe HlsMode
minSegmentLength :: Maybe Natural
manifestDurationFormat :: Maybe HlsManifestDurationFormat
manifestCompression :: Maybe HlsManifestCompression
keyProviderSettings :: Maybe KeyProviderSettings
keyFormatVersions :: Maybe Text
keyFormat :: Maybe Text
keepSegments :: Maybe Natural
ivSource :: Maybe HlsIvSource
ivInManifest :: Maybe HlsIvInManifest
inputLossAction :: Maybe InputLossActionForHlsOut
indexNSegments :: Maybe Natural
incompleteSegmentBehavior :: Maybe HlsIncompleteSegmentBehavior
iFrameOnlyPlaylists :: Maybe IFrameOnlyPlaylistType
hlsId3SegmentTagging :: Maybe HlsId3SegmentTaggingState
hlsCdnSettings :: Maybe HlsCdnSettings
encryptionType :: Maybe HlsEncryptionType
discontinuityTags :: Maybe HlsDiscontinuityTags
directoryStructure :: Maybe HlsDirectoryStructure
constantIv :: Maybe Text
codecSpecification :: Maybe HlsCodecSpecification
clientCache :: Maybe HlsClientCache
captionLanguageSetting :: Maybe HlsCaptionLanguageSetting
captionLanguageMappings :: Maybe [CaptionLanguageMapping]
baseUrlManifest1 :: Maybe Text
baseUrlManifest :: Maybe Text
baseUrlContent1 :: Maybe Text
baseUrlContent :: Maybe Text
adMarkers :: Maybe [HlsAdMarkers]
$sel:destination:HlsGroupSettings' :: HlsGroupSettings -> OutputLocationRef
$sel:tsFileMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTsFileMode
$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Period:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Frame:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTimedMetadataId3Frame
$sel:streamInfResolution:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsStreamInfResolution
$sel:segmentsPerSubdirectory:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:segmentationMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsSegmentationMode
$sel:segmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:redundantManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsRedundantManifest
$sel:programDateTimePeriod:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:programDateTimeClock:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTimeClock
$sel:programDateTime:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTime
$sel:outputSelection:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsOutputSelection
$sel:mode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsMode
$sel:minSegmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:manifestDurationFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestDurationFormat
$sel:manifestCompression:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestCompression
$sel:keyProviderSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe KeyProviderSettings
$sel:keyFormatVersions:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keyFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keepSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:ivSource:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvSource
$sel:ivInManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvInManifest
$sel:inputLossAction:HlsGroupSettings' :: HlsGroupSettings -> Maybe InputLossActionForHlsOut
$sel:indexNSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:incompleteSegmentBehavior:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIncompleteSegmentBehavior
$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: HlsGroupSettings -> Maybe IFrameOnlyPlaylistType
$sel:hlsId3SegmentTagging:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsId3SegmentTaggingState
$sel:hlsCdnSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCdnSettings
$sel:encryptionType:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsEncryptionType
$sel:discontinuityTags:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDiscontinuityTags
$sel:directoryStructure:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDirectoryStructure
$sel:constantIv:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:codecSpecification:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCodecSpecification
$sel:clientCache:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsClientCache
$sel:captionLanguageSetting:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCaptionLanguageSetting
$sel:captionLanguageMappings:HlsGroupSettings' :: HlsGroupSettings -> Maybe [CaptionLanguageMapping]
$sel:baseUrlManifest1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:adMarkers:HlsGroupSettings' :: HlsGroupSettings -> Maybe [HlsAdMarkers]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [HlsAdMarkers]
adMarkers
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseUrlContent
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseUrlContent1
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseUrlManifest
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseUrlManifest1
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CaptionLanguageMapping]
captionLanguageMappings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsCaptionLanguageSetting
captionLanguageSetting
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsClientCache
clientCache
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsCodecSpecification
codecSpecification
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
constantIv
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsDirectoryStructure
directoryStructure
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsDiscontinuityTags
discontinuityTags
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsEncryptionType
encryptionType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsCdnSettings
hlsCdnSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
indexNSegments
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputLossActionForHlsOut
inputLossAction
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsIvInManifest
ivInManifest
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsIvSource
ivSource
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
keepSegments
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyFormat
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Text
keyFormatVersions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe KeyProviderSettings
keyProviderSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsManifestCompression
manifestCompression
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsManifestDurationFormat
manifestDurationFormat
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
minSegmentLength
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsMode
mode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsOutputSelection
outputSelection
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsProgramDateTime
programDateTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsProgramDateTimeClock
programDateTimeClock
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
programDateTimePeriod
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsRedundantManifest
redundantManifest
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
segmentLength
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsSegmentationMode
segmentationMode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
segmentsPerSubdirectory
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsStreamInfResolution
streamInfResolution
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
timedMetadataId3Period
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
timestampDeltaMilliseconds
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe HlsTsFileMode
tsFileMode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
OutputLocationRef
destination
instance Data.ToJSON HlsGroupSettings where
toJSON :: HlsGroupSettings -> Value
toJSON HlsGroupSettings' {Maybe Natural
Maybe [CaptionLanguageMapping]
Maybe [HlsAdMarkers]
Maybe Text
Maybe HlsCaptionLanguageSetting
Maybe HlsClientCache
Maybe HlsCodecSpecification
Maybe HlsDirectoryStructure
Maybe HlsDiscontinuityTags
Maybe HlsEncryptionType
Maybe HlsId3SegmentTaggingState
Maybe HlsIncompleteSegmentBehavior
Maybe HlsIvInManifest
Maybe HlsIvSource
Maybe HlsManifestCompression
Maybe HlsManifestDurationFormat
Maybe HlsMode
Maybe HlsOutputSelection
Maybe HlsProgramDateTime
Maybe HlsProgramDateTimeClock
Maybe HlsRedundantManifest
Maybe HlsSegmentationMode
Maybe HlsStreamInfResolution
Maybe HlsTimedMetadataId3Frame
Maybe HlsTsFileMode
Maybe IFrameOnlyPlaylistType
Maybe InputLossActionForHlsOut
Maybe HlsCdnSettings
Maybe KeyProviderSettings
OutputLocationRef
destination :: OutputLocationRef
tsFileMode :: Maybe HlsTsFileMode
timestampDeltaMilliseconds :: Maybe Natural
timedMetadataId3Period :: Maybe Natural
timedMetadataId3Frame :: Maybe HlsTimedMetadataId3Frame
streamInfResolution :: Maybe HlsStreamInfResolution
segmentsPerSubdirectory :: Maybe Natural
segmentationMode :: Maybe HlsSegmentationMode
segmentLength :: Maybe Natural
redundantManifest :: Maybe HlsRedundantManifest
programDateTimePeriod :: Maybe Natural
programDateTimeClock :: Maybe HlsProgramDateTimeClock
programDateTime :: Maybe HlsProgramDateTime
outputSelection :: Maybe HlsOutputSelection
mode :: Maybe HlsMode
minSegmentLength :: Maybe Natural
manifestDurationFormat :: Maybe HlsManifestDurationFormat
manifestCompression :: Maybe HlsManifestCompression
keyProviderSettings :: Maybe KeyProviderSettings
keyFormatVersions :: Maybe Text
keyFormat :: Maybe Text
keepSegments :: Maybe Natural
ivSource :: Maybe HlsIvSource
ivInManifest :: Maybe HlsIvInManifest
inputLossAction :: Maybe InputLossActionForHlsOut
indexNSegments :: Maybe Natural
incompleteSegmentBehavior :: Maybe HlsIncompleteSegmentBehavior
iFrameOnlyPlaylists :: Maybe IFrameOnlyPlaylistType
hlsId3SegmentTagging :: Maybe HlsId3SegmentTaggingState
hlsCdnSettings :: Maybe HlsCdnSettings
encryptionType :: Maybe HlsEncryptionType
discontinuityTags :: Maybe HlsDiscontinuityTags
directoryStructure :: Maybe HlsDirectoryStructure
constantIv :: Maybe Text
codecSpecification :: Maybe HlsCodecSpecification
clientCache :: Maybe HlsClientCache
captionLanguageSetting :: Maybe HlsCaptionLanguageSetting
captionLanguageMappings :: Maybe [CaptionLanguageMapping]
baseUrlManifest1 :: Maybe Text
baseUrlManifest :: Maybe Text
baseUrlContent1 :: Maybe Text
baseUrlContent :: Maybe Text
adMarkers :: Maybe [HlsAdMarkers]
$sel:destination:HlsGroupSettings' :: HlsGroupSettings -> OutputLocationRef
$sel:tsFileMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTsFileMode
$sel:timestampDeltaMilliseconds:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Period:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:timedMetadataId3Frame:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsTimedMetadataId3Frame
$sel:streamInfResolution:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsStreamInfResolution
$sel:segmentsPerSubdirectory:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:segmentationMode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsSegmentationMode
$sel:segmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:redundantManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsRedundantManifest
$sel:programDateTimePeriod:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:programDateTimeClock:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTimeClock
$sel:programDateTime:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsProgramDateTime
$sel:outputSelection:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsOutputSelection
$sel:mode:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsMode
$sel:minSegmentLength:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:manifestDurationFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestDurationFormat
$sel:manifestCompression:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsManifestCompression
$sel:keyProviderSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe KeyProviderSettings
$sel:keyFormatVersions:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keyFormat:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:keepSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:ivSource:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvSource
$sel:ivInManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIvInManifest
$sel:inputLossAction:HlsGroupSettings' :: HlsGroupSettings -> Maybe InputLossActionForHlsOut
$sel:indexNSegments:HlsGroupSettings' :: HlsGroupSettings -> Maybe Natural
$sel:incompleteSegmentBehavior:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsIncompleteSegmentBehavior
$sel:iFrameOnlyPlaylists:HlsGroupSettings' :: HlsGroupSettings -> Maybe IFrameOnlyPlaylistType
$sel:hlsId3SegmentTagging:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsId3SegmentTaggingState
$sel:hlsCdnSettings:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCdnSettings
$sel:encryptionType:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsEncryptionType
$sel:discontinuityTags:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDiscontinuityTags
$sel:directoryStructure:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsDirectoryStructure
$sel:constantIv:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:codecSpecification:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCodecSpecification
$sel:clientCache:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsClientCache
$sel:captionLanguageSetting:HlsGroupSettings' :: HlsGroupSettings -> Maybe HlsCaptionLanguageSetting
$sel:captionLanguageMappings:HlsGroupSettings' :: HlsGroupSettings -> Maybe [CaptionLanguageMapping]
$sel:baseUrlManifest1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlManifest:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent1:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:baseUrlContent:HlsGroupSettings' :: HlsGroupSettings -> Maybe Text
$sel:adMarkers:HlsGroupSettings' :: HlsGroupSettings -> Maybe [HlsAdMarkers]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"adMarkers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [HlsAdMarkers]
adMarkers,
(Key
"baseUrlContent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
baseUrlContent,
(Key
"baseUrlContent1" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
baseUrlContent1,
(Key
"baseUrlManifest" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
baseUrlManifest,
(Key
"baseUrlManifest1" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
baseUrlManifest1,
(Key
"captionLanguageMappings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CaptionLanguageMapping]
captionLanguageMappings,
(Key
"captionLanguageSetting" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsCaptionLanguageSetting
captionLanguageSetting,
(Key
"clientCache" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsClientCache
clientCache,
(Key
"codecSpecification" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsCodecSpecification
codecSpecification,
(Key
"constantIv" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
constantIv,
(Key
"directoryStructure" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsDirectoryStructure
directoryStructure,
(Key
"discontinuityTags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsDiscontinuityTags
discontinuityTags,
(Key
"encryptionType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsEncryptionType
encryptionType,
(Key
"hlsCdnSettings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsCdnSettings
hlsCdnSettings,
(Key
"hlsId3SegmentTagging" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsId3SegmentTaggingState
hlsId3SegmentTagging,
(Key
"iFrameOnlyPlaylists" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IFrameOnlyPlaylistType
iFrameOnlyPlaylists,
(Key
"incompleteSegmentBehavior" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsIncompleteSegmentBehavior
incompleteSegmentBehavior,
(Key
"indexNSegments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
indexNSegments,
(Key
"inputLossAction" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputLossActionForHlsOut
inputLossAction,
(Key
"ivInManifest" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsIvInManifest
ivInManifest,
(Key
"ivSource" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsIvSource
ivSource,
(Key
"keepSegments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
keepSegments,
(Key
"keyFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
keyFormat,
(Key
"keyFormatVersions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
keyFormatVersions,
(Key
"keyProviderSettings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KeyProviderSettings
keyProviderSettings,
(Key
"manifestCompression" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsManifestCompression
manifestCompression,
(Key
"manifestDurationFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsManifestDurationFormat
manifestDurationFormat,
(Key
"minSegmentLength" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
minSegmentLength,
(Key
"mode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsMode
mode,
(Key
"outputSelection" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsOutputSelection
outputSelection,
(Key
"programDateTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsProgramDateTime
programDateTime,
(Key
"programDateTimeClock" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsProgramDateTimeClock
programDateTimeClock,
(Key
"programDateTimePeriod" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
programDateTimePeriod,
(Key
"redundantManifest" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsRedundantManifest
redundantManifest,
(Key
"segmentLength" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
segmentLength,
(Key
"segmentationMode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsSegmentationMode
segmentationMode,
(Key
"segmentsPerSubdirectory" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
segmentsPerSubdirectory,
(Key
"streamInfResolution" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsStreamInfResolution
streamInfResolution,
(Key
"timedMetadataId3Frame" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsTimedMetadataId3Frame
timedMetadataId3Frame,
(Key
"timedMetadataId3Period" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timedMetadataId3Period,
(Key
"timestampDeltaMilliseconds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timestampDeltaMilliseconds,
(Key
"tsFileMode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HlsTsFileMode
tsFileMode,
forall a. a -> Maybe a
Prelude.Just (Key
"destination" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= OutputLocationRef
destination)
]
)