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

-- | A locksmith.
--
--   [@id@] Locksmith
--
--   [@label@] Locksmith
--
--   [@comment@] A locksmith.
--
--   [@ancestors@] @'Thing','Organization','LocalBusiness','HomeAndConstructionBusiness','Locksmith','Thing','Place','LocalBusiness','HomeAndConstructionBusiness'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'HomeAndConstructionBusiness'@
--
--   [@url@] <http://schema.org/Locksmith>
data Locksmith = Locksmith { 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 Locksmith where
  _label         = const "Locksmith"
  _comment_plain = const "A locksmith."
  _comment       = const "A locksmith."
  _url           = const "http://schema.org/Locksmith"
  _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.HomeAndConstructionBusiness.HomeAndConstructionBusiness)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Locksmith.Locksmith)
                         ,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.HomeAndConstructionBusiness.HomeAndConstructionBusiness)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.HomeAndConstructionBusiness.HomeAndConstructionBusiness)]