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

-- | A unique instance of a radio BroadcastService on a CableOrSatelliteService lineup.
--
--   [@id@] RadioChannel
--
--   [@label@] Radio Channel
--
--   [@comment@] A unique instance of a radio BroadcastService on a CableOrSatelliteService lineup.
--
--   [@ancestors@] @'Thing','Intangible','BroadcastChannel'@
--
--   [@subtypes@]
--
--   [@supertypes@] @'BroadcastChannel'@
--
--   [@url@] <http://schema.org/RadioChannel>
data RadioChannel = RadioChannel { broadcastChannelId :: BroadcastChannelId
                                 , broadcastServiceTier :: BroadcastServiceTier
                                 , inBroadcastLineup :: InBroadcastLineup
                                 , providesBroadcastService :: ProvidesBroadcastService
                                 , 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 RadioChannel where
  _label         = const "Radio Channel"
  _comment_plain = const "A unique instance of a radio BroadcastService on a CableOrSatelliteService lineup."
  _comment       = const "A unique instance of a radio BroadcastService on a CableOrSatelliteService lineup."
  _url           = const "http://schema.org/RadioChannel"
  _ancestors     = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.Intangible.Intangible)
                         ,typeOf (undefined :: Text.HTML5.MetaData.Schema.BroadcastChannel.BroadcastChannel)]
  _subtypes      = const []
  _supertypes    = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.BroadcastChannel.BroadcastChannel)]