{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.ForumTopic where

import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Text (Text)
import GHC.Generics (Generic)

import Telegram.Bot.API.Types.Common
import Telegram.Bot.API.Internal.Utils

-- ** 'ForumTopic'

-- | This object represents a forum topic.
data ForumTopic = ForumTopic
  { ForumTopic -> MessageThreadId
forumTopicMessageThreadId   :: MessageThreadId -- ^ Unique identifier of the forum topic
  , ForumTopic -> Text
forumTopicName              :: Text            -- ^ Name of the topic
  , ForumTopic -> Integer
forumTopicIconColor         :: Integer         -- ^ Color of the topic icon in RGB format.
  , ForumTopic -> Maybe Text
forumTopicIconCustomEmojiId :: Maybe Text      -- ^ Unique identifier of the custom emoji shown as the topic icon.
  }
  deriving (forall x. Rep ForumTopic x -> ForumTopic
forall x. ForumTopic -> Rep ForumTopic x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForumTopic x -> ForumTopic
$cfrom :: forall x. ForumTopic -> Rep ForumTopic x
Generic, Int -> ForumTopic -> ShowS
[ForumTopic] -> ShowS
ForumTopic -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForumTopic] -> ShowS
$cshowList :: [ForumTopic] -> ShowS
show :: ForumTopic -> String
$cshow :: ForumTopic -> String
showsPrec :: Int -> ForumTopic -> ShowS
$cshowsPrec :: Int -> ForumTopic -> ShowS
Show)

instance ToJSON   ForumTopic where toJSON :: ForumTopic -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON ForumTopic where parseJSON :: Value -> Parser ForumTopic
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON