{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.MusicVideoObject where

--  Valid: 2016-03-21 (Schema.rdfs.org)

import Text.HTML5.MetaData.Class
import Text.HTML5.MetaData.Type
import Data.Text
import Data.Typeable
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.Thing
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.CreativeWork
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.MediaObject

-- | A music video file.
--
--   [@id@] MusicVideoObject
--
--   [@label@] Music Video Object
--
--   [@comment@] A music video file.
--
--   [@ancestors@] @'Thing','CreativeWork','MediaObject'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'MediaObject'@
--
--   [@url@] <http://schema.org/MusicVideoObject>
data MusicVideoObject = MusicVideoObject { associatedArticle :: AssociatedArticle
                                         , bitrate :: Bitrate
                                         , contentSize :: ContentSize
                                         , contentUrl :: ContentUrl
                                         , duration :: Duration
                                         , embedUrl :: EmbedUrl
                                         , encodesCreativeWork :: EncodesCreativeWork
                                         , encodingFormat :: EncodingFormat
                                         , expires :: Expires
                                         , height :: Height
                                         , playerType :: PlayerType
                                         , productionCompany :: ProductionCompany
                                         , regionsAllowed :: RegionsAllowed
                                         , requiresSubscription :: RequiresSubscription
                                         , uploadDate :: UploadDate
                                         , width :: Width
                                         , about :: About
                                         , accessibilityAPI :: AccessibilityAPI
                                         , accessibilityControl :: AccessibilityControl
                                         , accessibilityFeature :: AccessibilityFeature
                                         , accessibilityHazard :: AccessibilityHazard
                                         , accountablePerson :: AccountablePerson
                                         , aggregateRating :: AggregateRating
                                         , alternativeHeadline :: AlternativeHeadline
                                         , associatedMedia :: AssociatedMedia
                                         , audience :: Audience
                                         , audio :: Audio
                                         , author :: Author
                                         , award :: Award
                                         , character :: Character
                                         , citation :: Citation
                                         , comment :: Comment
                                         , commentCount :: CommentCount
                                         , contentLocation :: ContentLocation
                                         , contentRating :: ContentRating
                                         , contributor :: Contributor
                                         , copyrightHolder :: CopyrightHolder
                                         , copyrightYear :: CopyrightYear
                                         , creator :: Creator
                                         , dateCreated :: DateCreated
                                         , dateModified :: DateModified
                                         , datePublished :: DatePublished
                                         , discussionUrl :: DiscussionUrl
                                         , editor :: Editor
                                         , educationalAlignment :: EducationalAlignment
                                         , educationalUse :: EducationalUse
                                         , encoding :: Encoding
                                         , exampleOfWork :: ExampleOfWork
                                         , fileFormat :: FileFormat
                                         , genre :: Genre
                                         , hasPart :: HasPart
                                         , headline :: Headline
                                         , inLanguage :: InLanguage
                                         , interactionStatistic :: InteractionStatistic
                                         , interactivityType :: InteractivityType
                                         , isBasedOnUrl :: IsBasedOnUrl
                                         , isFamilyFriendly :: IsFamilyFriendly
                                         , isPartOf :: IsPartOf
                                         , keywords :: Keywords
                                         , learningResourceType :: LearningResourceType
                                         , license :: License
                                         , locationCreated :: LocationCreated
                                         , mainEntity :: MainEntity
                                         , mentions :: Mentions
                                         , offers :: Offers
                                         , position :: Position
                                         , producer :: Producer
                                         , provider :: Provider
                                         , publication :: Publication
                                         , publisher :: Publisher
                                         , publishingPrinciples :: PublishingPrinciples
                                         , recordedAt :: RecordedAt
                                         , releasedEvent :: ReleasedEvent
                                         , review :: Review
                                         , schemaVersion :: SchemaVersion
                                         , sourceOrganization :: SourceOrganization
                                         , text :: Text
                                         , thumbnailUrl :: ThumbnailUrl
                                         , timeRequired :: TimeRequired
                                         , translator :: Translator
                                         , typicalAgeRange :: TypicalAgeRange
                                         , version :: Version
                                         , video :: Video
                                         , workExample :: WorkExample
                                         , additionalType :: AdditionalType
                                         , alternateName :: AlternateName
                                         , description :: Description
                                         , image :: Image
                                         , mainEntityOfPage :: MainEntityOfPage
                                         , name :: Name
                                         , potentialAction :: PotentialAction
                                         , sameAs :: SameAs
                                         , url :: Url
                                         }
                        deriving (Show, Read, Eq, Typeable)

instance MetaData MusicVideoObject where
  _label         = const "Music Video Object"
  _comment_plain = const "A music video file."
  _comment       = const "A music video file."
  _url           = const "http://schema.org/MusicVideoObject"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.MediaObject.MediaObject)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.MediaObject.MediaObject)]