{-# 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.AutomatedAbrRule
-- 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.AutomatedAbrRule 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.AllowedRenditionSize
import Amazonka.MediaConvert.Types.ForceIncludeRenditionSize
import Amazonka.MediaConvert.Types.MinBottomRenditionSize
import Amazonka.MediaConvert.Types.MinTopRenditionSize
import Amazonka.MediaConvert.Types.RuleType
import qualified Amazonka.Prelude as Prelude

-- | Specify one or more Automated ABR rule types. Note: Force include and
-- Allowed renditions are mutually exclusive.
--
-- /See:/ 'newAutomatedAbrRule' smart constructor.
data AutomatedAbrRule = AutomatedAbrRule'
  { -- | When customer adds the allowed renditions rule for auto ABR ladder, they
    -- are required to add at leat one rendition to allowedRenditions list
    AutomatedAbrRule -> Maybe [AllowedRenditionSize]
allowedRenditions :: Prelude.Maybe [AllowedRenditionSize],
    -- | When customer adds the force include renditions rule for auto ABR
    -- ladder, they are required to add at leat one rendition to
    -- forceIncludeRenditions list
    AutomatedAbrRule -> Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions :: Prelude.Maybe [ForceIncludeRenditionSize],
    -- | Use Min bottom rendition size to specify a minimum size for the lowest
    -- resolution in your ABR stack. * The lowest resolution in your ABR stack
    -- will be equal to or greater than the value that you enter. For example:
    -- If you specify 640x360 the lowest resolution in your ABR stack will be
    -- equal to or greater than to 640x360. * If you specify a Min top
    -- rendition size rule, the value that you specify for Min bottom rendition
    -- size must be less than, or equal to, Min top rendition size.
    AutomatedAbrRule -> Maybe MinBottomRenditionSize
minBottomRenditionSize :: Prelude.Maybe MinBottomRenditionSize,
    -- | Use Min top rendition size to specify a minimum size for the highest
    -- resolution in your ABR stack. * The highest resolution in your ABR stack
    -- will be equal to or greater than the value that you enter. For example:
    -- If you specify 1280x720 the highest resolution in your ABR stack will be
    -- equal to or greater than 1280x720. * If you specify a value for Max
    -- resolution, the value that you specify for Min top rendition size must
    -- be less than, or equal to, Max resolution.
    AutomatedAbrRule -> Maybe MinTopRenditionSize
minTopRenditionSize :: Prelude.Maybe MinTopRenditionSize,
    -- | Use Min top rendition size to specify a minimum size for the highest
    -- resolution in your ABR stack. * The highest resolution in your ABR stack
    -- will be equal to or greater than the value that you enter. For example:
    -- If you specify 1280x720 the highest resolution in your ABR stack will be
    -- equal to or greater than 1280x720. * If you specify a value for Max
    -- resolution, the value that you specify for Min top rendition size must
    -- be less than, or equal to, Max resolution. Use Min bottom rendition size
    -- to specify a minimum size for the lowest resolution in your ABR stack. *
    -- The lowest resolution in your ABR stack will be equal to or greater than
    -- the value that you enter. For example: If you specify 640x360 the lowest
    -- resolution in your ABR stack will be equal to or greater than to
    -- 640x360. * If you specify a Min top rendition size rule, the value that
    -- you specify for Min bottom rendition size must be less than, or equal
    -- to, Min top rendition size. Use Force include renditions to specify one
    -- or more resolutions to include your ABR stack. * (Recommended) To
    -- optimize automated ABR, specify as few resolutions as possible. *
    -- (Required) The number of resolutions that you specify must be equal to,
    -- or less than, the Max renditions setting. * If you specify a Min top
    -- rendition size rule, specify at least one resolution that is equal to,
    -- or greater than, Min top rendition size. * If you specify a Min bottom
    -- rendition size rule, only specify resolutions that are equal to, or
    -- greater than, Min bottom rendition size. * If you specify a Force
    -- include renditions rule, do not specify a separate rule for Allowed
    -- renditions. * Note: The ABR stack may include other resolutions that you
    -- do not specify here, depending on the Max renditions setting. Use
    -- Allowed renditions to specify a list of possible resolutions in your ABR
    -- stack. * (Required) The number of resolutions that you specify must be
    -- equal to, or greater than, the Max renditions setting. * MediaConvert
    -- will create an ABR stack exclusively from the list of resolutions that
    -- you specify. * Some resolutions in the Allowed renditions list may not
    -- be included, however you can force a resolution to be included by
    -- setting Required to ENABLED. * You must specify at least one resolution
    -- that is greater than or equal to any resolutions that you specify in Min
    -- top rendition size or Min bottom rendition size. * If you specify
    -- Allowed renditions, you must not specify a separate rule for Force
    -- include renditions.
    AutomatedAbrRule -> Maybe RuleType
type' :: Prelude.Maybe RuleType
  }
  deriving (AutomatedAbrRule -> AutomatedAbrRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutomatedAbrRule -> AutomatedAbrRule -> Bool
$c/= :: AutomatedAbrRule -> AutomatedAbrRule -> Bool
== :: AutomatedAbrRule -> AutomatedAbrRule -> Bool
$c== :: AutomatedAbrRule -> AutomatedAbrRule -> Bool
Prelude.Eq, ReadPrec [AutomatedAbrRule]
ReadPrec AutomatedAbrRule
Int -> ReadS AutomatedAbrRule
ReadS [AutomatedAbrRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutomatedAbrRule]
$creadListPrec :: ReadPrec [AutomatedAbrRule]
readPrec :: ReadPrec AutomatedAbrRule
$creadPrec :: ReadPrec AutomatedAbrRule
readList :: ReadS [AutomatedAbrRule]
$creadList :: ReadS [AutomatedAbrRule]
readsPrec :: Int -> ReadS AutomatedAbrRule
$creadsPrec :: Int -> ReadS AutomatedAbrRule
Prelude.Read, Int -> AutomatedAbrRule -> ShowS
[AutomatedAbrRule] -> ShowS
AutomatedAbrRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutomatedAbrRule] -> ShowS
$cshowList :: [AutomatedAbrRule] -> ShowS
show :: AutomatedAbrRule -> String
$cshow :: AutomatedAbrRule -> String
showsPrec :: Int -> AutomatedAbrRule -> ShowS
$cshowsPrec :: Int -> AutomatedAbrRule -> ShowS
Prelude.Show, forall x. Rep AutomatedAbrRule x -> AutomatedAbrRule
forall x. AutomatedAbrRule -> Rep AutomatedAbrRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AutomatedAbrRule x -> AutomatedAbrRule
$cfrom :: forall x. AutomatedAbrRule -> Rep AutomatedAbrRule x
Prelude.Generic)

