{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.Hotel 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.Organization
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.LocalBusiness
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.LodgingBusiness
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.Hotel
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.Place

-- | A hotel.
--
--   [@id@] Hotel
--
--   [@label@] Hotel
--
--   [@comment@] A hotel.
--
--   [@ancestors@] @'Thing','Organization','LocalBusiness','LodgingBusiness','Hotel','Thing','Place','LocalBusiness','LodgingBusiness'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'LodgingBusiness'@
--
--   [@url@] <http://schema.org/Hotel>
data Hotel = Hotel { branchCode :: BranchCode
                   , currenciesAccepted :: CurrenciesAccepted
                   , openingHours :: OpeningHours
                   , paymentAccepted :: PaymentAccepted
                   , priceRange :: PriceRange
                   , address :: Address
                   , aggregateRating :: AggregateRating
                   , alumni :: Alumni
                   , areaServed :: AreaServed
                   , award :: Award
                   , brand :: Brand
                   , contactPoint :: ContactPoint
                   , department :: Department
                   , dissolutionDate :: DissolutionDate
                   , duns :: Duns
                   , email :: Email
                   , employee :: Employee
                   , event :: Event
                   , faxNumber :: FaxNumber
                   , founder :: Founder
                   , foundingDate :: FoundingDate
                   , foundingLocation :: FoundingLocation
                   , globalLocationNumber :: GlobalLocationNumber
                   , hasOfferCatalog :: HasOfferCatalog
                   , hasPOS :: HasPOS
                   , isicV4 :: IsicV4
                   , legalName :: LegalName
                   , location :: Location
                   , logo :: Logo
                   , makesOffer :: MakesOffer
                   , member :: Member
                   , memberOf :: MemberOf
                   , naics :: Naics
                   , numberOfEmployees :: NumberOfEmployees
                   , owns :: Owns
                   , parentOrganization :: ParentOrganization
                   , review :: Review
                   , seeks :: Seeks
                   , subOrganization :: SubOrganization
                   , taxID :: TaxID
                   , telephone :: Telephone
                   , vatID :: VatID
                   , additionalProperty :: AdditionalProperty
                   , containedInPlace :: ContainedInPlace
                   , containsPlace :: ContainsPlace
                   , geo :: Geo
                   , hasMap :: HasMap
                   , openingHoursSpecification :: OpeningHoursSpecification
                   , photo :: Photo
                   , 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 Hotel where
  _label         = const "Hotel"
  _comment_plain = const "A hotel."
  _comment       = const "A hotel."
  _url           = const "http://schema.org/Hotel"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Organization.Organization)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LocalBusiness.LocalBusiness)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LodgingBusiness.LodgingBusiness)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Hotel.Hotel)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Place.Place)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LocalBusiness.LocalBusiness)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.LodgingBusiness.LodgingBusiness)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.LodgingBusiness.LodgingBusiness)]