{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.UserComments where
-- Valid: 2016-02-03 (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.Event
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.UserInteraction
-- | UserInteraction and its subtypes is an old way of talking about users interacting with pages. It is generally better to use Action-based vocabulary, alongside types such as Comment.
--
-- [@id@] UserComments
--
-- [@label@] User Comments
--
-- [@comment@] UserInteraction and its subtypes is an old way of talking about users interacting with pages. It is generally better to use Action-based vocabulary, alongside types such as Comment.
--
-- [@ancestors@] @'Thing','Event','UserInteraction'@
--
-- [@subtypes@]
--
-- [@supertypes@] @'UserInteraction'@
--
-- [@url@]
data UserComments = UserComments { commentText :: CommentText
, commentTime :: CommentTime
, creator :: Creator
, discusses :: Discusses
, replyToUrl :: ReplyToUrl
, aggregateRating :: AggregateRating
, attendee :: Attendee
, doorTime :: DoorTime
, duration :: Duration
, endDate :: EndDate
, eventStatus :: EventStatus
, inLanguage :: InLanguage
, location :: Location
, offers :: Offers
, organizer :: Organizer
, performer :: Performer
, previousStartDate :: PreviousStartDate
, recordedIn :: RecordedIn
, review :: Review
, startDate :: StartDate
, subEvent :: SubEvent
, superEvent :: SuperEvent
, typicalAgeRange :: TypicalAgeRange
, workFeatured :: WorkFeatured
, workPerformed :: WorkPerformed
, 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 UserComments where
_label = const "User Comments"
_comment_plain = const "UserInteraction and its subtypes is an old way of talking about users interacting with pages. It is generally better to use Action-based vocabulary, alongside types such as Comment."
_comment = const "UserInteraction and its subtypes is an old way of talking about users interacting with pages. It is generally better to use Action-based vocabulary, alongside types such as Comment. "
_url = const "http://schema.org/UserComments"
_ancestors = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
,typeOf (undefined :: Text.HTML5.MetaData.Schema.Event.Event)
,typeOf (undefined :: Text.HTML5.MetaData.Schema.UserInteraction.UserInteraction)]
_subtypes = const []
_supertypes = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.UserInteraction.UserInteraction)]