{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.WebPage 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.AboutPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.CheckoutPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.CollectionPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.ContactPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.ItemPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.MedicalWebPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.ProfilePage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.QAPage
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.SearchResultsPage

-- | A web page. Every web page is implicitly assumed to be declared to be of type WebPage, so the various properties about that webpage, such as breadcrumb may be used. We recommend explicit declaration if these properties are specified, but if they are found outside of an itemscope, they will be assumed to be about the page.
--
--   [@id@] WebPage
--
--   [@label@] Web Page
--
--   [@comment@] A web page. Every web page is implicitly assumed to be declared to be of type WebPage, so the various properties about that webpage, such as <code>breadcrumb</code> may be used. We recommend explicit declaration if these properties are specified, but if they are found outside of an itemscope, they will be assumed to be about the page.
--
--   [@ancestors@] @'Thing','CreativeWork'@
--
--   [@subtypes@] @'AboutPage','CheckoutPage','CollectionPage','ContactPage','ItemPage','MedicalWebPage','ProfilePage','QAPage','SearchResultsPage'@
--
--   [@supertypes@] @'CreativeWork'@
--
--   [@url@] <http://schema.org/WebPage>
data WebPage = WebPage { breadcrumb :: Breadcrumb
                       , lastReviewed :: LastReviewed
                       , mainContentOfPage :: MainContentOfPage
                       , primaryImageOfPage :: PrimaryImageOfPage
                       , relatedLink :: RelatedLink
                       , reviewedBy :: ReviewedBy
                       , significantLink :: SignificantLink
                       , specialty :: Specialty
                       , 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 WebPage where
  _label         = const "Web Page"
  _comment_plain = const "A web page. Every web page is implicitly assumed to be declared to be of type WebPage, so the various properties about that webpage, such as breadcrumb may be used. We recommend explicit declaration if these properties are specified, but if they are found outside of an itemscope, they will be assumed to be about the page."
  _comment       = const "A web page. Every web page is implicitly assumed to be declared to be of type WebPage, so the various properties about that webpage, such as <code>breadcrumb</code> may be used. We recommend explicit declaration if these properties are specified, but if they are found outside of an itemscope, they will be assumed to be about the page."
  _url           = const "http://schema.org/WebPage"
  _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.AboutPage.AboutPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CheckoutPage.CheckoutPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CollectionPage.CollectionPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.ContactPage.ContactPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.ItemPage.ItemPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.MedicalWebPage.MedicalWebPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.ProfilePage.ProfilePage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.QAPage.QAPage)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.SearchResultsPage.SearchResultsPage)]
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)]