{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.ChatFullInfo where
import Data.Aeson (ToJSON(..), FromJSON(..))
import Data.Time.Clock.POSIX (POSIXTime)
import Data.Text (Text)
import GHC.Generics (Generic)
import Telegram.Bot.API.Types.Birthdate
import Telegram.Bot.API.Types.BusinessIntro
import Telegram.Bot.API.Types.BusinessLocation
import Telegram.Bot.API.Types.BusinessOpeningHours
import Telegram.Bot.API.Types.Chat
import Telegram.Bot.API.Types.ChatLocation
import Telegram.Bot.API.Types.ChatPhoto
import Telegram.Bot.API.Types.ChatPermissions
import Telegram.Bot.API.Types.ChatType
import Telegram.Bot.API.Types.Common
import Telegram.Bot.API.Types.Message
import Telegram.Bot.API.Types.ReactionType
import Telegram.Bot.API.Internal.Utils
data ChatFullInfo = ChatFullInfo
  { ChatFullInfo -> ChatId
chatFullInfoId               :: ChatId          
  , ChatFullInfo -> Maybe Bool
chatFullInfoIsBot            :: Maybe Bool      
  , ChatFullInfo -> ChatType
chatFullInfoType             :: ChatType        
  , ChatFullInfo -> Maybe Text
chatFullInfoTitle            :: Maybe Text      
  , ChatFullInfo -> Maybe Text
chatFullInfoUsername         :: Maybe Text      
  , ChatFullInfo -> Maybe Text
chatFullInfoFirstName        :: Maybe Text      
  , ChatFullInfo -> Maybe Text
chatFullInfoLastName         :: Maybe Text      
  , ChatFullInfo -> Maybe Bool
chatFullInfoIsForum          :: Maybe Bool      
  , ChatFullInfo -> Maybe Int
chatFullInfoAccentColorId    :: Maybe Int 
  , ChatFullInfo -> Int
chatFullInfoMaxReactionCount :: Int 
  , ChatFullInfo -> Maybe ChatPhoto
chatFullInfoPhoto            :: Maybe ChatPhoto 
  , ChatFullInfo -> Maybe Text
chatFullInfoActiveUsernames  :: Maybe Text      
  , ChatFullInfo -> Maybe Birthdate
chatFullInfoBirthdate        :: Maybe Birthdate 
  , ChatFullInfo -> Maybe BusinessIntro
chatFullInfoBusinessIntro    :: Maybe BusinessIntro 
  , ChatFullInfo -> Maybe BusinessLocation
chatFullInfoBusinessLocation :: Maybe BusinessLocation 
  , ChatFullInfo -> Maybe BusinessOpeningHours
chatFullInfoBusinessOpeningHours :: Maybe BusinessOpeningHours 
  , ChatFullInfo -> Maybe Chat
chatFullInfoPersonalChat     :: Maybe Chat 
  , ChatFullInfo -> Maybe [ReactionType]
chatFullInfoAvailableReactions :: Maybe [ReactionType] 
  , ChatFullInfo -> Maybe Text
chatFullInfoBackgroundCustomEmojiId :: Maybe Text 
  , ChatFullInfo -> Maybe Int
chatFullInfoProfileAccentColorId :: Maybe Int 
  , ChatFullInfo -> Maybe Text
chatFullInfoProfileBackgroundCustomEmojiId :: Maybe Text 
  , ChatFullInfo -> Maybe Text
chatFullInfoEmojiStatusCustomEmojiId :: Maybe Text 
  , ChatFullInfo -> Maybe POSIXTime
chatFullInfoEmojiStatusExpirationDate :: Maybe POSIXTime 
  , ChatFullInfo -> Maybe Text
chatFullInfoBio              :: Maybe Text      
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasPrivateForwards :: Maybe Bool    
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasRestrictedVoiceAndVideoMessages :: Maybe Bool 
  , ChatFullInfo -> Maybe Bool
chatFullInfoJoinToSendMessages :: Maybe Bool    
  , ChatFullInfo -> Maybe Bool
chatFullInfoJoinByRequest    :: Maybe Bool      
  , ChatFullInfo -> Maybe Text
chatFullInfoDescription      :: Maybe Text      
  , ChatFullInfo -> Maybe Text
chatFullInfoInviteLink       :: Maybe Text      
  , ChatFullInfo -> Maybe Message
chatFullInfoPinnedMessage    :: Maybe Message   
  , ChatFullInfo -> Maybe ChatPermissions
chatFullInfoPermissions      :: Maybe ChatPermissions 
  , ChatFullInfo -> Maybe Int
chatFullInfoSlowModeDelay    :: Maybe Int       
  , ChatFullInfo -> Maybe Int
chatFullInfoUnrestrictBootCount :: Maybe Int 
  , ChatFullInfo -> Maybe POSIXTime
chatFullInfoMessageAutoDeleteTime :: Maybe POSIXTime 
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasAggressiveAntiSpamEnabled :: Maybe Bool 
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasHiddenMembers :: Maybe Bool      
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasProtectedContent :: Maybe Bool   
  , ChatFullInfo -> Maybe Bool
chatFullInfoHasVisibleHistory :: Maybe Bool     
  , ChatFullInfo -> Maybe Text
chatFullInfoStickerSetName   :: Maybe Text      
  , ChatFullInfo -> Maybe Bool
chatFullInfoCanSetStickerSet :: Maybe Bool      
  , ChatFullInfo -> Maybe Text
chatFullInfoCustomEmojiStickerSet :: Maybe Text 
  , ChatFullInfo -> Maybe ChatId
chatFullInfoLinkedChatId     :: Maybe ChatId    
  , ChatFullInfo -> Maybe ChatLocation
chatFullInfoLocation         :: Maybe ChatLocation 
  }
  deriving ((forall x. ChatFullInfo -> Rep ChatFullInfo x)
-> (forall x. Rep ChatFullInfo x -> ChatFullInfo)
-> Generic ChatFullInfo
forall x. Rep ChatFullInfo x -> ChatFullInfo
forall x. ChatFullInfo -> Rep ChatFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChatFullInfo -> Rep ChatFullInfo x
from :: forall x. ChatFullInfo -> Rep ChatFullInfo x
$cto :: forall x. Rep ChatFullInfo x -> ChatFullInfo
to :: forall x. Rep ChatFullInfo x -> ChatFullInfo
Generic, Int -> ChatFullInfo -> ShowS
[ChatFullInfo] -> ShowS
ChatFullInfo -> String
(Int -> ChatFullInfo -> ShowS)
-> (ChatFullInfo -> String)
-> ([ChatFullInfo] -> ShowS)
-> Show ChatFullInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChatFullInfo -> ShowS
showsPrec :: Int -> ChatFullInfo -> ShowS
$cshow :: ChatFullInfo -> String
show :: ChatFullInfo -> String
$cshowList :: [ChatFullInfo] -> ShowS
showList :: [ChatFullInfo] -> ShowS
Show)
instance ToJSON   ChatFullInfo where toJSON :: ChatFullInfo -> Value
toJSON = ChatFullInfo -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON ChatFullInfo where parseJSON :: Value -> Parser ChatFullInfo
parseJSON = Value -> Parser ChatFullInfo
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON