{-# 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.MediaConvert.Types.DashIsoGroupSettings
-- 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.MediaConvert.Types.DashIsoGroupSettings where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaConvert.Types.DashAdditionalManifest
import Amazonka.MediaConvert.Types.DashIsoEncryptionSettings
import Amazonka.MediaConvert.Types.DashIsoGroupAudioChannelConfigSchemeIdUri
import Amazonka.MediaConvert.Types.DashIsoHbbtvCompliance
import Amazonka.MediaConvert.Types.DashIsoImageBasedTrickPlay
import Amazonka.MediaConvert.Types.DashIsoImageBasedTrickPlaySettings
import Amazonka.MediaConvert.Types.DashIsoMpdManifestBandwidthType
import Amazonka.MediaConvert.Types.DashIsoMpdProfile
import Amazonka.MediaConvert.Types.DashIsoPtsOffsetHandlingForBFrames
import Amazonka.MediaConvert.Types.DashIsoSegmentControl
import Amazonka.MediaConvert.Types.DashIsoSegmentLengthControl
import Amazonka.MediaConvert.Types.DashIsoVideoCompositionOffsets
import Amazonka.MediaConvert.Types.DashIsoWriteSegmentTimelineInRepresentation
import Amazonka.MediaConvert.Types.DestinationSettings
import qualified Amazonka.Prelude as Prelude

-- | Settings related to your DASH output package. For more information, see
-- https:\/\/docs.aws.amazon.com\/mediaconvert\/latest\/ug\/outputs-file-ABR.html.
-- When you work directly in your JSON job specification, include this
-- object and any required children when you set Type, under
-- OutputGroupSettings, to DASH_ISO_GROUP_SETTINGS.
--
-- /See:/ 'newDashIsoGroupSettings' smart constructor.
data DashIsoGroupSettings = DashIsoGroupSettings'
  { -- | By default, the service creates one .mpd DASH manifest for each DASH ISO
    -- output group in your job. This default manifest references every output
    -- in the output group. To create additional DASH manifests that reference
    -- a subset of the outputs in the output group, specify a list of them
    -- here.
    DashIsoGroupSettings -> Maybe [DashAdditionalManifest]
additionalManifests :: Prelude.Maybe [DashAdditionalManifest],
    -- | Use this setting only when your audio codec is a Dolby one (AC3, EAC3,
    -- or Atmos) and your downstream workflow requires that your DASH manifest
    -- use the Dolby channel configuration tag, rather than the MPEG one. For
    -- example, you might need to use this to make dynamic ad insertion work.
    -- Specify which audio channel configuration scheme ID URI MediaConvert
    -- writes in your DASH manifest. Keep the default value, MPEG channel
    -- configuration (MPEG_CHANNEL_CONFIGURATION), to have MediaConvert write
    -- this: urn:mpeg:mpegB:cicp:ChannelConfiguration. Choose Dolby channel
    -- configuration (DOLBY_CHANNEL_CONFIGURATION) to have MediaConvert write
    -- this instead: tag:dolby.com,2014:dash:audio_channel_configuration:2011.
    DashIsoGroupSettings
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri :: Prelude.Maybe DashIsoGroupAudioChannelConfigSchemeIdUri,
    -- | A partial URI prefix that will be put in the manifest (.mpd) file at the
    -- top level BaseURL element. Can be used if streams are delivered from a
    -- different URL than the manifest file.
    DashIsoGroupSettings -> Maybe Text
baseUrl :: Prelude.Maybe Prelude.Text,
    -- | Use Destination (Destination) to specify the S3 output location and the
    -- output filename base. Destination accepts format identifiers. If you do
    -- not specify the base filename in the URI, the service will use the
    -- filename of the input file. If your job has multiple inputs, the service
    -- uses the filename of the first input file.
    DashIsoGroupSettings -> Maybe Text
destination :: Prelude.Maybe Prelude.Text,
    -- | Settings associated with the destination. Will vary based on the type of
    -- destination
    DashIsoGroupSettings -> Maybe DestinationSettings
destinationSettings :: Prelude.Maybe DestinationSettings,
    -- | DRM settings.
    DashIsoGroupSettings -> Maybe DashIsoEncryptionSettings
encryption :: Prelude.Maybe DashIsoEncryptionSettings,
    -- | Length of fragments to generate (in seconds). Fragment length must be
    -- compatible with GOP size and Framerate. Note that fragments will end on
    -- the next keyframe after this number of seconds, so actual fragment
    -- length may be longer. When Emit Single File is checked, the
    -- fragmentation is internal to a single output file and it does not cause
    -- the creation of many output files as in other output types.
    DashIsoGroupSettings -> Maybe Natural
fragmentLength :: Prelude.Maybe Prelude.Natural,
    -- | Supports HbbTV specification as indicated
    DashIsoGroupSettings -> Maybe DashIsoHbbtvCompliance
hbbtvCompliance :: Prelude.Maybe DashIsoHbbtvCompliance,
    -- | Specify whether MediaConvert generates images for trick play. Keep the
    -- default value, None (NONE), to not generate any images. Choose Thumbnail
    -- (THUMBNAIL) to generate tiled thumbnails. Choose Thumbnail and full
    -- frame (THUMBNAIL_AND_FULLFRAME) to generate tiled thumbnails and
    -- full-resolution images of single frames. MediaConvert adds an entry in
    -- the .mpd manifest for each set of images that you generate. A common
    -- application for these images is Roku trick mode. The thumbnails and
    -- full-frame images that MediaConvert creates with this feature are
    -- compatible with this Roku specification:
    -- https:\/\/developer.roku.com\/docs\/developer-program\/media-playback\/trick-mode\/hls-and-dash.md
    DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay :: Prelude.Maybe DashIsoImageBasedTrickPlay,
    -- | Tile and thumbnail settings applicable when imageBasedTrickPlay is
    -- ADVANCED
    DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings :: Prelude.Maybe DashIsoImageBasedTrickPlaySettings,
    -- | Minimum time of initially buffered media that is needed to ensure smooth
    -- playout.
    DashIsoGroupSettings -> Maybe Natural
minBufferTime :: Prelude.Maybe Prelude.Natural,
    -- | Keep this setting at the default value of 0, unless you are
    -- troubleshooting a problem with how devices play back the end of your
    -- video asset. If you know that player devices are hanging on the final
    -- segment of your video because the length of your final segment is too
    -- short, use this setting to specify a minimum final segment length, in
    -- seconds. Choose a value that is greater than or equal to 1 and less than
    -- your segment length. When you specify a value for this setting, the
    -- encoder will combine any final segment that is shorter than the length
    -- that you specify with the previous segment. For example, your segment
    -- length is 3 seconds and your final segment is .5 seconds without a
    -- minimum final segment length; when you set the minimum final segment
    -- length to 1, your final segment is 3.5 seconds.
    DashIsoGroupSettings -> Maybe Double
minFinalSegmentLength :: Prelude.Maybe Prelude.Double,
    -- | Specify how the value for bandwidth is determined for each video
    -- Representation in your output MPD manifest. We recommend that you choose
    -- a MPD manifest bandwidth type that is compatible with your downstream
    -- player configuration. Max: Use the same value that you specify for Max
    -- bitrate in the video output, in bits per second. Average: Use the
    -- calculated average bitrate of the encoded video output, in bits per
    -- second.
    DashIsoGroupSettings -> Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType :: Prelude.Maybe DashIsoMpdManifestBandwidthType,
    -- | Specify whether your DASH profile is on-demand or main. When you choose
    -- Main profile (MAIN_PROFILE), the service signals
    -- urn:mpeg:dash:profile:isoff-main:2011 in your .mpd DASH manifest. When
    -- you choose On-demand (ON_DEMAND_PROFILE), the service signals
    -- urn:mpeg:dash:profile:isoff-on-demand:2011 in your .mpd. When you choose
    -- On-demand, you must also set the output group setting Segment control
    -- (SegmentControl) to Single file (SINGLE_FILE).
    DashIsoGroupSettings -> Maybe DashIsoMpdProfile
mpdProfile :: Prelude.Maybe DashIsoMpdProfile,
    -- | Use this setting only when your output video stream has B-frames, which
    -- causes the initial presentation time stamp (PTS) to be offset from the
    -- initial decode time stamp (DTS). Specify how MediaConvert handles PTS
    -- when writing time stamps in output DASH manifests. Choose Match initial
    -- PTS (MATCH_INITIAL_PTS) when you want MediaConvert to use the initial
    -- PTS as the first time stamp in the manifest. Choose Zero-based
    -- (ZERO_BASED) to have MediaConvert ignore the initial PTS in the video
    -- stream and instead write the initial time stamp as zero in the manifest.
    -- For outputs that don\'t have B-frames, the time stamps in your DASH
    -- manifests start at zero regardless of your choice here.
    DashIsoGroupSettings -> Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames :: Prelude.Maybe DashIsoPtsOffsetHandlingForBFrames,
    -- | When set to SINGLE_FILE, a single output file is generated, which is
    -- internally segmented using the Fragment Length and Segment Length. When
    -- set to SEGMENTED_FILES, separate segment files will be created.
    DashIsoGroupSettings -> Maybe DashIsoSegmentControl
segmentControl :: Prelude.Maybe DashIsoSegmentControl,
    -- | Specify the length, in whole seconds, of each segment. When you don\'t
    -- specify a value, MediaConvert defaults to 30. Related settings: Use
    -- Segment length control (SegmentLengthControl) to specify whether the
    -- encoder enforces this value strictly. Use Segment control
    -- (DashIsoSegmentControl) to specify whether MediaConvert creates separate
    -- segment files or one content file that has metadata to mark the segment
    -- boundaries.
    DashIsoGroupSettings -> Maybe Natural
segmentLength :: Prelude.Maybe Prelude.Natural,
    -- | Specify how you want MediaConvert to determine the segment length.
    -- Choose Exact (EXACT) to have the encoder use the exact length that you
    -- specify with the setting Segment length (SegmentLength). This might
    -- result in extra I-frames. Choose Multiple of GOP (GOP_MULTIPLE) to have
    -- the encoder round up the segment lengths to match the next GOP boundary.
    DashIsoGroupSettings -> Maybe DashIsoSegmentLengthControl
segmentLengthControl :: Prelude.Maybe DashIsoSegmentLengthControl,
    -- | Specify the video sample composition time offset mode in the output fMP4
    -- TRUN box. For wider player compatibility, set Video composition offsets
    -- to Unsigned or leave blank. The earliest presentation time may be
    -- greater than zero, and sample composition time offsets will increment
    -- using unsigned integers. For strict fMP4 video and audio timing, set
    -- Video composition offsets to Signed. The earliest presentation time will
    -- be equal to zero, and sample composition time offsets will increment
    -- using signed integers.
    DashIsoGroupSettings -> Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets :: Prelude.Maybe DashIsoVideoCompositionOffsets,
    -- | If you get an HTTP error in the 400 range when you play back your DASH
    -- output, enable this setting and run your transcoding job again. When you
    -- enable this setting, the service writes precise segment durations in the
    -- DASH manifest. The segment duration information appears inside the
    -- SegmentTimeline element, inside SegmentTemplate at the Representation
    -- level. When you don\'t enable this setting, the service writes
    -- approximate segment durations in your DASH manifest.
    DashIsoGroupSettings
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation :: Prelude.Maybe DashIsoWriteSegmentTimelineInRepresentation
  }
  deriving (DashIsoGroupSettings -> DashIsoGroupSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DashIsoGroupSettings -> DashIsoGroupSettings -> Bool
$c/= :: DashIsoGroupSettings -> DashIsoGroupSettings -> Bool
== :: DashIsoGroupSettings -> DashIsoGroupSettings -> Bool
$c== :: DashIsoGroupSettings -> DashIsoGroupSettings -> Bool
Prelude.Eq, ReadPrec [DashIsoGroupSettings]
ReadPrec DashIsoGroupSettings
Int -> ReadS DashIsoGroupSettings
ReadS [DashIsoGroupSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DashIsoGroupSettings]
$creadListPrec :: ReadPrec [DashIsoGroupSettings]
readPrec :: ReadPrec DashIsoGroupSettings
$creadPrec :: ReadPrec DashIsoGroupSettings
readList :: ReadS [DashIsoGroupSettings]
$creadList :: ReadS [DashIsoGroupSettings]
readsPrec :: Int -> ReadS DashIsoGroupSettings
$creadsPrec :: Int -> ReadS DashIsoGroupSettings
Prelude.Read, Int -> DashIsoGroupSettings -> ShowS
[DashIsoGroupSettings] -> ShowS
DashIsoGroupSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DashIsoGroupSettings] -> ShowS
$cshowList :: [DashIsoGroupSettings] -> ShowS
show :: DashIsoGroupSettings -> String
$cshow :: DashIsoGroupSettings -> String
showsPrec :: Int -> DashIsoGroupSettings -> ShowS
$cshowsPrec :: Int -> DashIsoGroupSettings -> ShowS
Prelude.Show, forall x. Rep DashIsoGroupSettings x -> DashIsoGroupSettings
forall x. DashIsoGroupSettings -> Rep DashIsoGroupSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DashIsoGroupSettings x -> DashIsoGroupSettings
$cfrom :: forall x. DashIsoGroupSettings -> Rep DashIsoGroupSettings x
Prelude.Generic)

-- |
-- Create a value of 'DashIsoGroupSettings' 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:
--
-- 'additionalManifests', 'dashIsoGroupSettings_additionalManifests' - By default, the service creates one .mpd DASH manifest for each DASH ISO
-- output group in your job. This default manifest references every output
-- in the output group. To create additional DASH manifests that reference
-- a subset of the outputs in the output group, specify a list of them
-- here.
--
-- 'audioChannelConfigSchemeIdUri', 'dashIsoGroupSettings_audioChannelConfigSchemeIdUri' - Use this setting only when your audio codec is a Dolby one (AC3, EAC3,
-- or Atmos) and your downstream workflow requires that your DASH manifest
-- use the Dolby channel configuration tag, rather than the MPEG one. For
-- example, you might need to use this to make dynamic ad insertion work.
-- Specify which audio channel configuration scheme ID URI MediaConvert
-- writes in your DASH manifest. Keep the default value, MPEG channel
-- configuration (MPEG_CHANNEL_CONFIGURATION), to have MediaConvert write
-- this: urn:mpeg:mpegB:cicp:ChannelConfiguration. Choose Dolby channel
-- configuration (DOLBY_CHANNEL_CONFIGURATION) to have MediaConvert write
-- this instead: tag:dolby.com,2014:dash:audio_channel_configuration:2011.
--
-- 'baseUrl', 'dashIsoGroupSettings_baseUrl' - A partial URI prefix that will be put in the manifest (.mpd) file at the
-- top level BaseURL element. Can be used if streams are delivered from a
-- different URL than the manifest file.
--
-- 'destination', 'dashIsoGroupSettings_destination' - Use Destination (Destination) to specify the S3 output location and the
-- output filename base. Destination accepts format identifiers. If you do
-- not specify the base filename in the URI, the service will use the
-- filename of the input file. If your job has multiple inputs, the service
-- uses the filename of the first input file.
--
-- 'destinationSettings', 'dashIsoGroupSettings_destinationSettings' - Settings associated with the destination. Will vary based on the type of
-- destination
--
-- 'encryption', 'dashIsoGroupSettings_encryption' - DRM settings.
--
-- 'fragmentLength', 'dashIsoGroupSettings_fragmentLength' - Length of fragments to generate (in seconds). Fragment length must be
-- compatible with GOP size and Framerate. Note that fragments will end on
-- the next keyframe after this number of seconds, so actual fragment
-- length may be longer. When Emit Single File is checked, the
-- fragmentation is internal to a single output file and it does not cause
-- the creation of many output files as in other output types.
--
-- 'hbbtvCompliance', 'dashIsoGroupSettings_hbbtvCompliance' - Supports HbbTV specification as indicated
--
-- 'imageBasedTrickPlay', 'dashIsoGroupSettings_imageBasedTrickPlay' - Specify whether MediaConvert generates images for trick play. Keep the
-- default value, None (NONE), to not generate any images. Choose Thumbnail
-- (THUMBNAIL) to generate tiled thumbnails. Choose Thumbnail and full
-- frame (THUMBNAIL_AND_FULLFRAME) to generate tiled thumbnails and
-- full-resolution images of single frames. MediaConvert adds an entry in
-- the .mpd manifest for each set of images that you generate. A common
-- application for these images is Roku trick mode. The thumbnails and
-- full-frame images that MediaConvert creates with this feature are
-- compatible with this Roku specification:
-- https:\/\/developer.roku.com\/docs\/developer-program\/media-playback\/trick-mode\/hls-and-dash.md
--
-- 'imageBasedTrickPlaySettings', 'dashIsoGroupSettings_imageBasedTrickPlaySettings' - Tile and thumbnail settings applicable when imageBasedTrickPlay is
-- ADVANCED
--
-- 'minBufferTime', 'dashIsoGroupSettings_minBufferTime' - Minimum time of initially buffered media that is needed to ensure smooth
-- playout.
--
-- 'minFinalSegmentLength', 'dashIsoGroupSettings_minFinalSegmentLength' - Keep this setting at the default value of 0, unless you are
-- troubleshooting a problem with how devices play back the end of your
-- video asset. If you know that player devices are hanging on the final
-- segment of your video because the length of your final segment is too
-- short, use this setting to specify a minimum final segment length, in
-- seconds. Choose a value that is greater than or equal to 1 and less than
-- your segment length. When you specify a value for this setting, the
-- encoder will combine any final segment that is shorter than the length
-- that you specify with the previous segment. For example, your segment
-- length is 3 seconds and your final segment is .5 seconds without a
-- minimum final segment length; when you set the minimum final segment
-- length to 1, your final segment is 3.5 seconds.
--
-- 'mpdManifestBandwidthType', 'dashIsoGroupSettings_mpdManifestBandwidthType' - Specify how the value for bandwidth is determined for each video
-- Representation in your output MPD manifest. We recommend that you choose
-- a MPD manifest bandwidth type that is compatible with your downstream
-- player configuration. Max: Use the same value that you specify for Max
-- bitrate in the video output, in bits per second. Average: Use the
-- calculated average bitrate of the encoded video output, in bits per
-- second.
--
-- 'mpdProfile', 'dashIsoGroupSettings_mpdProfile' - Specify whether your DASH profile is on-demand or main. When you choose
-- Main profile (MAIN_PROFILE), the service signals
-- urn:mpeg:dash:profile:isoff-main:2011 in your .mpd DASH manifest. When
-- you choose On-demand (ON_DEMAND_PROFILE), the service signals
-- urn:mpeg:dash:profile:isoff-on-demand:2011 in your .mpd. When you choose
-- On-demand, you must also set the output group setting Segment control
-- (SegmentControl) to Single file (SINGLE_FILE).
--
-- 'ptsOffsetHandlingForBFrames', 'dashIsoGroupSettings_ptsOffsetHandlingForBFrames' - Use this setting only when your output video stream has B-frames, which
-- causes the initial presentation time stamp (PTS) to be offset from the
-- initial decode time stamp (DTS). Specify how MediaConvert handles PTS
-- when writing time stamps in output DASH manifests. Choose Match initial
-- PTS (MATCH_INITIAL_PTS) when you want MediaConvert to use the initial
-- PTS as the first time stamp in the manifest. Choose Zero-based
-- (ZERO_BASED) to have MediaConvert ignore the initial PTS in the video
-- stream and instead write the initial time stamp as zero in the manifest.
-- For outputs that don\'t have B-frames, the time stamps in your DASH
-- manifests start at zero regardless of your choice here.
--
-- 'segmentControl', 'dashIsoGroupSettings_segmentControl' - When set to SINGLE_FILE, a single output file is generated, which is
-- internally segmented using the Fragment Length and Segment Length. When
-- set to SEGMENTED_FILES, separate segment files will be created.
--
-- 'segmentLength', 'dashIsoGroupSettings_segmentLength' - Specify the length, in whole seconds, of each segment. When you don\'t
-- specify a value, MediaConvert defaults to 30. Related settings: Use
-- Segment length control (SegmentLengthControl) to specify whether the
-- encoder enforces this value strictly. Use Segment control
-- (DashIsoSegmentControl) to specify whether MediaConvert creates separate
-- segment files or one content file that has metadata to mark the segment
-- boundaries.
--
-- 'segmentLengthControl', 'dashIsoGroupSettings_segmentLengthControl' - Specify how you want MediaConvert to determine the segment length.
-- Choose Exact (EXACT) to have the encoder use the exact length that you
-- specify with the setting Segment length (SegmentLength). This might
-- result in extra I-frames. Choose Multiple of GOP (GOP_MULTIPLE) to have
-- the encoder round up the segment lengths to match the next GOP boundary.
--
-- 'videoCompositionOffsets', 'dashIsoGroupSettings_videoCompositionOffsets' - Specify the video sample composition time offset mode in the output fMP4
-- TRUN box. For wider player compatibility, set Video composition offsets
-- to Unsigned or leave blank. The earliest presentation time may be
-- greater than zero, and sample composition time offsets will increment
-- using unsigned integers. For strict fMP4 video and audio timing, set
-- Video composition offsets to Signed. The earliest presentation time will
-- be equal to zero, and sample composition time offsets will increment
-- using signed integers.
--
-- 'writeSegmentTimelineInRepresentation', 'dashIsoGroupSettings_writeSegmentTimelineInRepresentation' - If you get an HTTP error in the 400 range when you play back your DASH
-- output, enable this setting and run your transcoding job again. When you
-- enable this setting, the service writes precise segment durations in the
-- DASH manifest. The segment duration information appears inside the
-- SegmentTimeline element, inside SegmentTemplate at the Representation
-- level. When you don\'t enable this setting, the service writes
-- approximate segment durations in your DASH manifest.
newDashIsoGroupSettings ::
  DashIsoGroupSettings
