{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.Diet 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.Diet
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.MedicalEntity
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.MedicalTherapy
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.LifestyleModification

-- | A strategy of regulating the intake of food to achieve or maintain a specific health-related goal.
--
--   [@id@] Diet
--
--   [@label@] Diet
--
--   [@comment@] A strategy of regulating the intake of food to achieve or maintain a specific health-related goal.
--
--   [@ancestors@] @'Thing','CreativeWork','Diet','Thing','MedicalEntity','MedicalTherapy','LifestyleModification'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'CreativeWork','LifestyleModification'@
--
--   [@url@] <http://schema.org/Diet>
data Diet = Diet { dietFeatures :: DietFeatures
                 , endorsers :: Endorsers
                 , expertConsiderations :: ExpertConsiderations
                 , overview :: Overview
                 , physiologicalBenefits :: PhysiologicalBenefits
                 , proprietaryName :: ProprietaryName
                 , risks :: Risks
                 , 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
                 , adverseOutcome :: AdverseOutcome
                 , contraindication :: Contraindication
                 , duplicateTherapy :: DuplicateTherapy
                 , indication :: Indication
                 , seriousAdverseOutcome :: SeriousAdverseOutcome
                 , code :: Code
                 , guideline :: Guideline
                 , medicineSystem :: MedicineSystem
                 , recognizingAuthority :: RecognizingAuthority
                 , relevantSpecialty :: RelevantSpecialty
                 , study :: Study
                 , 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 Diet where
  _label         = const "Diet"
  _comment_plain = const "A strategy of regulating the intake of food to achieve or maintain a specific health-related goal."
  _comment       = const "A strategy of regulating the intake of food to achieve or maintain a specific health-related goal."
  _url           = const "http://schema.org/Diet"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Diet.Diet)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.MedicalEntity.MedicalEntity)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.MedicalTherapy.MedicalTherapy)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LifestyleModification.LifestyleModification)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.CreativeWork.CreativeWork)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LifestyleModification.LifestyleModification)]