-- |
-- Create a value of 'AutomatedAbrRule' 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:
--
-- 'allowedRenditions', 'automatedAbrRule_allowedRenditions' - When customer adds the allowed renditions rule for auto ABR ladder, they
-- are required to add at leat one rendition to allowedRenditions list
--
-- 'forceIncludeRenditions', 'automatedAbrRule_forceIncludeRenditions' - When customer adds the force include renditions rule for auto ABR
-- ladder, they are required to add at leat one rendition to
-- forceIncludeRenditions list
--
-- 'minBottomRenditionSize', 'automatedAbrRule_minBottomRenditionSize' - Use Min bottom rendition size to specify a minimum size for the lowest
-- resolution in your ABR stack. * The lowest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 640x360 the lowest resolution in your ABR stack will be
-- equal to or greater than to 640x360. * If you specify a Min top
-- rendition size rule, the value that you specify for Min bottom rendition
-- size must be less than, or equal to, Min top rendition size.
--
-- 'minTopRenditionSize', 'automatedAbrRule_minTopRenditionSize' - Use Min top rendition size to specify a minimum size for the highest
-- resolution in your ABR stack. * The highest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 1280x720 the highest resolution in your ABR stack will be
-- equal to or greater than 1280x720. * If you specify a value for Max
-- resolution, the value that you specify for Min top rendition size must
-- be less than, or equal to, Max resolution.
--
-- 'type'', 'automatedAbrRule_type' - Use Min top rendition size to specify a minimum size for the highest
-- resolution in your ABR stack. * The highest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 1280x720 the highest resolution in your ABR stack will be
-- equal to or greater than 1280x720. * If you specify a value for Max
-- resolution, the value that you specify for Min top rendition size must
-- be less than, or equal to, Max resolution. Use Min bottom rendition size
-- to specify a minimum size for the lowest resolution in your ABR stack. *
-- The lowest resolution in your ABR stack will be equal to or greater than
-- the value that you enter. For example: If you specify 640x360 the lowest
-- resolution in your ABR stack will be equal to or greater than to
-- 640x360. * If you specify a Min top rendition size rule, the value that
-- you specify for Min bottom rendition size must be less than, or equal
-- to, Min top rendition size. Use Force include renditions to specify one
-- or more resolutions to include your ABR stack. * (Recommended) To
-- optimize automated ABR, specify as few resolutions as possible. *
-- (Required) The number of resolutions that you specify must be equal to,
-- or less than, the Max renditions setting. * If you specify a Min top
-- rendition size rule, specify at least one resolution that is equal to,
-- or greater than, Min top rendition size. * If you specify a Min bottom
-- rendition size rule, only specify resolutions that are equal to, or
-- greater than, Min bottom rendition size. * If you specify a Force
-- include renditions rule, do not specify a separate rule for Allowed
-- renditions. * Note: The ABR stack may include other resolutions that you
-- do not specify here, depending on the Max renditions setting. Use
-- Allowed renditions to specify a list of possible resolutions in your ABR
-- stack. * (Required) The number of resolutions that you specify must be
-- equal to, or greater than, the Max renditions setting. * MediaConvert
-- will create an ABR stack exclusively from the list of resolutions that
-- you specify. * Some resolutions in the Allowed renditions list may not
-- be included, however you can force a resolution to be included by
-- setting Required to ENABLED. * You must specify at least one resolution
-- that is greater than or equal to any resolutions that you specify in Min
-- top rendition size or Min bottom rendition size. * If you specify
-- Allowed renditions, you must not specify a separate rule for Force
-- include renditions.
newAutomatedAbrRule ::
  AutomatedAbrRule
