{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.LiveBlogPosting 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.Article
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.SocialMediaPosting
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.BlogPosting

-- | A blog post intended to provide a rolling textual coverage of an ongoing event through continuous updates.
--
--   [@id@] LiveBlogPosting
--
--   [@label@] Live Blog Posting
--
--   [@comment@] A blog post intended to provide a rolling textual coverage of an ongoing event through continuous updates.
--
--   [@ancestors@] @'Thing','CreativeWork','Article','SocialMediaPosting','BlogPosting'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'BlogPosting'@
--
--   [@url@] <http://schema.org/LiveBlogPosting>
data LiveBlogPosting = LiveBlogPosting { coverageEndTime :: CoverageEndTime
                                       , coverageStartTime :: CoverageStartTime
                                       , liveBlogUpdate :: LiveBlogUpdate
                                       , sharedContent :: SharedContent
                                       , articleBody :: ArticleBody
                                       , articleSection :: ArticleSection
                                       , pageEnd :: PageEnd
                                       , pageStart :: PageStart
                                       , pagination :: Pagination
                                       , wordCount :: WordCount
                                       , 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 LiveBlogPosting where
  _label         = const "Live Blog Posting"
  _comment_plain = const "A blog post intended to provide a rolling textual coverage of an ongoing event through continuous updates."
  _comment       = const "A blog post intended to provide a rolling textual coverage of an ongoing event through continuous updates."
  _url           = const "http://schema.org/LiveBlogPosting"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Article.Article)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.SocialMediaPosting.SocialMediaPosting)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.BlogPosting.BlogPosting)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.BlogPosting.BlogPosting)]