newDashIsoGroupSettings :: DashIsoGroupSettings
newDashIsoGroupSettings =
  DashIsoGroupSettings'
    { $sel:additionalManifests:DashIsoGroupSettings' :: Maybe [DashAdditionalManifest]
additionalManifests =
        forall a. Maybe a
Prelude.Nothing,
      $sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri = forall a. Maybe a
Prelude.Nothing,
      $sel:baseUrl:DashIsoGroupSettings' :: Maybe Text
baseUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:destination:DashIsoGroupSettings' :: Maybe Text
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationSettings:DashIsoGroupSettings' :: Maybe DestinationSettings
destinationSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:encryption:DashIsoGroupSettings' :: Maybe DashIsoEncryptionSettings
encryption = forall a. Maybe a
Prelude.Nothing,
      $sel:fragmentLength:DashIsoGroupSettings' :: Maybe Natural
fragmentLength = forall a. Maybe a
Prelude.Nothing,
      $sel:hbbtvCompliance:DashIsoGroupSettings' :: Maybe DashIsoHbbtvCompliance
hbbtvCompliance = forall a. Maybe a
Prelude.Nothing,
      $sel:imageBasedTrickPlay:DashIsoGroupSettings' :: Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay = forall a. Maybe a
Prelude.Nothing,
      $sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings = forall a. Maybe a
Prelude.Nothing,
      $sel:minBufferTime:DashIsoGroupSettings' :: Maybe Natural
minBufferTime = forall a. Maybe a
Prelude.Nothing,
      $sel:minFinalSegmentLength:DashIsoGroupSettings' :: Maybe Double
minFinalSegmentLength = forall a. Maybe a
Prelude.Nothing,
      $sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType = forall a. Maybe a
Prelude.Nothing,
      $sel:mpdProfile:DashIsoGroupSettings' :: Maybe DashIsoMpdProfile
mpdProfile = forall a. Maybe a
Prelude.Nothing,
      $sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames = forall a. Maybe a
Prelude.Nothing,
      $sel:segmentControl:DashIsoGroupSettings' :: Maybe DashIsoSegmentControl
segmentControl = forall a. Maybe a
Prelude.Nothing,
      $sel:segmentLength:DashIsoGroupSettings' :: Maybe Natural
segmentLength = forall a. Maybe a
Prelude.Nothing,
      $sel:segmentLengthControl:DashIsoGroupSettings' :: Maybe DashIsoSegmentLengthControl
segmentLengthControl = forall a. Maybe a
Prelude.Nothing,
      $sel:videoCompositionOffsets:DashIsoGroupSettings' :: Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets = forall a. Maybe a
Prelude.Nothing,
      $sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation =
        forall a. Maybe a
Prelude.Nothing
    }

