{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.PublicationEvent 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.Event
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.BroadcastEvent
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.OnDemandEvent

-- | A PublicationEvent corresponds indifferently to the event of publication for a CreativeWork of any type e.g. a broadcast event, an on-demand event, a book/journal publication via a variety of delivery media.
--
--   [@id@] PublicationEvent
--
--   [@label@] Publication Event
--
--   [@comment@] A PublicationEvent corresponds indifferently to the event of publication for a CreativeWork of any type e.g. a broadcast event, an on-demand event, a book/journal publication via a variety of delivery media.
--
--   [@ancestors@] @'Thing','Event'@
--
--   [@subtypes@] @'BroadcastEvent','OnDemandEvent'@
--
--   [@supertypes@] @'Event'@
--
--   [@url@] <http://schema.org/PublicationEvent>
data PublicationEvent = PublicationEvent { isAccessibleForFree :: IsAccessibleForFree
                                         , publishedOn :: PublishedOn
                                         , 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 PublicationEvent where
  _label         = const "Publication Event"
  _comment_plain = const "A PublicationEvent corresponds indifferently to the event of publication for a CreativeWork of any type e.g. a broadcast event, an on-demand event, a book/journal publication via a variety of delivery media."
  _comment       = const "A PublicationEvent corresponds indifferently to the event of publication for a CreativeWork of any type e.g. a broadcast event, an on-demand event, a book/journal publication via a variety of delivery media."
  _url           = const "http://schema.org/PublicationEvent"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Event.Event)]
  _subtypes      = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.BroadcastEvent.BroadcastEvent)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.OnDemandEvent.OnDemandEvent)]
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Event.Event)]