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

-- | A part of a successively published publication such as a periodical or multi-volume work, often numbered. It may represent a time span, such as a year.      See also blog post.
--
--   [@id@] PublicationVolume
--
--   [@label@] Publication Volume
--
--   [@comment@] A part of a successively published publication such as a periodical or multi-volume work, often numbered. It may represent a time span, such as a year.      <br/><br/>See also <a href=\"http://blog.schema.org/2014/09/schemaorg-support-for-bibliographic_2.html\">blog post</a>.
--
--   [@ancestors@] @'Thing','CreativeWork'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'CreativeWork'@
--
--   [@url@] <http://schema.org/PublicationVolume>
data PublicationVolume = PublicationVolume { pageEnd :: PageEnd
                                           , pageStart :: PageStart
                                           , pagination :: Pagination
                                           , volumeNumber :: VolumeNumber
                                           , 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 PublicationVolume where
  _label         = const "Publication Volume"
  _comment_plain = const "A part of a successively published publication such as a periodical or multi-volume work, often numbered. It may represent a time span, such as a year.      See also blog post."
  _comment       = const "A part of a successively published publication such as a periodical or multi-volume work, often numbered. It may represent a time span, such as a year.      <br/><br/>See also <a href=\"http://blog.schema.org/2014/09/schemaorg-support-for-bibliographic_2.html\">blog post</a>."
  _url           = const "http://schema.org/PublicationVolume"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)]