-- | By default, the service creates one .mpd DASH manifest for each DASH ISO
-- output group in your job. This default manifest references every output
-- in the output group. To create additional DASH manifests that reference
-- a subset of the outputs in the output group, specify a list of them
-- here.
dashIsoGroupSettings_additionalManifests :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe [DashAdditionalManifest])
dashIsoGroupSettings_additionalManifests :: Lens' DashIsoGroupSettings (Maybe [DashAdditionalManifest])
dashIsoGroupSettings_additionalManifests = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe [DashAdditionalManifest]
additionalManifests :: Maybe [DashAdditionalManifest]
$sel:additionalManifests:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe [DashAdditionalManifest]
additionalManifests} -> Maybe [DashAdditionalManifest]
additionalManifests) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe [DashAdditionalManifest]
a -> DashIsoGroupSettings
s {$sel:additionalManifests:DashIsoGroupSettings' :: Maybe [DashAdditionalManifest]
additionalManifests = Maybe [DashAdditionalManifest]
a} :: DashIsoGroupSettings) 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

-- | Use this setting only when your audio codec is a Dolby one (AC3, EAC3,
-- or Atmos) and your downstream workflow requires that your DASH manifest
-- use the Dolby channel configuration tag, rather than the MPEG one. For
-- example, you might need to use this to make dynamic ad insertion work.
-- Specify which audio channel configuration scheme ID URI MediaConvert
-- writes in your DASH manifest. Keep the default value, MPEG channel
-- configuration (MPEG_CHANNEL_CONFIGURATION), to have MediaConvert write
-- this: urn:mpeg:mpegB:cicp:ChannelConfiguration. Choose Dolby channel
-- configuration (DOLBY_CHANNEL_CONFIGURATION) to have MediaConvert write
-- this instead: tag:dolby.com,2014:dash:audio_channel_configuration:2011.
dashIsoGroupSettings_audioChannelConfigSchemeIdUri :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoGroupAudioChannelConfigSchemeIdUri)
dashIsoGroupSettings_audioChannelConfigSchemeIdUri :: Lens'
  DashIsoGroupSettings
  (Maybe DashIsoGroupAudioChannelConfigSchemeIdUri)
dashIsoGroupSettings_audioChannelConfigSchemeIdUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
$sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri} -> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
a -> DashIsoGroupSettings
s {$sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri = Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
a} :: DashIsoGroupSettings)

-- | A partial URI prefix that will be put in the manifest (.mpd) file at the
-- top level BaseURL element. Can be used if streams are delivered from a
-- different URL than the manifest file.
dashIsoGroupSettings_baseUrl :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Text)
dashIsoGroupSettings_baseUrl :: Lens' DashIsoGroupSettings (Maybe Text)
dashIsoGroupSettings_baseUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Text
baseUrl :: Maybe Text
$sel:baseUrl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
baseUrl} -> Maybe Text
baseUrl) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Text
a -> DashIsoGroupSettings
s {$sel:baseUrl:DashIsoGroupSettings' :: Maybe Text
baseUrl = Maybe Text
a} :: DashIsoGroupSettings)

-- | Use Destination (Destination) to specify the S3 output location and the
-- output filename base. Destination accepts format identifiers. If you do
-- not specify the base filename in the URI, the service will use the
-- filename of the input file. If your job has multiple inputs, the service
-- uses the filename of the first input file.
dashIsoGroupSettings_destination :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Text)
dashIsoGroupSettings_destination :: Lens' DashIsoGroupSettings (Maybe Text)
dashIsoGroupSettings_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Text
destination :: Maybe Text
$sel:destination:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
destination} -> Maybe Text
destination) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Text
a -> DashIsoGroupSettings
s {$sel:destination:DashIsoGroupSettings' :: Maybe Text
destination = Maybe Text
a} :: DashIsoGroupSettings)

-- | Settings associated with the destination. Will vary based on the type of
-- destination
dashIsoGroupSettings_destinationSettings :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DestinationSettings)
dashIsoGroupSettings_destinationSettings :: Lens' DashIsoGroupSettings (Maybe DestinationSettings)
dashIsoGroupSettings_destinationSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DestinationSettings
destinationSettings :: Maybe DestinationSettings
$sel:destinationSettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DestinationSettings
destinationSettings} -> Maybe DestinationSettings
destinationSettings) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DestinationSettings
a -> DashIsoGroupSettings
s {$sel:destinationSettings:DashIsoGroupSettings' :: Maybe DestinationSettings
destinationSettings = Maybe DestinationSettings
a} :: DashIsoGroupSettings)

