{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.Answer 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.Comment

-- | An answer offered to a question; perhaps correct, perhaps opinionated or wrong.
--
--   [@id@] Answer
--
--   [@label@] Answer
--
--   [@comment@] An answer offered to a question; perhaps correct, perhaps opinionated or wrong.
--
--   [@ancestors@] @'Thing','CreativeWork','Comment'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'Comment'@
--
--   [@url@] <http://schema.org/Answer>
data Answer = Answer { 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 Answer where
  _label         = const "Answer"
  _comment_plain = const "An answer offered to a question; perhaps correct, perhaps opinionated or wrong."
  _comment       = const "An answer offered to a question; perhaps correct, perhaps opinionated or wrong."
  _url           = const "http://schema.org/Answer"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Comment.Comment)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Comment.Comment)]