{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.VideoGame 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
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.Game
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.VideoGame
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.SoftwareApplication

-- | A video game is an electronic game that involves human interaction with a user interface to generate visual feedback on a video device.
--
--   [@id@] VideoGame
--
--   [@label@] Video Game
--
--   [@comment@] A video game is an electronic game that involves human interaction with a user interface to generate visual feedback on a video device.
--
--   [@ancestors@] @'Thing','CreativeWork','Game','VideoGame','Thing','CreativeWork','SoftwareApplication'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'Game','SoftwareApplication'@
--
--   [@url@] <http://schema.org/VideoGame>
data VideoGame = VideoGame { actor :: Actor
                           , cheatCode :: CheatCode
                           , director :: Director
                           , gamePlatform :: GamePlatform
                           , gameServer :: GameServer
                           , gameTip :: GameTip
                           , musicBy :: MusicBy
                           , playMode :: PlayMode
                           , trailer :: Trailer
                           , applicationCategory :: ApplicationCategory
                           , applicationSubCategory :: ApplicationSubCategory
                           , applicationSuite :: ApplicationSuite
                           , availableOnDevice :: AvailableOnDevice
                           , countriesNotSupported :: CountriesNotSupported
                           , countriesSupported :: CountriesSupported
                           , downloadUrl :: DownloadUrl
                           , featureList :: FeatureList
                           , fileSize :: FileSize
                           , installUrl :: InstallUrl
                           , memoryRequirements :: MemoryRequirements
                           , operatingSystem :: OperatingSystem
                           , permissions :: Permissions
                           , processorRequirements :: ProcessorRequirements
                           , releaseNotes :: ReleaseNotes
                           , screenshot :: Screenshot
                           , softwareAddOn :: SoftwareAddOn
                           , softwareHelp :: SoftwareHelp
                           , softwareRequirements :: SoftwareRequirements
                           , softwareVersion :: SoftwareVersion
                           , storageRequirements :: StorageRequirements
                           , supportingData :: SupportingData
                           , 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
                           , characterAttribute :: CharacterAttribute
                           , gameItem :: GameItem
                           , gameLocation :: GameLocation
                           , numberOfPlayers :: NumberOfPlayers
                           , quest :: Quest
                           , 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 VideoGame where
  _label         = const "Video Game"
  _comment_plain = const "A video game is an electronic game that involves human interaction with a user interface to generate visual feedback on a video device."
  _comment       = const "A video game is an electronic game that involves human interaction with a user interface to generate visual feedback on a video device."
  _url           = const "http://schema.org/VideoGame"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Game.Game)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.VideoGame.VideoGame)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.SoftwareApplication.SoftwareApplication)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Game.Game)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.SoftwareApplication.SoftwareApplication)]