-- | DRM settings.
dashIsoGroupSettings_encryption :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoEncryptionSettings)
dashIsoGroupSettings_encryption :: Lens' DashIsoGroupSettings (Maybe DashIsoEncryptionSettings)
dashIsoGroupSettings_encryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoEncryptionSettings
encryption :: Maybe DashIsoEncryptionSettings
$sel:encryption:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoEncryptionSettings
encryption} -> Maybe DashIsoEncryptionSettings
encryption) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoEncryptionSettings
a -> DashIsoGroupSettings
s {$sel:encryption:DashIsoGroupSettings' :: Maybe DashIsoEncryptionSettings
encryption = Maybe DashIsoEncryptionSettings
a} :: DashIsoGroupSettings)

-- | Length of fragments to generate (in seconds). Fragment length must be
-- compatible with GOP size and Framerate. Note that fragments will end on
-- the next keyframe after this number of seconds, so actual fragment
-- length may be longer. When Emit Single File is checked, the
-- fragmentation is internal to a single output file and it does not cause
-- the creation of many output files as in other output types.
dashIsoGroupSettings_fragmentLength :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Natural)
dashIsoGroupSettings_fragmentLength :: Lens' DashIsoGroupSettings (Maybe Natural)
dashIsoGroupSettings_fragmentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Natural
fragmentLength :: Maybe Natural
$sel:fragmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
fragmentLength} -> Maybe Natural
fragmentLength) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Natural
a -> DashIsoGroupSettings
s {$sel:fragmentLength:DashIsoGroupSettings' :: Maybe Natural
fragmentLength = Maybe Natural
a} :: DashIsoGroupSettings)

-- | Supports HbbTV specification as indicated
dashIsoGroupSettings_hbbtvCompliance :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoHbbtvCompliance)
dashIsoGroupSettings_hbbtvCompliance :: Lens' DashIsoGroupSettings (Maybe DashIsoHbbtvCompliance)
dashIsoGroupSettings_hbbtvCompliance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoHbbtvCompliance
hbbtvCompliance :: Maybe DashIsoHbbtvCompliance
$sel:hbbtvCompliance:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoHbbtvCompliance
hbbtvCompliance} -> Maybe DashIsoHbbtvCompliance
hbbtvCompliance) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoHbbtvCompliance
a -> DashIsoGroupSettings
s {$sel:hbbtvCompliance:DashIsoGroupSettings' :: Maybe DashIsoHbbtvCompliance
hbbtvCompliance = Maybe DashIsoHbbtvCompliance
a} :: DashIsoGroupSettings)

-- | Specify whether MediaConvert generates images for trick play. Keep the
-- default value, None (NONE), to not generate any images. Choose Thumbnail
-- (THUMBNAIL) to generate tiled thumbnails. Choose Thumbnail and full
-- frame (THUMBNAIL_AND_FULLFRAME) to generate tiled thumbnails and
-- full-resolution images of single frames. MediaConvert adds an entry in
-- the .mpd manifest for each set of images that you generate. A common
-- application for these images is Roku trick mode. The thumbnails and
-- full-frame images that MediaConvert creates with this feature are
-- compatible with this Roku specification:
-- https:\/\/developer.roku.com\/docs\/developer-program\/media-playback\/trick-mode\/hls-and-dash.md
dashIsoGroupSettings_imageBasedTrickPlay :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoImageBasedTrickPlay)
dashIsoGroupSettings_imageBasedTrickPlay :: Lens' DashIsoGroupSettings (Maybe DashIsoImageBasedTrickPlay)
dashIsoGroupSettings_imageBasedTrickPlay = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay :: Maybe DashIsoImageBasedTrickPlay
$sel:imageBasedTrickPlay:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay} -> Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoImageBasedTrickPlay
a -> DashIsoGroupSettings
s {$sel:imageBasedTrickPlay:DashIsoGroupSettings' :: Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay = Maybe DashIsoImageBasedTrickPlay
a} :: DashIsoGroupSettings)

-- | Tile and thumbnail settings applicable when imageBasedTrickPlay is
-- ADVANCED
dashIsoGroupSettings_imageBasedTrickPlaySettings :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoImageBasedTrickPlaySettings)
dashIsoGroupSettings_imageBasedTrickPlaySettings :: Lens'
  DashIsoGroupSettings (Maybe DashIsoImageBasedTrickPlaySettings)
dashIsoGroupSettings_imageBasedTrickPlaySettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings :: Maybe DashIsoImageBasedTrickPlaySettings
$sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings} -> Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoImageBasedTrickPlaySettings
a -> DashIsoGroupSettings
s {$sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings = Maybe DashIsoImageBasedTrickPlaySettings
a} :: DashIsoGroupSettings)

-- | Minimum time of initially buffered media that is needed to ensure smooth
-- playout.
dashIsoGroupSettings_minBufferTime :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Natural)
dashIsoGroupSettings_minBufferTime :: Lens' DashIsoGroupSettings (Maybe Natural)
dashIsoGroupSettings_minBufferTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Natural
minBufferTime :: Maybe Natural
$sel:minBufferTime:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
minBufferTime} -> Maybe Natural
minBufferTime) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Natural
a -> DashIsoGroupSettings
s {$sel:minBufferTime:DashIsoGroupSettings' :: Maybe Natural
minBufferTime = Maybe Natural
a} :: DashIsoGroupSettings)

-- | Keep this setting at the default value of 0, unless you are
-- troubleshooting a problem with how devices play back the end of your
-- video asset. If you know that player devices are hanging on the final
-- segment of your video because the length of your final segment is too
-- short, use this setting to specify a minimum final segment length, in
-- seconds. Choose a value that is greater than or equal to 1 and less than
-- your segment length. When you specify a value for this setting, the
-- encoder will combine any final segment that is shorter than the length
-- that you specify with the previous segment. For example, your segment
-- length is 3 seconds and your final segment is .5 seconds without a
-- minimum final segment length; when you set the minimum final segment
-- length to 1, your final segment is 3.5 seconds.
dashIsoGroupSettings_minFinalSegmentLength :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Double)
dashIsoGroupSettings_minFinalSegmentLength :: Lens' DashIsoGroupSettings (Maybe Double)
dashIsoGroupSettings_minFinalSegmentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Double
minFinalSegmentLength :: Maybe Double
$sel:minFinalSegmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Double
minFinalSegmentLength} -> Maybe Double
minFinalSegmentLength) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Double
a -> DashIsoGroupSettings
s {$sel:minFinalSegmentLength:DashIsoGroupSettings' :: Maybe Double
minFinalSegmentLength = Maybe Double
a} :: DashIsoGroupSettings)

-- | Specify how the value for bandwidth is determined for each video
-- Representation in your output MPD manifest. We recommend that you choose
-- a MPD manifest bandwidth type that is compatible with your downstream
-- player configuration. Max: Use the same value that you specify for Max
-- bitrate in the video output, in bits per second. Average: Use the
-- calculated average bitrate of the encoded video output, in bits per
-- second.
dashIsoGroupSettings_mpdManifestBandwidthType :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoMpdManifestBandwidthType)
dashIsoGroupSettings_mpdManifestBandwidthType :: Lens' DashIsoGroupSettings (Maybe DashIsoMpdManifestBandwidthType)
dashIsoGroupSettings_mpdManifestBandwidthType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType :: Maybe DashIsoMpdManifestBandwidthType
$sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType} -> Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoMpdManifestBandwidthType
a -> DashIsoGroupSettings
s {$sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType = Maybe DashIsoMpdManifestBandwidthType
a} :: DashIsoGroupSettings)

