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

-- | A listing that describes a job opening in a certain organization.
--
--   [@id@] JobPosting
--
--   [@label@] Job Posting
--
--   [@comment@] A listing that describes a job opening in a certain organization.
--
--   [@ancestors@] @'Thing','Intangible'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'Intangible'@
--
--   [@url@] <http://schema.org/JobPosting>
data JobPosting = JobPosting { baseSalary :: BaseSalary
                             , datePosted :: DatePosted
                             , educationRequirements :: EducationRequirements
                             , employmentType :: EmploymentType
                             , experienceRequirements :: ExperienceRequirements
                             , hiringOrganization :: HiringOrganization
                             , incentiveCompensation :: IncentiveCompensation
                             , industry :: Industry
                             , jobBenefits :: JobBenefits
                             , jobLocation :: JobLocation
                             , occupationalCategory :: OccupationalCategory
                             , qualifications :: Qualifications
                             , responsibilities :: Responsibilities
                             , salaryCurrency :: SalaryCurrency
                             , skills :: Skills
                             , specialCommitments :: SpecialCommitments
                             , title :: Title
                             , workHours :: WorkHours
                             , 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 JobPosting where
  _label         = const "Job Posting"
  _comment_plain = const "A listing that describes a job opening in a certain organization."
  _comment       = const "A listing that describes a job opening in a certain organization."
  _url           = const "http://schema.org/JobPosting"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Intangible.Intangible)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Intangible.Intangible)]