{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.MediaLive.Types.Eac3AtmosSettings where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types.Eac3AtmosCodingMode
import Amazonka.MediaLive.Types.Eac3AtmosDrcLine
import Amazonka.MediaLive.Types.Eac3AtmosDrcRf
import qualified Amazonka.Prelude as Prelude
data Eac3AtmosSettings = Eac3AtmosSettings'
{
Eac3AtmosSettings -> Maybe Double
bitrate :: Prelude.Maybe Prelude.Double,
Eac3AtmosSettings -> Maybe Eac3AtmosCodingMode
codingMode :: Prelude.Maybe Eac3AtmosCodingMode,
Eac3AtmosSettings -> Maybe Natural
dialnorm :: Prelude.Maybe Prelude.Natural,
Eac3AtmosSettings -> Maybe Eac3AtmosDrcLine
drcLine :: Prelude.Maybe Eac3AtmosDrcLine,
Eac3AtmosSettings -> Maybe Eac3AtmosDrcRf
drcRf :: Prelude.Maybe Eac3AtmosDrcRf,
Eac3AtmosSettings -> Maybe Double
heightTrim :: Prelude.Maybe Prelude.Double,
Eac3AtmosSettings -> Maybe Double
surroundTrim :: Prelude.Maybe Prelude.Double
}
deriving (Eac3AtmosSettings -> Eac3AtmosSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Eac3AtmosSettings -> Eac3AtmosSettings -> Bool
$c/= :: Eac3AtmosSettings -> Eac3AtmosSettings -> Bool
== :: Eac3AtmosSettings -> Eac3AtmosSettings -> Bool
$c== :: Eac3AtmosSettings -> Eac3AtmosSettings -> Bool
Prelude.Eq, ReadPrec [Eac3AtmosSettings]
ReadPrec Eac3AtmosSettings
Int -> ReadS Eac3AtmosSettings
ReadS [Eac3AtmosSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Eac3AtmosSettings]
$creadListPrec :: ReadPrec [Eac3AtmosSettings]
readPrec :: ReadPrec Eac3AtmosSettings
$creadPrec :: ReadPrec Eac3AtmosSettings
readList :: ReadS [Eac3AtmosSettings]
$creadList :: ReadS [Eac3AtmosSettings]
readsPrec :: Int -> ReadS Eac3AtmosSettings
$creadsPrec :: Int -> ReadS Eac3AtmosSettings
Prelude.Read, Int -> Eac3AtmosSettings -> ShowS
[Eac3AtmosSettings] -> ShowS
Eac3AtmosSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Eac3AtmosSettings] -> ShowS
$cshowList :: [Eac3AtmosSettings] -> ShowS
show :: Eac3AtmosSettings -> String
$cshow :: Eac3AtmosSettings -> String
showsPrec :: Int -> Eac3AtmosSettings -> ShowS
$cshowsPrec :: Int -> Eac3AtmosSettings -> ShowS
Prelude.Show, forall x. Rep Eac3AtmosSettings x -> Eac3AtmosSettings
forall x. Eac3AtmosSettings -> Rep Eac3AtmosSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Eac3AtmosSettings x -> Eac3AtmosSettings
$cfrom :: forall x. Eac3AtmosSettings -> Rep Eac3AtmosSettings x
Prelude.Generic)
newEac3AtmosSettings ::
Eac3AtmosSettings
newEac3AtmosSettings :: Eac3AtmosSettings
newEac3AtmosSettings =
Eac3AtmosSettings'
{ $sel:bitrate:Eac3AtmosSettings' :: Maybe Double
bitrate = forall a. Maybe a
Prelude.Nothing,
$sel:codingMode:Eac3AtmosSettings' :: Maybe Eac3AtmosCodingMode
codingMode = forall a. Maybe a
Prelude.Nothing,
$sel:dialnorm:Eac3AtmosSettings' :: Maybe Natural
dialnorm = forall a. Maybe a
Prelude.Nothing,
$sel:drcLine:Eac3AtmosSettings' :: Maybe Eac3AtmosDrcLine
drcLine = forall a. Maybe a
Prelude.Nothing,
$sel:drcRf:Eac3AtmosSettings' :: Maybe Eac3AtmosDrcRf
drcRf = forall a. Maybe a
Prelude.Nothing,
$sel:heightTrim:Eac3AtmosSettings' :: Maybe Double
heightTrim = forall a. Maybe a
Prelude.Nothing,
$sel:surroundTrim:Eac3AtmosSettings' :: Maybe Double
surroundTrim = forall a. Maybe a
Prelude.Nothing
}
eac3AtmosSettings_bitrate :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Prelude.Double)
eac3AtmosSettings_bitrate :: Lens' Eac3AtmosSettings (Maybe Double)
eac3AtmosSettings_bitrate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Double
bitrate :: Maybe Double
$sel:bitrate:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
bitrate} -> Maybe Double
bitrate) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Double
a -> Eac3AtmosSettings
s {$sel:bitrate:Eac3AtmosSettings' :: Maybe Double
bitrate = Maybe Double
a} :: Eac3AtmosSettings)
eac3AtmosSettings_codingMode :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Eac3AtmosCodingMode)
eac3AtmosSettings_codingMode :: Lens' Eac3AtmosSettings (Maybe Eac3AtmosCodingMode)
eac3AtmosSettings_codingMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Eac3AtmosCodingMode
codingMode :: Maybe Eac3AtmosCodingMode
$sel:codingMode:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosCodingMode
codingMode} -> Maybe Eac3AtmosCodingMode
codingMode) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Eac3AtmosCodingMode
a -> Eac3AtmosSettings
s {$sel:codingMode:Eac3AtmosSettings' :: Maybe Eac3AtmosCodingMode
codingMode = Maybe Eac3AtmosCodingMode
a} :: Eac3AtmosSettings)
eac3AtmosSettings_dialnorm :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Prelude.Natural)
eac3AtmosSettings_dialnorm :: Lens' Eac3AtmosSettings (Maybe Natural)
eac3AtmosSettings_dialnorm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Natural
dialnorm :: Maybe Natural
$sel:dialnorm:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Natural
dialnorm} -> Maybe Natural
dialnorm) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Natural
a -> Eac3AtmosSettings
s {$sel:dialnorm:Eac3AtmosSettings' :: Maybe Natural
dialnorm = Maybe Natural
a} :: Eac3AtmosSettings)
eac3AtmosSettings_drcLine :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Eac3AtmosDrcLine)
eac3AtmosSettings_drcLine :: Lens' Eac3AtmosSettings (Maybe Eac3AtmosDrcLine)
eac3AtmosSettings_drcLine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Eac3AtmosDrcLine
drcLine :: Maybe Eac3AtmosDrcLine
$sel:drcLine:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcLine
drcLine} -> Maybe Eac3AtmosDrcLine
drcLine) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Eac3AtmosDrcLine
a -> Eac3AtmosSettings
s {$sel:drcLine:Eac3AtmosSettings' :: Maybe Eac3AtmosDrcLine
drcLine = Maybe Eac3AtmosDrcLine
a} :: Eac3AtmosSettings)
eac3AtmosSettings_drcRf :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Eac3AtmosDrcRf)
eac3AtmosSettings_drcRf :: Lens' Eac3AtmosSettings (Maybe Eac3AtmosDrcRf)
eac3AtmosSettings_drcRf = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Eac3AtmosDrcRf
drcRf :: Maybe Eac3AtmosDrcRf
$sel:drcRf:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcRf
drcRf} -> Maybe Eac3AtmosDrcRf
drcRf) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Eac3AtmosDrcRf
a -> Eac3AtmosSettings
s {$sel:drcRf:Eac3AtmosSettings' :: Maybe Eac3AtmosDrcRf
drcRf = Maybe Eac3AtmosDrcRf
a} :: Eac3AtmosSettings)
eac3AtmosSettings_heightTrim :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Prelude.Double)
eac3AtmosSettings_heightTrim :: Lens' Eac3AtmosSettings (Maybe Double)
eac3AtmosSettings_heightTrim = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Double
heightTrim :: Maybe Double
$sel:heightTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
heightTrim} -> Maybe Double
heightTrim) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Double
a -> Eac3AtmosSettings
s {$sel:heightTrim:Eac3AtmosSettings' :: Maybe Double
heightTrim = Maybe Double
a} :: Eac3AtmosSettings)
eac3AtmosSettings_surroundTrim :: Lens.Lens' Eac3AtmosSettings (Prelude.Maybe Prelude.Double)
eac3AtmosSettings_surroundTrim :: Lens' Eac3AtmosSettings (Maybe Double)
eac3AtmosSettings_surroundTrim = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Eac3AtmosSettings' {Maybe Double
surroundTrim :: Maybe Double
$sel:surroundTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
surroundTrim} -> Maybe Double
surroundTrim) (\s :: Eac3AtmosSettings
s@Eac3AtmosSettings' {} Maybe Double
a -> Eac3AtmosSettings
s {$sel:surroundTrim:Eac3AtmosSettings' :: Maybe Double
surroundTrim = Maybe Double
a} :: Eac3AtmosSettings)
instance Data.FromJSON Eac3AtmosSettings where
parseJSON :: Value -> Parser Eac3AtmosSettings
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"Eac3AtmosSettings"
( \Object
x ->
Maybe Double
-> Maybe Eac3AtmosCodingMode
-> Maybe Natural
-> Maybe Eac3AtmosDrcLine
-> Maybe Eac3AtmosDrcRf
-> Maybe Double
-> Maybe Double
-> Eac3AtmosSettings
Eac3AtmosSettings'
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
"bitrate")
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
"codingMode")
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
"dialnorm")
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
"drcLine")
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
"drcRf")
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
"heightTrim")
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
"surroundTrim")
)
instance Prelude.Hashable Eac3AtmosSettings where
hashWithSalt :: Int -> Eac3AtmosSettings -> Int
hashWithSalt Int
_salt Eac3AtmosSettings' {Maybe Double
Maybe Natural
Maybe Eac3AtmosCodingMode
Maybe Eac3AtmosDrcLine
Maybe Eac3AtmosDrcRf
surroundTrim :: Maybe Double
heightTrim :: Maybe Double
drcRf :: Maybe Eac3AtmosDrcRf
drcLine :: Maybe Eac3AtmosDrcLine
dialnorm :: Maybe Natural
codingMode :: Maybe Eac3AtmosCodingMode
bitrate :: Maybe Double
$sel:surroundTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:heightTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:drcRf:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcRf
$sel:drcLine:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcLine
$sel:dialnorm:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Natural
$sel:codingMode:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosCodingMode
$sel:bitrate:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
bitrate
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Eac3AtmosCodingMode
codingMode
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
dialnorm
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Eac3AtmosDrcLine
drcLine
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Eac3AtmosDrcRf
drcRf
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
heightTrim
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
surroundTrim
instance Prelude.NFData Eac3AtmosSettings where
rnf :: Eac3AtmosSettings -> ()
rnf Eac3AtmosSettings' {Maybe Double
Maybe Natural
Maybe Eac3AtmosCodingMode
Maybe Eac3AtmosDrcLine
Maybe Eac3AtmosDrcRf
surroundTrim :: Maybe Double
heightTrim :: Maybe Double
drcRf :: Maybe Eac3AtmosDrcRf
drcLine :: Maybe Eac3AtmosDrcLine
dialnorm :: Maybe Natural
codingMode :: Maybe Eac3AtmosCodingMode
bitrate :: Maybe Double
$sel:surroundTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:heightTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:drcRf:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcRf
$sel:drcLine:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcLine
$sel:dialnorm:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Natural
$sel:codingMode:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosCodingMode
$sel:bitrate:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
bitrate
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Eac3AtmosCodingMode
codingMode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
dialnorm
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Eac3AtmosDrcLine
drcLine
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Eac3AtmosDrcRf
drcRf
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
heightTrim
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
surroundTrim
instance Data.ToJSON Eac3AtmosSettings where
toJSON :: Eac3AtmosSettings -> Value
toJSON Eac3AtmosSettings' {Maybe Double
Maybe Natural
Maybe Eac3AtmosCodingMode
Maybe Eac3AtmosDrcLine
Maybe Eac3AtmosDrcRf
surroundTrim :: Maybe Double
heightTrim :: Maybe Double
drcRf :: Maybe Eac3AtmosDrcRf
drcLine :: Maybe Eac3AtmosDrcLine
dialnorm :: Maybe Natural
codingMode :: Maybe Eac3AtmosCodingMode
bitrate :: Maybe Double
$sel:surroundTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:heightTrim:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
$sel:drcRf:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcRf
$sel:drcLine:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosDrcLine
$sel:dialnorm:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Natural
$sel:codingMode:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Eac3AtmosCodingMode
$sel:bitrate:Eac3AtmosSettings' :: Eac3AtmosSettings -> Maybe Double
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"bitrate" 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
bitrate,
(Key
"codingMode" 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 Eac3AtmosCodingMode
codingMode,
(Key
"dialnorm" 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
dialnorm,
(Key
"drcLine" 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 Eac3AtmosDrcLine
drcLine,
(Key
"drcRf" 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 Eac3AtmosDrcRf
drcRf,
(Key
"heightTrim" 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
heightTrim,
(Key
"surroundTrim" 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
surroundTrim
]
)