-- | Specify whether your DASH profile is on-demand or main. When you choose
-- Main profile (MAIN_PROFILE), the service signals
-- urn:mpeg:dash:profile:isoff-main:2011 in your .mpd DASH manifest. When
-- you choose On-demand (ON_DEMAND_PROFILE), the service signals
-- urn:mpeg:dash:profile:isoff-on-demand:2011 in your .mpd. When you choose
-- On-demand, you must also set the output group setting Segment control
-- (SegmentControl) to Single file (SINGLE_FILE).
dashIsoGroupSettings_mpdProfile :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoMpdProfile)
dashIsoGroupSettings_mpdProfile :: Lens' DashIsoGroupSettings (Maybe DashIsoMpdProfile)
dashIsoGroupSettings_mpdProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoMpdProfile
mpdProfile :: Maybe DashIsoMpdProfile
$sel:mpdProfile:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdProfile
mpdProfile} -> Maybe DashIsoMpdProfile
mpdProfile) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoMpdProfile
a -> DashIsoGroupSettings
s {$sel:mpdProfile:DashIsoGroupSettings' :: Maybe DashIsoMpdProfile
mpdProfile = Maybe DashIsoMpdProfile
a} :: DashIsoGroupSettings)

-- | Use this setting only when your output video stream has B-frames, which
-- causes the initial presentation time stamp (PTS) to be offset from the
-- initial decode time stamp (DTS). Specify how MediaConvert handles PTS
-- when writing time stamps in output DASH manifests. Choose Match initial
-- PTS (MATCH_INITIAL_PTS) when you want MediaConvert to use the initial
-- PTS as the first time stamp in the manifest. Choose Zero-based
-- (ZERO_BASED) to have MediaConvert ignore the initial PTS in the video
-- stream and instead write the initial time stamp as zero in the manifest.
-- For outputs that don\'t have B-frames, the time stamps in your DASH
-- manifests start at zero regardless of your choice here.
dashIsoGroupSettings_ptsOffsetHandlingForBFrames :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoPtsOffsetHandlingForBFrames)
dashIsoGroupSettings_ptsOffsetHandlingForBFrames :: Lens'
  DashIsoGroupSettings (Maybe DashIsoPtsOffsetHandlingForBFrames)
dashIsoGroupSettings_ptsOffsetHandlingForBFrames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames :: Maybe DashIsoPtsOffsetHandlingForBFrames
$sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames} -> Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoPtsOffsetHandlingForBFrames
a -> DashIsoGroupSettings
s {$sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames = Maybe DashIsoPtsOffsetHandlingForBFrames
a} :: DashIsoGroupSettings)

-- | When set to SINGLE_FILE, a single output file is generated, which is
-- internally segmented using the Fragment Length and Segment Length. When
-- set to SEGMENTED_FILES, separate segment files will be created.
dashIsoGroupSettings_segmentControl :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoSegmentControl)
dashIsoGroupSettings_segmentControl :: Lens' DashIsoGroupSettings (Maybe DashIsoSegmentControl)
dashIsoGroupSettings_segmentControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoSegmentControl
segmentControl :: Maybe DashIsoSegmentControl
$sel:segmentControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentControl
segmentControl} -> Maybe DashIsoSegmentControl
segmentControl) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoSegmentControl
a -> DashIsoGroupSettings
s {$sel:segmentControl:DashIsoGroupSettings' :: Maybe DashIsoSegmentControl
segmentControl = Maybe DashIsoSegmentControl
a} :: DashIsoGroupSettings)

-- | Specify the length, in whole seconds, of each segment. When you don\'t
-- specify a value, MediaConvert defaults to 30. Related settings: Use
-- Segment length control (SegmentLengthControl) to specify whether the
-- encoder enforces this value strictly. Use Segment control
-- (DashIsoSegmentControl) to specify whether MediaConvert creates separate
-- segment files or one content file that has metadata to mark the segment
-- boundaries.
dashIsoGroupSettings_segmentLength :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe Prelude.Natural)
dashIsoGroupSettings_segmentLength :: Lens' DashIsoGroupSettings (Maybe Natural)
dashIsoGroupSettings_segmentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe Natural
segmentLength :: Maybe Natural
$sel:segmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
segmentLength} -> Maybe Natural
segmentLength) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe Natural
a -> DashIsoGroupSettings
s {$sel:segmentLength:DashIsoGroupSettings' :: Maybe Natural
segmentLength = Maybe Natural
a} :: DashIsoGroupSettings)

-- | Specify how you want MediaConvert to determine the segment length.
-- Choose Exact (EXACT) to have the encoder use the exact length that you
-- specify with the setting Segment length (SegmentLength). This might
-- result in extra I-frames. Choose Multiple of GOP (GOP_MULTIPLE) to have
-- the encoder round up the segment lengths to match the next GOP boundary.
dashIsoGroupSettings_segmentLengthControl :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoSegmentLengthControl)
dashIsoGroupSettings_segmentLengthControl :: Lens' DashIsoGroupSettings (Maybe DashIsoSegmentLengthControl)
dashIsoGroupSettings_segmentLengthControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoSegmentLengthControl
segmentLengthControl :: Maybe DashIsoSegmentLengthControl
$sel:segmentLengthControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentLengthControl
segmentLengthControl} -> Maybe DashIsoSegmentLengthControl
segmentLengthControl) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoSegmentLengthControl
a -> DashIsoGroupSettings
s {$sel:segmentLengthControl:DashIsoGroupSettings' :: Maybe DashIsoSegmentLengthControl
segmentLengthControl = Maybe DashIsoSegmentLengthControl
a} :: DashIsoGroupSettings)

-- | Specify the video sample composition time offset mode in the output fMP4
-- TRUN box. For wider player compatibility, set Video composition offsets
-- to Unsigned or leave blank. The earliest presentation time may be
-- greater than zero, and sample composition time offsets will increment
-- using unsigned integers. For strict fMP4 video and audio timing, set
-- Video composition offsets to Signed. The earliest presentation time will
-- be equal to zero, and sample composition time offsets will increment
-- using signed integers.
dashIsoGroupSettings_videoCompositionOffsets :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoVideoCompositionOffsets)
dashIsoGroupSettings_videoCompositionOffsets :: Lens' DashIsoGroupSettings (Maybe DashIsoVideoCompositionOffsets)
dashIsoGroupSettings_videoCompositionOffsets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets :: Maybe DashIsoVideoCompositionOffsets
$sel:videoCompositionOffsets:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets} -> Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoVideoCompositionOffsets
a -> DashIsoGroupSettings
s {$sel:videoCompositionOffsets:DashIsoGroupSettings' :: Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets = Maybe DashIsoVideoCompositionOffsets
a} :: DashIsoGroupSettings)