newAutomatedAbrRule :: AutomatedAbrRule
newAutomatedAbrRule =
  AutomatedAbrRule'
    { $sel:allowedRenditions:AutomatedAbrRule' :: Maybe [AllowedRenditionSize]
allowedRenditions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:forceIncludeRenditions:AutomatedAbrRule' :: Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions = forall a. Maybe a
Prelude.Nothing,
      $sel:minBottomRenditionSize:AutomatedAbrRule' :: Maybe MinBottomRenditionSize
minBottomRenditionSize = forall a. Maybe a
Prelude.Nothing,
      $sel:minTopRenditionSize:AutomatedAbrRule' :: Maybe MinTopRenditionSize
minTopRenditionSize = forall a. Maybe a
Prelude.Nothing,
      $sel:type':AutomatedAbrRule' :: Maybe RuleType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | When customer adds the allowed renditions rule for auto ABR ladder, they
-- are required to add at leat one rendition to allowedRenditions list
automatedAbrRule_allowedRenditions :: Lens.Lens' AutomatedAbrRule (Prelude.Maybe [AllowedRenditionSize])
automatedAbrRule_allowedRenditions :: Lens' AutomatedAbrRule (Maybe [AllowedRenditionSize])
automatedAbrRule_allowedRenditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomatedAbrRule' {Maybe [AllowedRenditionSize]
allowedRenditions :: Maybe [AllowedRenditionSize]
$sel:allowedRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [AllowedRenditionSize]
allowedRenditions} -> Maybe [AllowedRenditionSize]
allowedRenditions) (\s :: AutomatedAbrRule
s@AutomatedAbrRule' {} Maybe [AllowedRenditionSize]
a -> AutomatedAbrRule
s {$sel:allowedRenditions:AutomatedAbrRule' :: Maybe [AllowedRenditionSize]
allowedRenditions = Maybe [AllowedRenditionSize]
a} :: AutomatedAbrRule) 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

