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

-- | An order is a confirmation of a transaction (a receipt), which can contain multiple line items, each represented by an Offer that has been accepted by the customer.
--
--   [@id@] Order
--
--   [@label@] Order
--
--   [@comment@] An order is a confirmation of a transaction (a receipt), which can contain multiple line items, each represented by an Offer that has been accepted by the customer.
--
--   [@ancestors@] @'Thing','Intangible'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'Intangible'@
--
--   [@url@] <http://schema.org/Order>
data Order = Order { acceptedOffer :: AcceptedOffer
                   , billingAddress :: BillingAddress
                   , broker :: Broker
                   , confirmationNumber :: ConfirmationNumber
                   , customer :: Customer
                   , discount :: Discount
                   , discountCode :: DiscountCode
                   , discountCurrency :: DiscountCurrency
                   , isGift :: IsGift
                   , orderDate :: OrderDate
                   , orderDelivery :: OrderDelivery
                   , orderNumber :: OrderNumber
                   , orderStatus :: OrderStatus
                   , orderedItem :: OrderedItem
                   , partOfInvoice :: PartOfInvoice
                   , paymentDueDate :: PaymentDueDate
                   , paymentMethod :: PaymentMethod
                   , paymentMethodId :: PaymentMethodId
                   , paymentUrl :: PaymentUrl
                   , seller :: Seller
                   , 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 Order where
  _label         = const "Order"
  _comment_plain = const "An order is a confirmation of a transaction (a receipt), which can contain multiple line items, each represented by an Offer that has been accepted by the customer."
  _comment       = const "An order is a confirmation of a transaction (a receipt), which can contain multiple line items, each represented by an Offer that has been accepted by the customer."
  _url           = const "http://schema.org/Order"
  _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)]