-- | If you get an HTTP error in the 400 range when you play back your DASH
-- output, enable this setting and run your transcoding job again. When you
-- enable this setting, the service writes precise segment durations in the
-- DASH manifest. The segment duration information appears inside the
-- SegmentTimeline element, inside SegmentTemplate at the Representation
-- level. When you don\'t enable this setting, the service writes
-- approximate segment durations in your DASH manifest.
dashIsoGroupSettings_writeSegmentTimelineInRepresentation :: Lens.Lens' DashIsoGroupSettings (Prelude.Maybe DashIsoWriteSegmentTimelineInRepresentation)
dashIsoGroupSettings_writeSegmentTimelineInRepresentation :: Lens'
  DashIsoGroupSettings
  (Maybe DashIsoWriteSegmentTimelineInRepresentation)
dashIsoGroupSettings_writeSegmentTimelineInRepresentation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashIsoGroupSettings' {Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation :: Maybe DashIsoWriteSegmentTimelineInRepresentation
$sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation} -> Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation) (\s :: DashIsoGroupSettings
s@DashIsoGroupSettings' {} Maybe DashIsoWriteSegmentTimelineInRepresentation
a -> DashIsoGroupSettings
s {$sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation = Maybe DashIsoWriteSegmentTimelineInRepresentation
a} :: DashIsoGroupSettings)

instance Data.FromJSON DashIsoGroupSettings where
  parseJSON :: Value -> Parser DashIsoGroupSettings
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DashIsoGroupSettings"
      ( \Object
x ->
          Maybe [DashAdditionalManifest]
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
-> Maybe Text
-> Maybe Text
-> Maybe DestinationSettings
-> Maybe DashIsoEncryptionSettings
-> Maybe Natural
-> Maybe DashIsoHbbtvCompliance
-> Maybe DashIsoImageBasedTrickPlay
-> Maybe DashIsoImageBasedTrickPlaySettings
-> Maybe Natural
-> Maybe Double
-> Maybe DashIsoMpdManifestBandwidthType
-> Maybe DashIsoMpdProfile
-> Maybe DashIsoPtsOffsetHandlingForBFrames
-> Maybe DashIsoSegmentControl
-> Maybe Natural
-> Maybe DashIsoSegmentLengthControl
-> Maybe DashIsoVideoCompositionOffsets
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
-> DashIsoGroupSettings
DashIsoGroupSettings'
            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
"additionalManifests"
                            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
"audioChannelConfigSchemeIdUri")
            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
"baseUrl")
            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
"destination")
            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
"destinationSettings")
            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
"encryption")
            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
"fragmentLength")
            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
"hbbtvCompliance")
            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
"imageBasedTrickPlay")
            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
"imageBasedTrickPlaySettings")
            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
"minBufferTime")
            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
"minFinalSegmentLength")
            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
"mpdManifestBandwidthType")
            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
"mpdProfile")
            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
"ptsOffsetHandlingForBFrames")
            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
"segmentControl")
            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
"segmentLengthControl")
            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
"videoCompositionOffsets")
            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
"writeSegmentTimelineInRepresentation")
      )

instance Prelude.Hashable DashIsoGroupSettings where
  hashWithSalt :: Int -> DashIsoGroupSettings -> Int
hashWithSalt Int
_salt DashIsoGroupSettings' {Maybe Double
Maybe Natural
Maybe [DashAdditionalManifest]
Maybe Text
Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
Maybe DashIsoHbbtvCompliance
Maybe DashIsoImageBasedTrickPlay
Maybe DashIsoImageBasedTrickPlaySettings
Maybe DashIsoMpdManifestBandwidthType
Maybe DashIsoMpdProfile
Maybe DashIsoPtsOffsetHandlingForBFrames
Maybe DashIsoSegmentControl
Maybe DashIsoSegmentLengthControl
Maybe DashIsoVideoCompositionOffsets
Maybe DashIsoWriteSegmentTimelineInRepresentation
Maybe DestinationSettings
Maybe DashIsoEncryptionSettings
writeSegmentTimelineInRepresentation :: Maybe DashIsoWriteSegmentTimelineInRepresentation
videoCompositionOffsets :: Maybe DashIsoVideoCompositionOffsets
segmentLengthControl :: Maybe DashIsoSegmentLengthControl
segmentLength :: Maybe Natural
segmentControl :: Maybe DashIsoSegmentControl
ptsOffsetHandlingForBFrames :: Maybe DashIsoPtsOffsetHandlingForBFrames
mpdProfile :: Maybe DashIsoMpdProfile
mpdManifestBandwidthType :: Maybe DashIsoMpdManifestBandwidthType
minFinalSegmentLength :: Maybe Double
minBufferTime :: Maybe Natural
imageBasedTrickPlaySettings :: Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlay :: Maybe DashIsoImageBasedTrickPlay
hbbtvCompliance :: Maybe DashIsoHbbtvCompliance
fragmentLength :: Maybe Natural
encryption :: Maybe DashIsoEncryptionSettings
destinationSettings :: Maybe DestinationSettings
destination :: Maybe Text
baseUrl :: Maybe Text
audioChannelConfigSchemeIdUri :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
additionalManifests :: Maybe [DashAdditionalManifest]
$sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
$sel:videoCompositionOffsets:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoVideoCompositionOffsets
$sel:segmentLengthControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentLengthControl
$sel:segmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:segmentControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentControl
$sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoPtsOffsetHandlingForBFrames
$sel:mpdProfile:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdProfile
$sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdManifestBandwidthType
$sel:minFinalSegmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Double
$sel:minBufferTime:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlaySettings
$sel:imageBasedTrickPlay:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlay
$sel:hbbtvCompliance:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoHbbtvCompliance
$sel:fragmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:encryption:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoEncryptionSettings
$sel:destinationSettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DestinationSettings
$sel:destination:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:baseUrl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
$sel:additionalManifests:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe [DashAdditionalManifest]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DashAdditionalManifest]
additionalManifests
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
baseUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DestinationSettings
destinationSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoEncryptionSettings
encryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
fragmentLength
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoHbbtvCompliance
hbbtvCompliance
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
minBufferTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
minFinalSegmentLength
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoMpdProfile
mpdProfile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoSegmentControl
segmentControl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
segmentLength
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoSegmentLengthControl
segmentLengthControl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation

instance Prelude.NFData DashIsoGroupSettings where
  rnf :: DashIsoGroupSettings -> ()
