{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Text.HTML5.MetaData.Schema.Offer 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.Intangible
import {-# SOURCE #-} qualified Text.HTML5.MetaData.Schema.AggregateOffer
-- | An offer to transfer some rights to an item or to provide a service—for example, an offer to sell tickets to an event, to rent the DVD of a movie, to stream a TV show over the internet, to repair a motorcycle, or to loan a book. For GTIN-related fields, see Check Digit calculator and validation guide from GS1.
--
-- [@id@] Offer
--
-- [@label@] Offer
--
-- [@comment@] An offer to transfer some rights to an item or to provide a service—for example, an offer to sell tickets to an event, to rent the DVD of a movie, to stream a TV show over the internet, to repair a motorcycle, or to loan a book.
For GTIN-related fields, see Check Digit calculator and validation guide from GS1.
--
-- [@ancestors@] @'Thing','Intangible'@
--
-- [@subtypes@] @'AggregateOffer'@
--
-- [@supertypes@] @'Intangible'@
--
-- [@url@]
data Offer = Offer { acceptedPaymentMethod :: AcceptedPaymentMethod
, addOn :: AddOn
, advanceBookingRequirement :: AdvanceBookingRequirement
, aggregateRating :: AggregateRating
, areaServed :: AreaServed
, availability :: Availability
, availabilityEnds :: AvailabilityEnds
, availabilityStarts :: AvailabilityStarts
, availableAtOrFrom :: AvailableAtOrFrom
, availableDeliveryMethod :: AvailableDeliveryMethod
, businessFunction :: BusinessFunction
, category :: Category
, deliveryLeadTime :: DeliveryLeadTime
, eligibleCustomerType :: EligibleCustomerType
, eligibleDuration :: EligibleDuration
, eligibleQuantity :: EligibleQuantity
, eligibleRegion :: EligibleRegion
, eligibleTransactionVolume :: EligibleTransactionVolume
, gtin12 :: Gtin12
, gtin13 :: Gtin13
, gtin14 :: Gtin14
, gtin8 :: Gtin8
, includesObject :: IncludesObject
, ineligibleRegion :: IneligibleRegion
, inventoryLevel :: InventoryLevel
, itemCondition :: ItemCondition
, itemOffered :: ItemOffered
, mpn :: Mpn
, offeredBy :: OfferedBy
, price :: Price
, priceCurrency :: PriceCurrency
, priceSpecification :: PriceSpecification
, priceValidUntil :: PriceValidUntil
, review :: Review
, seller :: Seller
, serialNumber :: SerialNumber
, sku :: Sku
, validFrom :: ValidFrom
, validThrough :: ValidThrough
, warranty :: Warranty
, 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 Offer where
_label = const "Offer"
_comment_plain = const "An offer to transfer some rights to an item or to provide a service—for example, an offer to sell tickets to an event, to rent the DVD of a movie, to stream a TV show over the internet, to repair a motorcycle, or to loan a book. For GTIN-related fields, see Check Digit calculator and validation guide from GS1."
_comment = const "An offer to transfer some rights to an item or to provide a service—for example, an offer to sell tickets to an event, to rent the DVD of a movie, to stream a TV show over the internet, to repair a motorcycle, or to loan a book.
For GTIN-related fields, see Check Digit calculator and validation guide from GS1."
_url = const "http://schema.org/Offer"
_ancestors = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
,typeOf (undefined :: Text.HTML5.MetaData.Schema.Intangible.Intangible)]
_subtypes = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.AggregateOffer.AggregateOffer)]
_supertypes = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Intangible.Intangible)]