module Stratosphere.MediaLive.Channel.HtmlMotionGraphicsSettingsProperty (
        HtmlMotionGraphicsSettingsProperty(..),
        mkHtmlMotionGraphicsSettingsProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.ResourceProperties
data HtmlMotionGraphicsSettingsProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-medialive-channel-htmlmotiongraphicssettings.html>
    HtmlMotionGraphicsSettingsProperty {HtmlMotionGraphicsSettingsProperty -> ()
haddock_workaround_ :: ()}
  deriving stock (HtmlMotionGraphicsSettingsProperty
-> HtmlMotionGraphicsSettingsProperty -> Bool
(HtmlMotionGraphicsSettingsProperty
 -> HtmlMotionGraphicsSettingsProperty -> Bool)
-> (HtmlMotionGraphicsSettingsProperty
    -> HtmlMotionGraphicsSettingsProperty -> Bool)
-> Eq HtmlMotionGraphicsSettingsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HtmlMotionGraphicsSettingsProperty
-> HtmlMotionGraphicsSettingsProperty -> Bool
== :: HtmlMotionGraphicsSettingsProperty
-> HtmlMotionGraphicsSettingsProperty -> Bool
$c/= :: HtmlMotionGraphicsSettingsProperty
-> HtmlMotionGraphicsSettingsProperty -> Bool
/= :: HtmlMotionGraphicsSettingsProperty
-> HtmlMotionGraphicsSettingsProperty -> Bool
Prelude.Eq, Int -> HtmlMotionGraphicsSettingsProperty -> ShowS
[HtmlMotionGraphicsSettingsProperty] -> ShowS
HtmlMotionGraphicsSettingsProperty -> String
(Int -> HtmlMotionGraphicsSettingsProperty -> ShowS)
-> (HtmlMotionGraphicsSettingsProperty -> String)
-> ([HtmlMotionGraphicsSettingsProperty] -> ShowS)
-> Show HtmlMotionGraphicsSettingsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HtmlMotionGraphicsSettingsProperty -> ShowS
showsPrec :: Int -> HtmlMotionGraphicsSettingsProperty -> ShowS
$cshow :: HtmlMotionGraphicsSettingsProperty -> String
show :: HtmlMotionGraphicsSettingsProperty -> String
$cshowList :: [HtmlMotionGraphicsSettingsProperty] -> ShowS
showList :: [HtmlMotionGraphicsSettingsProperty] -> ShowS
Prelude.Show)
mkHtmlMotionGraphicsSettingsProperty ::
  HtmlMotionGraphicsSettingsProperty
mkHtmlMotionGraphicsSettingsProperty :: HtmlMotionGraphicsSettingsProperty
mkHtmlMotionGraphicsSettingsProperty
  = HtmlMotionGraphicsSettingsProperty {haddock_workaround_ :: ()
haddock_workaround_ = ()}
instance ToResourceProperties HtmlMotionGraphicsSettingsProperty where
  toResourceProperties :: HtmlMotionGraphicsSettingsProperty -> ResourceProperties
toResourceProperties HtmlMotionGraphicsSettingsProperty {}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::MediaLive::Channel.HtmlMotionGraphicsSettings",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = []}
instance JSON.ToJSON HtmlMotionGraphicsSettingsProperty where
  toJSON :: HtmlMotionGraphicsSettingsProperty -> Value
toJSON HtmlMotionGraphicsSettingsProperty {} = [Pair] -> Value
JSON.object []