module Stratosphere.MediaPackage.PackagingConfiguration.EncryptionContractConfigurationProperty (
        EncryptionContractConfigurationProperty(..),
        mkEncryptionContractConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data EncryptionContractConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-mediapackage-packagingconfiguration-encryptioncontractconfiguration.html>
    EncryptionContractConfigurationProperty {EncryptionContractConfigurationProperty -> ()
haddock_workaround_ :: (),
                                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-mediapackage-packagingconfiguration-encryptioncontractconfiguration.html#cfn-mediapackage-packagingconfiguration-encryptioncontractconfiguration-presetspeke20audio>
                                             EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Audio :: (Value Prelude.Text),
                                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-mediapackage-packagingconfiguration-encryptioncontractconfiguration.html#cfn-mediapackage-packagingconfiguration-encryptioncontractconfiguration-presetspeke20video>
                                             EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Video :: (Value Prelude.Text)}
  deriving stock (EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty -> Bool
(EncryptionContractConfigurationProperty
 -> EncryptionContractConfigurationProperty -> Bool)
-> (EncryptionContractConfigurationProperty
    -> EncryptionContractConfigurationProperty -> Bool)
-> Eq EncryptionContractConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty -> Bool
== :: EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty -> Bool
$c/= :: EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty -> Bool
/= :: EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty -> Bool
Prelude.Eq, Int -> EncryptionContractConfigurationProperty -> ShowS
[EncryptionContractConfigurationProperty] -> ShowS
EncryptionContractConfigurationProperty -> String
(Int -> EncryptionContractConfigurationProperty -> ShowS)
-> (EncryptionContractConfigurationProperty -> String)
-> ([EncryptionContractConfigurationProperty] -> ShowS)
-> Show EncryptionContractConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EncryptionContractConfigurationProperty -> ShowS
showsPrec :: Int -> EncryptionContractConfigurationProperty -> ShowS
$cshow :: EncryptionContractConfigurationProperty -> String
show :: EncryptionContractConfigurationProperty -> String
$cshowList :: [EncryptionContractConfigurationProperty] -> ShowS
showList :: [EncryptionContractConfigurationProperty] -> ShowS
Prelude.Show)
mkEncryptionContractConfigurationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> EncryptionContractConfigurationProperty
mkEncryptionContractConfigurationProperty :: Value Text -> Value Text -> EncryptionContractConfigurationProperty
mkEncryptionContractConfigurationProperty
  Value Text
presetSpeke20Audio
  Value Text
presetSpeke20Video
  = EncryptionContractConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), presetSpeke20Audio :: Value Text
presetSpeke20Audio = Value Text
presetSpeke20Audio,
       presetSpeke20Video :: Value Text
presetSpeke20Video = Value Text
presetSpeke20Video}
instance ToResourceProperties EncryptionContractConfigurationProperty where
  toResourceProperties :: EncryptionContractConfigurationProperty -> ResourceProperties
toResourceProperties EncryptionContractConfigurationProperty {()
Value Text
haddock_workaround_ :: EncryptionContractConfigurationProperty -> ()
presetSpeke20Audio :: EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Video :: EncryptionContractConfigurationProperty -> Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
presetSpeke20Video :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::MediaPackage::PackagingConfiguration.EncryptionContractConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"PresetSpeke20Audio" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
presetSpeke20Audio,
                       Key
"PresetSpeke20Video" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
presetSpeke20Video]}
instance JSON.ToJSON EncryptionContractConfigurationProperty where
  toJSON :: EncryptionContractConfigurationProperty -> Value
toJSON EncryptionContractConfigurationProperty {()
Value Text
haddock_workaround_ :: EncryptionContractConfigurationProperty -> ()
presetSpeke20Audio :: EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Video :: EncryptionContractConfigurationProperty -> Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
presetSpeke20Video :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"PresetSpeke20Audio" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
presetSpeke20Audio,
         Key
"PresetSpeke20Video" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
presetSpeke20Video]
instance Property "PresetSpeke20Audio" EncryptionContractConfigurationProperty where
  type PropertyType "PresetSpeke20Audio" EncryptionContractConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "PresetSpeke20Audio" EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty
set PropertyType
  "PresetSpeke20Audio" EncryptionContractConfigurationProperty
newValue EncryptionContractConfigurationProperty {()
Value Text
haddock_workaround_ :: EncryptionContractConfigurationProperty -> ()
presetSpeke20Audio :: EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Video :: EncryptionContractConfigurationProperty -> Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
presetSpeke20Video :: Value Text
..}
    = EncryptionContractConfigurationProperty
        {presetSpeke20Audio :: Value Text
presetSpeke20Audio = PropertyType
  "PresetSpeke20Audio" EncryptionContractConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
presetSpeke20Video :: Value Text
haddock_workaround_ :: ()
presetSpeke20Video :: Value Text
..}
instance Property "PresetSpeke20Video" EncryptionContractConfigurationProperty where
  type PropertyType "PresetSpeke20Video" EncryptionContractConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "PresetSpeke20Video" EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty
-> EncryptionContractConfigurationProperty
set PropertyType
  "PresetSpeke20Video" EncryptionContractConfigurationProperty
newValue EncryptionContractConfigurationProperty {()
Value Text
haddock_workaround_ :: EncryptionContractConfigurationProperty -> ()
presetSpeke20Audio :: EncryptionContractConfigurationProperty -> Value Text
presetSpeke20Video :: EncryptionContractConfigurationProperty -> Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
presetSpeke20Video :: Value Text
..}
    = EncryptionContractConfigurationProperty
        {presetSpeke20Video :: Value Text
presetSpeke20Video = PropertyType
  "PresetSpeke20Video" EncryptionContractConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
haddock_workaround_ :: ()
presetSpeke20Audio :: Value Text
..}