-- | When customer adds the force include renditions rule for auto ABR
-- ladder, they are required to add at leat one rendition to
-- forceIncludeRenditions list
automatedAbrRule_forceIncludeRenditions :: Lens.Lens' AutomatedAbrRule (Prelude.Maybe [ForceIncludeRenditionSize])
automatedAbrRule_forceIncludeRenditions :: Lens' AutomatedAbrRule (Maybe [ForceIncludeRenditionSize])
automatedAbrRule_forceIncludeRenditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomatedAbrRule' {Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions :: Maybe [ForceIncludeRenditionSize]
$sel:forceIncludeRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions} -> Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions) (\s :: AutomatedAbrRule
s@AutomatedAbrRule' {} Maybe [ForceIncludeRenditionSize]
a -> AutomatedAbrRule
s {$sel:forceIncludeRenditions:AutomatedAbrRule' :: Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions = Maybe [ForceIncludeRenditionSize]
a} :: AutomatedAbrRule) 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 Min bottom rendition size to specify a minimum size for the lowest
-- resolution in your ABR stack. * The lowest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 640x360 the lowest resolution in your ABR stack will be
-- equal to or greater than to 640x360. * If you specify a Min top
-- rendition size rule, the value that you specify for Min bottom rendition
-- size must be less than, or equal to, Min top rendition size.
automatedAbrRule_minBottomRenditionSize :: Lens.Lens' AutomatedAbrRule (Prelude.Maybe MinBottomRenditionSize)
automatedAbrRule_minBottomRenditionSize :: Lens' AutomatedAbrRule (Maybe MinBottomRenditionSize)
automatedAbrRule_minBottomRenditionSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomatedAbrRule' {Maybe MinBottomRenditionSize
minBottomRenditionSize :: Maybe MinBottomRenditionSize
$sel:minBottomRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinBottomRenditionSize
minBottomRenditionSize} -> Maybe MinBottomRenditionSize
minBottomRenditionSize) (\s :: AutomatedAbrRule
s@AutomatedAbrRule' {} Maybe MinBottomRenditionSize
a -> AutomatedAbrRule
s {$sel:minBottomRenditionSize:AutomatedAbrRule' :: Maybe MinBottomRenditionSize
minBottomRenditionSize = Maybe MinBottomRenditionSize
a} :: AutomatedAbrRule)

-- | Use Min top rendition size to specify a minimum size for the highest
-- resolution in your ABR stack. * The highest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 1280x720 the highest resolution in your ABR stack will be
-- equal to or greater than 1280x720. * If you specify a value for Max
-- resolution, the value that you specify for Min top rendition size must
-- be less than, or equal to, Max resolution.
automatedAbrRule_minTopRenditionSize :: Lens.Lens' AutomatedAbrRule (Prelude.Maybe MinTopRenditionSize)
automatedAbrRule_minTopRenditionSize :: Lens' AutomatedAbrRule (Maybe MinTopRenditionSize)
automatedAbrRule_minTopRenditionSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomatedAbrRule' {Maybe MinTopRenditionSize
minTopRenditionSize :: Maybe MinTopRenditionSize
$sel:minTopRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinTopRenditionSize
minTopRenditionSize} -> Maybe MinTopRenditionSize
minTopRenditionSize) (\s :: AutomatedAbrRule
s@AutomatedAbrRule' {} Maybe MinTopRenditionSize
a -> AutomatedAbrRule
s {$sel:minTopRenditionSize:AutomatedAbrRule' :: Maybe MinTopRenditionSize
minTopRenditionSize = Maybe MinTopRenditionSize
a} :: AutomatedAbrRule)

