module Stratosphere.MediaPackage.PackagingConfiguration.CmafPackageProperty (
module Exports, CmafPackageProperty(..), mkCmafPackageProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.MediaPackage.PackagingConfiguration.CmafEncryptionProperty as Exports
import {-# SOURCE #-} Stratosphere.MediaPackage.PackagingConfiguration.HlsManifestProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CmafPackageProperty
=
CmafPackageProperty {CmafPackageProperty -> ()
haddock_workaround_ :: (),
CmafPackageProperty -> Maybe CmafEncryptionProperty
encryption :: (Prelude.Maybe CmafEncryptionProperty),
CmafPackageProperty -> [HlsManifestProperty]
hlsManifests :: [HlsManifestProperty],
CmafPackageProperty -> Maybe (Value Bool)
includeEncoderConfigurationInSegments :: (Prelude.Maybe (Value Prelude.Bool)),
CmafPackageProperty -> Maybe (Value Integer)
segmentDurationSeconds :: (Prelude.Maybe (Value Prelude.Integer))}
deriving stock (CmafPackageProperty -> CmafPackageProperty -> Bool
(CmafPackageProperty -> CmafPackageProperty -> Bool)
-> (CmafPackageProperty -> CmafPackageProperty -> Bool)
-> Eq CmafPackageProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CmafPackageProperty -> CmafPackageProperty -> Bool
== :: CmafPackageProperty -> CmafPackageProperty -> Bool
$c/= :: CmafPackageProperty -> CmafPackageProperty -> Bool
/= :: CmafPackageProperty -> CmafPackageProperty -> Bool
Prelude.Eq, Int -> CmafPackageProperty -> ShowS
[CmafPackageProperty] -> ShowS
CmafPackageProperty -> String
(Int -> CmafPackageProperty -> ShowS)
-> (CmafPackageProperty -> String)
-> ([CmafPackageProperty] -> ShowS)
-> Show CmafPackageProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CmafPackageProperty -> ShowS
showsPrec :: Int -> CmafPackageProperty -> ShowS
$cshow :: CmafPackageProperty -> String
show :: CmafPackageProperty -> String
$cshowList :: [CmafPackageProperty] -> ShowS
showList :: [CmafPackageProperty] -> ShowS
Prelude.Show)
mkCmafPackageProperty ::
[HlsManifestProperty] -> CmafPackageProperty
mkCmafPackageProperty :: [HlsManifestProperty] -> CmafPackageProperty
mkCmafPackageProperty [HlsManifestProperty]
hlsManifests
= CmafPackageProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), hlsManifests :: [HlsManifestProperty]
hlsManifests = [HlsManifestProperty]
hlsManifests,
encryption :: Maybe CmafEncryptionProperty
encryption = Maybe CmafEncryptionProperty
forall a. Maybe a
Prelude.Nothing,
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
includeEncoderConfigurationInSegments = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
segmentDurationSeconds :: Maybe (Value Integer)
segmentDurationSeconds = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties CmafPackageProperty where
toResourceProperties :: CmafPackageProperty -> ResourceProperties
toResourceProperties CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::MediaPackage::PackagingConfiguration.CmafPackage",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"HlsManifests" Key -> [HlsManifestProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [HlsManifestProperty]
hlsManifests]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CmafEncryptionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Encryption" (CmafEncryptionProperty -> (Key, Value))
-> Maybe CmafEncryptionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CmafEncryptionProperty
encryption,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeEncoderConfigurationInSegments"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeEncoderConfigurationInSegments,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SegmentDurationSeconds"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
segmentDurationSeconds]))}
instance JSON.ToJSON CmafPackageProperty where
toJSON :: CmafPackageProperty -> Value
toJSON CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"HlsManifests" Key -> [HlsManifestProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [HlsManifestProperty]
hlsManifests]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CmafEncryptionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Encryption" (CmafEncryptionProperty -> (Key, Value))
-> Maybe CmafEncryptionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CmafEncryptionProperty
encryption,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IncludeEncoderConfigurationInSegments"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
includeEncoderConfigurationInSegments,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SegmentDurationSeconds"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
segmentDurationSeconds])))
instance Property "Encryption" CmafPackageProperty where
type PropertyType "Encryption" CmafPackageProperty = CmafEncryptionProperty
set :: PropertyType "Encryption" CmafPackageProperty
-> CmafPackageProperty -> CmafPackageProperty
set PropertyType "Encryption" CmafPackageProperty
newValue CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= CmafPackageProperty {encryption :: Maybe CmafEncryptionProperty
encryption = CmafEncryptionProperty -> Maybe CmafEncryptionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Encryption" CmafPackageProperty
CmafEncryptionProperty
newValue, [HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
instance Property "HlsManifests" CmafPackageProperty where
type PropertyType "HlsManifests" CmafPackageProperty = [HlsManifestProperty]
set :: PropertyType "HlsManifests" CmafPackageProperty
-> CmafPackageProperty -> CmafPackageProperty
set PropertyType "HlsManifests" CmafPackageProperty
newValue CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= CmafPackageProperty {hlsManifests :: [HlsManifestProperty]
hlsManifests = [HlsManifestProperty]
PropertyType "HlsManifests" CmafPackageProperty
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
instance Property "IncludeEncoderConfigurationInSegments" CmafPackageProperty where
type PropertyType "IncludeEncoderConfigurationInSegments" CmafPackageProperty = Value Prelude.Bool
set :: PropertyType
"IncludeEncoderConfigurationInSegments" CmafPackageProperty
-> CmafPackageProperty -> CmafPackageProperty
set PropertyType
"IncludeEncoderConfigurationInSegments" CmafPackageProperty
newValue CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= CmafPackageProperty
{includeEncoderConfigurationInSegments :: Maybe (Value Bool)
includeEncoderConfigurationInSegments = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"IncludeEncoderConfigurationInSegments" CmafPackageProperty
Value Bool
newValue, [HlsManifestProperty]
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
segmentDurationSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
segmentDurationSeconds :: Maybe (Value Integer)
..}
instance Property "SegmentDurationSeconds" CmafPackageProperty where
type PropertyType "SegmentDurationSeconds" CmafPackageProperty = Value Prelude.Integer
set :: PropertyType "SegmentDurationSeconds" CmafPackageProperty
-> CmafPackageProperty -> CmafPackageProperty
set PropertyType "SegmentDurationSeconds" CmafPackageProperty
newValue CmafPackageProperty {[HlsManifestProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: CmafPackageProperty -> ()
encryption :: CmafPackageProperty -> Maybe CmafEncryptionProperty
hlsManifests :: CmafPackageProperty -> [HlsManifestProperty]
includeEncoderConfigurationInSegments :: CmafPackageProperty -> Maybe (Value Bool)
segmentDurationSeconds :: CmafPackageProperty -> Maybe (Value Integer)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
segmentDurationSeconds :: Maybe (Value Integer)
..}
= CmafPackageProperty
{segmentDurationSeconds :: Maybe (Value Integer)
segmentDurationSeconds = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SegmentDurationSeconds" CmafPackageProperty
Value Integer
newValue, [HlsManifestProperty]
Maybe (Value Bool)
Maybe CmafEncryptionProperty
()
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
haddock_workaround_ :: ()
encryption :: Maybe CmafEncryptionProperty
hlsManifests :: [HlsManifestProperty]
includeEncoderConfigurationInSegments :: Maybe (Value Bool)
..}