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

-- | A single, identifiable product instance (e.g. a laptop with a particular serial number).
--
--   [@id@] IndividualProduct
--
--   [@label@] Individual Product
--
--   [@comment@] A single, identifiable product instance (e.g. a laptop with a particular serial number).
--
--   [@ancestors@] @'Thing','Product'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'Product'@
--
--   [@url@] <http://schema.org/IndividualProduct>
data IndividualProduct = IndividualProduct { serialNumber :: SerialNumber
                                           , additionalProperty :: AdditionalProperty
                                           , aggregateRating :: AggregateRating
                                           , audience :: Audience
                                           , award :: Award
                                           , brand :: Brand
                                           , category :: Category
                                           , color :: Color
                                           , depth :: Depth
                                           , gtin12 :: Gtin12
                                           , gtin13 :: Gtin13
                                           , gtin14 :: Gtin14
                                           , gtin8 :: Gtin8
                                           , height :: Height
                                           , isAccessoryOrSparePartFor :: IsAccessoryOrSparePartFor
                                           , isConsumableFor :: IsConsumableFor
                                           , isRelatedTo :: IsRelatedTo
                                           , isSimilarTo :: IsSimilarTo
                                           , itemCondition :: ItemCondition
                                           , logo :: Logo
                                           , manufacturer :: Manufacturer
                                           , model :: Model
                                           , mpn :: Mpn
                                           , offers :: Offers
                                           , productID :: ProductID
                                           , productionDate :: ProductionDate
                                           , purchaseDate :: PurchaseDate
                                           , releaseDate :: ReleaseDate
                                           , review :: Review
                                           , sku :: Sku
                                           , weight :: Weight
                                           , width :: Width
                                           , 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 IndividualProduct where
  _label         = const "Individual Product"
  _comment_plain = const "A single, identifiable product instance (e.g. a laptop with a particular serial number)."
  _comment       = const "A single, identifiable product instance (e.g. a laptop with a particular serial number)."
  _url           = const "http://schema.org/IndividualProduct"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Product.Product)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Product.Product)]