-- | Use Min top rendition size to specify a minimum size for the highest
-- resolution in your ABR stack. * The highest resolution in your ABR stack
-- will be equal to or greater than the value that you enter. For example:
-- If you specify 1280x720 the highest resolution in your ABR stack will be
-- equal to or greater than 1280x720. * If you specify a value for Max
-- resolution, the value that you specify for Min top rendition size must
-- be less than, or equal to, Max resolution. Use Min bottom rendition size
-- to specify a minimum size for the lowest resolution in your ABR stack. *
-- The lowest resolution in your ABR stack will be equal to or greater than
-- the value that you enter. For example: If you specify 640x360 the lowest
-- resolution in your ABR stack will be equal to or greater than to
-- 640x360. * If you specify a Min top rendition size rule, the value that
-- you specify for Min bottom rendition size must be less than, or equal
-- to, Min top rendition size. Use Force include renditions to specify one
-- or more resolutions to include your ABR stack. * (Recommended) To
-- optimize automated ABR, specify as few resolutions as possible. *
-- (Required) The number of resolutions that you specify must be equal to,
-- or less than, the Max renditions setting. * If you specify a Min top
-- rendition size rule, specify at least one resolution that is equal to,
-- or greater than, Min top rendition size. * If you specify a Min bottom
-- rendition size rule, only specify resolutions that are equal to, or
-- greater than, Min bottom rendition size. * If you specify a Force
-- include renditions rule, do not specify a separate rule for Allowed
-- renditions. * Note: The ABR stack may include other resolutions that you
-- do not specify here, depending on the Max renditions setting. Use
-- Allowed renditions to specify a list of possible resolutions in your ABR
-- stack. * (Required) The number of resolutions that you specify must be
-- equal to, or greater than, the Max renditions setting. * MediaConvert
-- will create an ABR stack exclusively from the list of resolutions that
-- you specify. * Some resolutions in the Allowed renditions list may not
-- be included, however you can force a resolution to be included by
-- setting Required to ENABLED. * You must specify at least one resolution
-- that is greater than or equal to any resolutions that you specify in Min
-- top rendition size or Min bottom rendition size. * If you specify
-- Allowed renditions, you must not specify a separate rule for Force
-- include renditions.
automatedAbrRule_type :: Lens.Lens' AutomatedAbrRule (Prelude.Maybe RuleType)
automatedAbrRule_type :: Lens' AutomatedAbrRule (Maybe RuleType)
automatedAbrRule_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomatedAbrRule' {Maybe RuleType
type' :: Maybe RuleType
$sel:type':AutomatedAbrRule' :: AutomatedAbrRule -> Maybe RuleType
type'} -> Maybe RuleType
type') (\s :: AutomatedAbrRule
s@AutomatedAbrRule' {} Maybe RuleType
a -> AutomatedAbrRule
s {$sel:type':AutomatedAbrRule' :: Maybe RuleType
type' = Maybe RuleType
a} :: AutomatedAbrRule)

instance Data.FromJSON AutomatedAbrRule where
  parseJSON :: Value -> Parser AutomatedAbrRule
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AutomatedAbrRule"
      ( \Object
x ->
          Maybe [AllowedRenditionSize]
-> Maybe [ForceIncludeRenditionSize]
-> Maybe MinBottomRenditionSize
-> Maybe MinTopRenditionSize
-> Maybe RuleType
-> AutomatedAbrRule
AutomatedAbrRule'
            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
"allowedRenditions"
                            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
"forceIncludeRenditions"
                            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
"minBottomRenditionSize")
            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
"minTopRenditionSize")
            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
"type")
      )

instance Prelude.Hashable AutomatedAbrRule where
  hashWithSalt :: Int -> AutomatedAbrRule -> Int
