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

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

import Text.HTML5.MetaData.Class
import Text.HTML5.MetaData.Type hiding (Comment)
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.Answer

-- | A comment on an item - for example, a comment on a blog post. The comment's content is expressed via the \"text\" property, and its topic via \"about\", properties shared with all CreativeWorks.
--
--   [@id@] Comment
--
--   [@label@] Comment
--
--   [@comment@] A comment on an item - for example, a comment on a blog post. The comment's content is expressed via the \"text\" property, and its topic via \"about\", properties shared with all CreativeWorks.
--
--   [@ancestors@] @'Thing','CreativeWork'@
--
--   [@subtypes@] @'Answer'@
--
--   [@supertypes@] @'CreativeWork'@
--
--   [@url@] <http://schema.org/Comment>
data Comment = Comment { downvoteCount :: DownvoteCount
                       , parentItem :: ParentItem
                       , upvoteCount :: UpvoteCount
                       , 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 Comment where
  _label         = const "Comment"
  _comment_plain = const "A comment on an item - for example, a comment on a blog post. The comment's content is expressed via the \"text\" property, and its topic via \"about\", properties shared with all CreativeWorks."
  _comment       = const "A comment on an item - for example, a comment on a blog post. The comment's content is expressed via the \"text\" property, and its topic via \"about\", properties shared with all CreativeWorks."
  _url           = const "http://schema.org/Comment"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)]
  _subtypes      = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Answer.Answer)]
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)]