rnf DashIsoGroupSettings' {Maybe Double
Maybe Natural
Maybe [DashAdditionalManifest]
Maybe Text
Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
Maybe DashIsoHbbtvCompliance
Maybe DashIsoImageBasedTrickPlay
Maybe DashIsoImageBasedTrickPlaySettings
Maybe DashIsoMpdManifestBandwidthType
Maybe DashIsoMpdProfile
Maybe DashIsoPtsOffsetHandlingForBFrames
Maybe DashIsoSegmentControl
Maybe DashIsoSegmentLengthControl
Maybe DashIsoVideoCompositionOffsets
Maybe DashIsoWriteSegmentTimelineInRepresentation
Maybe DestinationSettings
Maybe DashIsoEncryptionSettings
writeSegmentTimelineInRepresentation :: Maybe DashIsoWriteSegmentTimelineInRepresentation
videoCompositionOffsets :: Maybe DashIsoVideoCompositionOffsets
segmentLengthControl :: Maybe DashIsoSegmentLengthControl
segmentLength :: Maybe Natural
segmentControl :: Maybe DashIsoSegmentControl
ptsOffsetHandlingForBFrames :: Maybe DashIsoPtsOffsetHandlingForBFrames
mpdProfile :: Maybe DashIsoMpdProfile
mpdManifestBandwidthType :: Maybe DashIsoMpdManifestBandwidthType
minFinalSegmentLength :: Maybe Double
minBufferTime :: Maybe Natural
imageBasedTrickPlaySettings :: Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlay :: Maybe DashIsoImageBasedTrickPlay
hbbtvCompliance :: Maybe DashIsoHbbtvCompliance
fragmentLength :: Maybe Natural
encryption :: Maybe DashIsoEncryptionSettings
destinationSettings :: Maybe DestinationSettings
destination :: Maybe Text
baseUrl :: Maybe Text
audioChannelConfigSchemeIdUri :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
additionalManifests :: Maybe [DashAdditionalManifest]
$sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
$sel:videoCompositionOffsets:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoVideoCompositionOffsets
$sel:segmentLengthControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentLengthControl
$sel:segmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:segmentControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentControl
$sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoPtsOffsetHandlingForBFrames
$sel:mpdProfile:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdProfile
$sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdManifestBandwidthType
$sel:minFinalSegmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Double
$sel:minBufferTime:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlaySettings
$sel:imageBasedTrickPlay:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlay
$sel:hbbtvCompliance:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoHbbtvCompliance
$sel:fragmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:encryption:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoEncryptionSettings
$sel:destinationSettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DestinationSettings
$sel:destination:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:baseUrl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
$sel:additionalManifests:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe [DashAdditionalManifest]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DashAdditionalManifest]
additionalManifests
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DestinationSettings
destinationSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoEncryptionSettings
encryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
fragmentLength
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoHbbtvCompliance
hbbtvCompliance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoImageBasedTrickPlay
imageBasedTrickPlay
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
minBufferTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
minFinalSegmentLength
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoMpdProfile
mpdProfile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DashIsoSegmentControl
segmentControl
      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 DashIsoSegmentLengthControl
segmentLengthControl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe DashIsoVideoCompositionOffsets
videoCompositionOffsets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation

instance Data.ToJSON DashIsoGroupSettings where
  toJSON :: DashIsoGroupSettings -> Value
toJSON DashIsoGroupSettings' {Maybe Double
Maybe Natural
Maybe [DashAdditionalManifest]
Maybe Text
Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
Maybe DashIsoHbbtvCompliance
Maybe DashIsoImageBasedTrickPlay
Maybe DashIsoImageBasedTrickPlaySettings
Maybe DashIsoMpdManifestBandwidthType
Maybe DashIsoMpdProfile
Maybe DashIsoPtsOffsetHandlingForBFrames
Maybe DashIsoSegmentControl
Maybe DashIsoSegmentLengthControl
Maybe DashIsoVideoCompositionOffsets
Maybe DashIsoWriteSegmentTimelineInRepresentation
Maybe DestinationSettings
Maybe DashIsoEncryptionSettings
writeSegmentTimelineInRepresentation :: Maybe DashIsoWriteSegmentTimelineInRepresentation
videoCompositionOffsets :: Maybe DashIsoVideoCompositionOffsets
segmentLengthControl :: Maybe DashIsoSegmentLengthControl
segmentLength :: Maybe Natural
segmentControl :: Maybe DashIsoSegmentControl
ptsOffsetHandlingForBFrames :: Maybe DashIsoPtsOffsetHandlingForBFrames
mpdProfile :: Maybe DashIsoMpdProfile
mpdManifestBandwidthType :: Maybe DashIsoMpdManifestBandwidthType
minFinalSegmentLength :: Maybe Double
minBufferTime :: Maybe Natural
imageBasedTrickPlaySettings :: Maybe DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlay :: Maybe DashIsoImageBasedTrickPlay
hbbtvCompliance :: Maybe DashIsoHbbtvCompliance
fragmentLength :: Maybe Natural
encryption :: Maybe DashIsoEncryptionSettings
destinationSettings :: Maybe DestinationSettings
destination :: Maybe Text
baseUrl :: Maybe Text
audioChannelConfigSchemeIdUri :: Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
additionalManifests :: Maybe [DashAdditionalManifest]
$sel:writeSegmentTimelineInRepresentation:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoWriteSegmentTimelineInRepresentation
$sel:videoCompositionOffsets:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoVideoCompositionOffsets
$sel:segmentLengthControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentLengthControl
$sel:segmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:segmentControl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoSegmentControl
$sel:ptsOffsetHandlingForBFrames:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoPtsOffsetHandlingForBFrames
$sel:mpdProfile:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdProfile
$sel:mpdManifestBandwidthType:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoMpdManifestBandwidthType
$sel:minFinalSegmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Double
$sel:minBufferTime:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:imageBasedTrickPlaySettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlaySettings
$sel:imageBasedTrickPlay:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoImageBasedTrickPlay
$sel:hbbtvCompliance:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoHbbtvCompliance
$sel:fragmentLength:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Natural
$sel:encryption:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DashIsoEncryptionSettings
$sel:destinationSettings:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe DestinationSettings
$sel:destination:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:baseUrl:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe Text
$sel:audioChannelConfigSchemeIdUri:DashIsoGroupSettings' :: DashIsoGroupSettings
-> Maybe DashIsoGroupAudioChannelConfigSchemeIdUri
$sel:additionalManifests:DashIsoGroupSettings' :: DashIsoGroupSettings -> Maybe [DashAdditionalManifest]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"additionalManifests" 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 [DashAdditionalManifest]
additionalManifests,
            (Key
"audioChannelConfigSchemeIdUri" 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 DashIsoGroupAudioChannelConfigSchemeIdUri
audioChannelConfigSchemeIdUri,
            (Key
"baseUrl" 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
baseUrl,
            (Key
"destination" 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
destination,
            (Key
"destinationSettings" 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 DestinationSettings
destinationSettings,
            (Key
"encryption" 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 DashIsoEncryptionSettings
encryption,
            (Key
"fragmentLength" 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
fragmentLength,
            (Key
"hbbtvCompliance" 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 DashIsoHbbtvCompliance
hbbtvCompliance,
            (Key
"imageBasedTrickPlay" 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 DashIsoImageBasedTrickPlay
imageBasedTrickPlay,
            (Key
"imageBasedTrickPlaySettings" 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 DashIsoImageBasedTrickPlaySettings
imageBasedTrickPlaySettings,
            (Key
"minBufferTime" 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
minBufferTime,
            (Key
"minFinalSegmentLength" 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 Double
minFinalSegmentLength,
            (Key
"mpdManifestBandwidthType" 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 DashIsoMpdManifestBandwidthType
mpdManifestBandwidthType,
            (Key
"mpdProfile" 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 DashIsoMpdProfile
mpdProfile,
            (Key
"ptsOffsetHandlingForBFrames" 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 DashIsoPtsOffsetHandlingForBFrames
ptsOffsetHandlingForBFrames,
            (Key
"segmentControl" 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 DashIsoSegmentControl
segmentControl,
            (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
"segmentLengthControl" 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 DashIsoSegmentLengthControl
segmentLengthControl,
            (Key
"videoCompositionOffsets" 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 DashIsoVideoCompositionOffsets
videoCompositionOffsets,
            (Key
"writeSegmentTimelineInRepresentation" 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 DashIsoWriteSegmentTimelineInRepresentation
writeSegmentTimelineInRepresentation
          ]
      )