hashWithSalt Int
_salt AutomatedAbrRule' {Maybe [ForceIncludeRenditionSize]
Maybe [AllowedRenditionSize]
Maybe MinBottomRenditionSize
Maybe MinTopRenditionSize
Maybe RuleType
type' :: Maybe RuleType
minTopRenditionSize :: Maybe MinTopRenditionSize
minBottomRenditionSize :: Maybe MinBottomRenditionSize
forceIncludeRenditions :: Maybe [ForceIncludeRenditionSize]
allowedRenditions :: Maybe [AllowedRenditionSize]
$sel:type':AutomatedAbrRule' :: AutomatedAbrRule -> Maybe RuleType
$sel:minTopRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinTopRenditionSize
$sel:minBottomRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinBottomRenditionSize
$sel:forceIncludeRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [ForceIncludeRenditionSize]
$sel:allowedRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [AllowedRenditionSize]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AllowedRenditionSize]
allowedRenditions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MinBottomRenditionSize
minBottomRenditionSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MinTopRenditionSize
minTopRenditionSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RuleType
type'

instance Prelude.NFData AutomatedAbrRule where
  rnf :: AutomatedAbrRule -> ()
rnf AutomatedAbrRule' {Maybe [ForceIncludeRenditionSize]
Maybe [AllowedRenditionSize]
Maybe MinBottomRenditionSize
Maybe MinTopRenditionSize
Maybe RuleType
type' :: Maybe RuleType
minTopRenditionSize :: Maybe MinTopRenditionSize
minBottomRenditionSize :: Maybe MinBottomRenditionSize
forceIncludeRenditions :: Maybe [ForceIncludeRenditionSize]
allowedRenditions :: Maybe [AllowedRenditionSize]
$sel:type':AutomatedAbrRule' :: AutomatedAbrRule -> Maybe RuleType
$sel:minTopRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinTopRenditionSize
$sel:minBottomRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinBottomRenditionSize
$sel:forceIncludeRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [ForceIncludeRenditionSize]
$sel:allowedRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [AllowedRenditionSize]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AllowedRenditionSize]
allowedRenditions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ForceIncludeRenditionSize]
forceIncludeRenditions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MinBottomRenditionSize
minBottomRenditionSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MinTopRenditionSize
minTopRenditionSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RuleType
type'

instance Data.ToJSON AutomatedAbrRule where
  toJSON :: AutomatedAbrRule -> Value
toJSON AutomatedAbrRule' {Maybe [ForceIncludeRenditionSize]
Maybe [AllowedRenditionSize]
Maybe MinBottomRenditionSize
Maybe MinTopRenditionSize
Maybe RuleType
type' :: Maybe RuleType
minTopRenditionSize :: Maybe MinTopRenditionSize
minBottomRenditionSize :: Maybe MinBottomRenditionSize
forceIncludeRenditions :: Maybe [ForceIncludeRenditionSize]
allowedRenditions :: Maybe [AllowedRenditionSize]
$sel:type':AutomatedAbrRule' :: AutomatedAbrRule -> Maybe RuleType
$sel:minTopRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinTopRenditionSize
$sel:minBottomRenditionSize:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe MinBottomRenditionSize
$sel:forceIncludeRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [ForceIncludeRenditionSize]
$sel:allowedRenditions:AutomatedAbrRule' :: AutomatedAbrRule -> Maybe [AllowedRenditionSize]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"allowedRenditions" 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 [AllowedRenditionSize]
allowedRenditions,
            (Key
"forceIncludeRenditions" 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 [ForceIncludeRenditionSize]
forceIncludeRenditions,
            (Key
"minBottomRenditionSize" 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 MinBottomRenditionSize
minBottomRenditionSize,
            (Key
"minTopRenditionSize" 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 MinTopRenditionSize
minTopRenditionSize,
            (Key
"type" 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 RuleType
type'
          ]
      )